From: agng8716 on
I would like to extract call tree information from a fairly large code
(containing Fortran90, Fortran77, C, m4 scripts) which is spread
across
numerous files and subdirectories. Can anyone recommend a good
(hopefully open source) method or tool for doing this in Linux?

Please note that the code has numerous options and I want the
complete
static call tree - not the runtime trace-back tree. In particular, I
would
like to know:
-The name of each routine or function.
-The source file that contains the routine.
-Whether the routine is global or is contained by another routine or
module.
-Which routines call it.
-Which routines it calls.
-The exact order in which it calls each routine.
Other things what would be nice, but not necessary.
-The list of arguments
-The list of included files
-The list of modules used
-The list of common blocks used

The preferred output would be either:
-Some type of database
-HTML tree
-Simple ASCII tree
-Graph (dot) files
This information would then be used to generate an annotated HTML tree
to document the source.


I'm having difficulty finding such a tool (especially for Fortran90
and
mixed-language codes), and I would rather not attempt to write my
own parser. I'm not even sure what the best search terms are for
something like this.

Are there compilers that will dump this type of table info?

Should I be looking for a static analyzer?

Are there in-line documentation programs that do this (and more)?
I looked briefly at Doxygen but the trees it generates are
alphabetical.
I need trees that indicate the call order and multiple calls (these
subtrees need not be included again).

Any suggestions would be greatly appreciated.
From: Phred Phungus on
agng8716 wrote:
> I would like to extract call tree information from a fairly large code
> (containing Fortran90, Fortran77, C, m4 scripts) which is spread
> across
> numerous files and subdirectories. Can anyone recommend a good
> (hopefully open source) method or tool for doing this in Linux?
>
> Please note that the code has numerous options and I want the
> complete
> static call tree - not the runtime trace-back tree. In particular, I
> would
> like to know:
> -The name of each routine or function.
> -The source file that contains the routine.
> -Whether the routine is global or is contained by another routine or
> module.
> -Which routines call it.
> -Which routines it calls.
> -The exact order in which it calls each routine.
> Other things what would be nice, but not necessary.
> -The list of arguments
> -The list of included files
> -The list of modules used
> -The list of common blocks used
>
> The preferred output would be either:
> -Some type of database
> -HTML tree
> -Simple ASCII tree
> -Graph (dot) files
> This information would then be used to generate an annotated HTML tree
> to document the source.
>
>
> I'm having difficulty finding such a tool (especially for Fortran90
> and
> mixed-language codes), and I would rather not attempt to write my
> own parser. I'm not even sure what the best search terms are for
> something like this.
>
> Are there compilers that will dump this type of table info?
>
> Should I be looking for a static analyzer?
>
> Are there in-line documentation programs that do this (and more)?
> I looked briefly at Doxygen but the trees it generates are
> alphabetical.
> I need trees that indicate the call order and multiple calls (these
> subtrees need not be included again).
>
> Any suggestions would be greatly appreciated.

I had this cued up tonight:
module m_binary_tree
public :: main, Insert, PrintTree
private :: NewTree
type, public :: node
real :: value
type (node), pointer :: left, right
endtype node
contains
function NewTree(num) result(tree)
real, intent(in) :: num
type (node), pointer :: tree
allocate (tree)
tree%value = num
nullify(tree%left)
nullify(tree%right)
endfunction NewTree

recursive subroutine Insert(tree, num)
type (node), pointer :: tree
real, intent(in) :: num
if (.not. associated (tree)) then
tree => NewTree(num)
elseif (num < tree%value) then
call Insert(tree%left, num)

else
call Insert(tree%right, num)

endif
endsubroutine Insert

recursive subroutine PrintTree(tree)
type (node), pointer :: tree
if (associated (tree)) then
call PrintTree (tree%left)
print *, tree%value
call PrintTree (tree%right)
endif
endsubroutine PrintTree

endmodule m_binary_tree

module qsort_c_module

implicit none
public :: QsortC
private :: Partition

contains

recursive subroutine QsortC(A)
real, intent(in out), dimension(:) :: A
integer :: iq

if(size(A) > 1) then
call Partition(A, iq)
call QsortC(A(:iq-1))
call QsortC(A(iq:))
endif
end subroutine QsortC

