forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

use of /xref

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Thu Apr 04, 2019 5:13 am    Post subject: use of /xref Reply with quote

I have been investigating the use of /xref and I am finding a few problems.
When I review the results, I am getting a lot of incorrect reports. For example; the routine daxpy is at the end of a file from lines 520:532 and consists of:
Code:
   subroutine daxpy ( n, a, x, y )
!   [y] = [y] + a * [x]
      integer*4, INTENT (IN)    :: n
      real*8,    INTENT (IN)    :: x(n), a
      real*8,    INTENT (INOUT) :: y(n)

      if ( n==1 ) then
        y(1) = y(1) + a * x(1)
      else
        y = y + a * x
      end if

   end subroutine daxpy

The xref produced includes
Code:
Generating information for SUBROUTINE DAXPY

DOUBLE PRECISION, INTENT(IN), ARGUMENT :: A
   317,     333,     347,     348,     349*,    351*,    359, 
   363,     364,     385,     405,     425,     427,     429, 
   457,     494,     515,     543,     558,     566,     599, 
   606,     614,     631,     641*,    646*,    681,     691, 
   693,     736,     740,     742   

SUBROUTINE DAXPY

INTEGER, INTENT(IN), ARGUMENT :: N
   314,     315,     317,     327,     333,     385,     405*,
   421,     425,     427,     429,     453,     454,     457, 
   466,     467,     468,     494,     515,     538,     539, 
   543,     549,     550,     558,     566,     595,     596, 
   599,     606,     614,     626,     627,     631,     636, 
   645,     677,     678,     681,     686,     730*,    735, 
   736,     738,     739   

DOUBLE PRECISION, INTENT(IN), ARGUMENT, DIMENSION(1:) :: X
   317,     345,     347,     363*,    365,     390,     404, 
   425,     427,     429,     457,     494,     543,     558, 
   599,     606,     631,     641,     681,     693,     736, 
   740,     742   

DOUBLE PRECISION, INTENT(INOUT), ARGUMENT, DIMENSION(1:) :: Y
   315,     332,     333,     389,     400,     425,     427, 
   429,     454,     468,     494,     515,     539,     558, 
   566,     596,     606,     614,     631,     646,     678, 
   690,     738,     740*,    742* 

My understanding is that the numbers refer to line numbers, which should be in the range 520:532 ?
In general the line number references are not correct.
There are 13 routines in the file, which has USE, INCLUDE and CONTAINS being used.
I am using:
Silverfrost FTN95/.NET Copyright (C) 1993-2018 Silverfrost Ltd
Version: 8.40.0
Built: Mon Nov 12 12:24:36 2018

Actually I am also investigating a reverse xref, where I can list all places where a routine is being referenced. I was intending to generate .xrf files and then try to interpret them and so produce the reverse reference.

I thought there was once a /XREFS option (FTN77 ?) that listed only those variables that are defined AND used, which excludes listing variables in INCLUDE and USE that are not used in the routine.

I would be happy to explain further or email an example.

John
Back to top
View user's profile Send private message
wahorger



Joined: 13 Oct 2014
Posts: 1217
Location: Morrison, CO, USA

PostPosted: Thu Apr 04, 2019 5:32 am    Post subject: Reply with quote

I am interested in this as well! There is a lot of information to be gleaned, especially for large programs with many routines, COMMON's, and TYPE's.
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7916
Location: Salford, UK

PostPosted: Thu Apr 04, 2019 6:57 am    Post subject: Reply with quote

An example would be helpful but I suspect that this issue will be given a low priority.
Back to top
View user's profile Send private message AIM Address
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Thu Apr 04, 2019 9:51 am    Post subject: Reply with quote

Paul,

In the short term : to check the problem only
I would prefer not to post the actual code on the forum, but I expect the problem is more general.
Could I email the example : ( 2 x .f90 files and 6 x .ins files )
One .f90 file for module definition, then .f90 file I am hoping to generate a .xrf file from. ( It uses INCLUDE, USE and CONTAIN in earlier routines )
The resulting .xrf has lists of line numbers that are not possible.
I was hoping FTN95's list generation could be inspected to see what is causing the problem.

In the longer term:
Abbreviated xref reporting
The other question: is there a /xrefs option ?
This eliminates reporting variables declared in INCLUDE files, but not referenced.
I thought it was FTN77, but it may have been Pr1me Fortran !!
I would like that extended to USE also.