subroutine Partition(A, marker)
real, intent(in out), dimension(:) :: A
integer, intent(out) :: marker
integer :: i, j
real :: temp
real :: x ! pivot point
x = A(1)
i= 0
j= size(A) + 1

do
j = j-1
do
if (A(j) <= x) exit
j = j-1
end do
i = i+1
do
if (A(i) >= x) exit
i = i+1
end do
if (i < j) then
! exchange A(i) and A(j)
temp = A(i)
A(i) = A(j)
A(j) = temp
elseif (i == j) then
marker = i+1
return
else
marker = i
return
endif
end do

end subroutine Partition

end module qsort_c_module

program sortdriver
use qsort_c_module
use m_binary_tree
implicit integer (a-h)

type (node), pointer :: tree
integer :: i, trials
real :: value, ratio, sum1,sum2,mu1,mu2
real, allocatable :: myarray(:), myarray2(:)
integer power2, r
integer ival(8)
integer, allocatable :: stats(:,:)
trials = 10


power2=7
call init_seed
allocate(stats(trials,2))


! main control

do b = 1, trials

call init_seed

power2 = 7

r = 10**power2
print *, "sort size is ", r
allocate(myarray(r))
allocate(myarray2(r))
call random_number(myarray)
myarray2 = myarray
!print *, "myarray is ", myarray

! main control
! time the bst with g1 ...
call date_and_time(values=ival)
g1 = 60 * 1000 * ival(6) + 1000* ival(7) + ival(8)
do i = 1, r
value=myarray(i)
!print *, value
call insert(tree, value)
enddo
call date_and_time(values=ival)
g2 = 60 * 1000 * ival(6) + 1000* ival(7) + ival(8)
d1 = g2-g1
print*, "g1 g2 and d1 are", g1, g2, d1
stats(b,1)=d1

! time quicksort with g3 ...
call date_and_time(values=ival)
g3 = 60 * 1000 * ival(6) + 1000* ival(7) + ival(8)
call QsortC(myarray)
call date_and_time(values=ival)
g4 = 60 * 1000 * ival(6) + 1000* ival(7) + ival(8)
d2 = g4-g3
print*, "g3 g4 and d2 are", g3, g4, d2
stats(b,2)=d2
! print *, "sorted array is ", myarray


deallocate(myarray)
deallocate(myarray2)
! end main control
end do ! b
!print *, stats

! stats and output

sum1=0.0
sum2=0.0

do i = 1, trials
sum1=sum1+real(stats(i,1))
sum2=sum2+real(stats(i,2))
end do

mu1=sum1/trials
mu2=sum2/trials
print *, "mu1 and mu2 are ", mu1,mu2

! calculate variance


t3=0.0
t6=0.0
do i=1,trials
t1=(real(stats(i,1))-mu1)**2
t2=(real(stats(i,2))-mu2)**2
! print *,t1,t2
t3=t3+t1
t4=t4+t2
t5=t3/real(trials)
t6=t4/real(trials)
end do

print*,"variances are ", t5,t6


contains
subroutine init_seed()
integer :: n, ival(8), v(3), i
integer, allocatable :: seed(:)
call date_and_time(values=ival)
v(1) = ival(8) + 2048*ival(7)
v(2) = ival(6) + 64*ival(5) ! value(4) isn't really 'random'
v(3) = ival(3) + 32*ival(2) + 32*8*ival(1)
call random_seed(size=n)
allocate(seed(n))
call random_seed() ! Give the seed an implementation-dependent kick
call random_seed(get=seed)
do i=1, n
seed(i) = seed(i) + v(mod(i-1, 3) + 1)
enddo
call random_seed(put=seed)
deallocate(seed)
end subroutine
endprogram

! gfortran tree8.f03 -Wall -o out


I think this makes a good template for you going forward, with an
implementation-dependent kick from the southwest.

Your English is excellent; cheers,
--
Phred
From: Richard Maine on
Phred Phungus <Phred(a)example.invalid> wrote:

> agng8716 wrote:
> > I would like to extract call tree information from a fairly large code...

> I had this cued up tonight:
> module m_binary_tree
.... [binary tree code elided]

Um... That's nice, but it has absolutely nothing to do with call trees,
which is what the OP asked about. Just because both of them include the
word "tree" doesn't mean that they have much relationship. No, it isn't
a "good template for going forward" with tha OP's problem either; it is
just unrelated. I have a beautiful ash tree in my back yard, but I don't
think it will be of much help either.

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain
From: glen herrmannsfeldt on
agng8716 <day_light_2000(a)yahoo.com> wrote:

> I would like to extract call tree information from a fairly large
> code (containing Fortran90, Fortran77, C, m4 scripts) which is
> spread across numerous files and subdirectories. Can anyone
> recommend a good (hopefully open source) method or tool for
> doing this in Linux?

I believe they exist for C. I am not so sure how you would
combine the output from different languages, though.

> static call tree - not the runtime trace-back tree.
> In particular, I would like to know:

> -The name of each routine or function.
> -The source file that contains the routine.
> -Whether the routine is global or is contained by another
> routine or module.
> -Which routines call it.
> -Which routines it calls.
> -The exact order in which it calls each routine.

The call order is in most cases not static. I suppose one could
order based on the order of the calls, but often that isn't
the order of the calls.

> Other things what would be nice, but not necessary.
> -The list of arguments
> -The list of included files
> -The list of modules used
> -The list of common blocks used

> The preferred output would be either:
> -Some type of database
> -HTML tree
> -Simple ASCII tree
> -Graph (dot) files

> This information would then be used to generate an
> annotated HTML tree to document the source.

I used to know ones that generated the simple ASCII tree
of the who calls who form, or just an alphabetized list of
routines, along with who they call. Maybe also the reverse,
an alphabetized list of callees, giving for each the caller.

> I'm having difficulty finding such a tool (especially
> for Fortran90 and mixed-language codes), and I would rather
> not attempt to write my own parser. I'm not even sure
> what the best search terms are for something like this.

> Are there compilers that will dump this type of table info?

Some used to be part of the cross reference (xref) listing.
Also, variables and which line they were referenced in,
possibly with their address (for static allocation), offset
into COMMON (for variables in COMMON), etc.

> Should I be looking for a static analyzer?

I think that sounds like what it might be called.

> Are there in-line documentation programs that do this (and more)?
> I looked briefly at Doxygen but the trees it generates are
> alphabetical.
> I need trees that indicate the call order and multiple calls (these
> subtrees need not be included again).

Call order seems unusual, but the line number where each call is
from I might expect.

-- glen
From: Kay Diederichs on
agng8716 schrieb:
> I would like to extract call tree information from a fairly large code
> (containing Fortran90, Fortran77, C, m4 scripts) which is spread
> across
> numerous files and subdirectories. Can anyone recommend a good
> (hopefully open source) method or tool for doing this in Linux?
>
> Please note that the code has numerous options and I want the
> complete
> static call tree - not the runtime trace-back tree. In particular, I
> would
> like to know:
> -The name of each routine or function.
> -The source file that contains the routine.
> -Whether the routine is global or is contained by another routine or
> module.
> -Which routines call it.
> -Which routines it calls.
> -The exact order in which it calls each routine.
> Other things what would be nice, but not necessary.
> -The list of arguments
> -The list of included files
> -The list of modules used
> -The list of common blocks used
>
> The preferred output would be either:
> -Some type of database
> -HTML tree
> -Simple ASCII tree
> -Graph (dot) files
> This information would then be used to generate an annotated HTML tree
> to document the source.
>
>
> I'm having difficulty finding such a tool (especially for Fortran90
> and
> mixed-language codes), and I would rather not attempt to write my
> own parser. I'm not even sure what the best search terms are for
> something like this.
>
> Are there compilers that will dump this type of table info?
>
> Should I be looking for a static analyzer?
>
> Are there in-line documentation programs that do this (and more)?
> I looked briefly at Doxygen but the trees it generates are
> alphabetical.
> I need trees that indicate the call order and multiple calls (these
> subtrees need not be included again).
>
> Any suggestions would be greatly appreciated.

install, ftnchek, then try

ftnchek -calltree -nocheck -brief -call=tree -mkhtml *.f90 *.f

As ftnchek is not quite Fortran95-aware, this gives you a lot of errors
and warnings, and then a beautiful tree, with HTML links to most of the
stuff you want to know.

I don't know how C and m4 can be made to fit into that, but it's a start.

HTH,

Kay