Even longer term
Reverse xrf option for external routines
I was also wondering if the report could be in a .csv file format, possibly with fixed column definitions then a list of line numbers.
( like the /timing report options )
This option could be a precursor to like ifort's checking of routine argument list,
where (I think) it creates an effective INTERFACE for all routines, then checks with all use.
The other usage is to identify everywhere that a routine is being used and if the argument list is compatible.
Pre F90 memory management always breaks this test.

This is where I am trying to head with this post.

John
Back to top
View user's profile Send private message
John-Silver



Joined: 30 Jul 2013
Posts: 1520
Location: Aerospace Valley

PostPosted: Fri Apr 05, 2019 12:53 am    Post subject: Reply with quote

John, you say your code has INCLUDE's.
Could the line numbers refer to the complete concatenated files line-numbering ?
_________________
''Computers (HAL and MARVIN excepted) are incredibly rigid. They question nothing. Especially input data.Human beings are incredibly trusting of computers and don't check input data. Together cocking up even the simplest calculation ... Smile "
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Fri Apr 05, 2019 4:57 am    Post subject: Reply with quote

John S,

For the example I provided, the problem is more extensive than that, as you can see in the original post, variable A is reported for 32 lines, but only appears on 4 lines. There are only 10 code lines in the routine.

I have now generated a simple example listed below, by repeating the same code. The following code has 6 routines.
When compiling routines ftn95 xz.f90 /xref, routines 5 and 6 are reporting extra code lines, outside the scope of the routine.
For larger code examples I have tested, this problem appears in the 3rd routine.
Code:
   REAL*8 function ddotp (n,x,y)
!z      ddotp = dot_product ( x, y )
      integer*4, INTENT (IN) :: n
      real*8,    INTENT (IN) :: x(n), y(n)
!
      integer*4 i
      real*8    ac
!
!  let the compiler optimise this
      if ( n == 1 ) then
        ac = x(1)*y(1)
      else   
        ac = 0
        do i = 1,n
          ac = ac + x(i)*y(i)
        end do
      end if
      ddotp = ac
   end function ddotp

   subroutine daxpy ( n, a, x, y )
!   [y] = [y] + a * [x]
      integer*4, INTENT (IN)    :: n
      real*8,    INTENT (IN)    :: x(n), a
      real*8,    INTENT (INOUT) :: y(n)

      if ( n==1 ) then
        y(1) = y(1) + a * x(1)
      else
        y = y + a * x
      end if

   end subroutine daxpy

   REAL*8 function xdotp (n,x,y)
!z      xdotp = dot_product ( x, y )
      integer*4, INTENT (IN) :: n
      real*8,    INTENT (IN) :: x(n), y(n)
!
      integer*4 i
      real*8    ac
!
!  let the compiler optimise this
      if ( n == 1 ) then
        ac = x(1)*y(1)
      else   
        ac = 0
        do i = 1,n
          ac = ac + x(i)*y(i)
        end do
      end if
      xdotp = ac
   end function xdotp

   subroutine xaxpy ( n, a, x, y )
!   [y] = [y] + a * [x]
      integer*4, INTENT (IN)    :: n
      real*8,    INTENT (IN)    :: x(n), a
      real*8,    INTENT (INOUT) :: y(n)

      if ( n==1 ) then
        y(1) = y(1) + a * x(1)
      else
        y = y + a * x
      end if

   end subroutine xaxpy

   REAL*8 function zdotp (n,x,y)
!z      zdotp = dot_product ( x, y )
      integer*4, INTENT (IN) :: n
      real*8,    INTENT (IN) :: x(n), y(n)
!
      integer*4 i
      real*8    ac
!
!  let the compiler optimise this
      if ( n == 1 ) then
        ac = x(1)*y(1)
      else   
        ac = 0
        do i = 1,n
          ac = ac + x(i)*y(i)
        end do
      end if
      zdotp = ac
   end function zdotp

   subroutine zaxpy ( n, a, x, y )
!   [y] = [y] + a * [x]
      integer*4, INTENT (IN)    :: n
      real*8,    INTENT (IN)    :: x(n), a
      real*8,    INTENT (INOUT) :: y(n)

      if ( n==1 ) then
        y(1) = y(1) + a * x(1)
      else
        y = y + a * x
      end if

   end subroutine zaxpy
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group