Content

LapackDoc

The intension of this project is a robust, maintainable, standalone and simple-to-use documentation tool for LAPACK. However, some of the core ingredients like the Fortran 77 lexer and parser f77crash might also be valuable for other documentation tools (e.g. doxygen). Technically f77crash is based on Netlib's f2c.

Fortran Lexer and Parser: f77crash

f77crash is short for “Fortran 77 cross referencing and syntax highlighting”. The tool lexes and parses a Fortran source code. An in particular it extracts from the source code the locations of types, variables, statements, constants and so on.

Simple Code

For demonstrating the functionality of f77crash consider this small and simple code snippet

      DO 10 I = 120
         X = Y * Z
   10 CONTINUE

Running f77crash on this Fortran code results in

$shell> f77crash/f77crash examples/simple.f                        
STATEMENT,0.6:0.7,0,33,do
CONSTANT,0.9:0.10,0,6,10
STATEMENT,0.14:0.14,0,76,=
CONSTANT,0.16:0.16,0,6,1
CONSTANT,0.19:0.20,0,6,20
STATEMENT,1.11:1.11,0,76,=
STATEMENT,1.15:1.15,0,82,*
STATEMENT,2.6:2.13,10,29,continue

Code locations are presented in the format line.column:line.column. Counting start at zero. So e.g. STATEMENT,0.6:0.7,0,33,do the statement do starts in row (first row), column 6 and ends in row , column 7.

Cool Example (VIM Syntax Highlighting Fails)

For demonstrating the power of f77crash we next consider a more complicated example. At a first glance the code looks obscure and illegal. But it actually is correct Fortran code as spaces are ignored.

      D O U B L E P R E C I S I O N  DO 10I
      INT E GER                      I

      DO 10 I = 120
         DO 10 I = 1.20
   10 CONTINUE

Here the syntax highlighting of most text editor (in this case VIM) produces wrong results. For example DO 10 I = 1.20 inside the loop is an assignment with left hand side variable DO10I and right hand side value 1.20.

The f77crash lexer and parser correctly detects all the tricky stuff:

$shell> f77crash/f77crash examples/obscure.f                       
TYPE,0.6:0.34,0,34,doubleprecision
TYPE,1.6:1.14,0,52,integer
STATEMENT,3.6:3.7,0,33,do
CONSTANT,3.9:3.10,0,6,10
STATEMENT,3.14:3.14,0,76,=
CONSTANT,3.16:3.16,0,6,1
CONSTANT,3.19:3.20,0,6,20
STATEMENT,4.17:4.17,0,76,=
CONSTANT,4.19:4.22,0,7,1.20
STATEMENT,5.6:5.13,10,29,continue
DEFINITION,0.37:0.42,1,do10i
DEFINITION,1.37:1.37,2,i
VARIABLE,3.12:3.12,2,i
VARIABLE,4.9:4.15,1,do10i

Syntax Highlighted and Cross Referenced Fortran Code: f2html

The output of f77crash can be used to create syntax highlighted and cross referenced listings. The f2html tool is a simple Perl script for this purpose.

First we store the output of f77crash in a file obscure.crash. Then we use f2html for producing a highlighted listing in HTML.

$shell> f77crash/f77crash examples/obscure.f > obscure.crash            
$shell> ./f2html obscure.crash examples/obscure.f  > obscure.html       

This results in the following HTML code:

      D O U B L E P R E C I S I O N  DO 10I
      INT E GER                      I

      DO 10 I = 120
         DO 10 I = 1.20
   10 CONTINUE

Note that the variables are cross referenced (indicated by the dotted underlining). Clicking the variable names lets you jump to its definition.

Cross Referencing External Subroutines

Having large projects (e.g. LAPACK) a user is very grateful for diagrams displaying dependencies. This includes caller trees (what functions/routines get called) and call trees (who calls a given function/routine). Furthermore in listings calls to external functions or subroutines can be cross referenced. That means clicking the functions name let's you jump to the external definition.

Setting up an Example

f77crash outputs all information relevant for external dependencies on STDERR. This includes calls to external routines as well as definitions of subroutines and programs. We store the result in a *.deps file.

For illustration the concept we setup a bunch of Fortran routines that partially call each other. For each of them we create a *.crash and *.deps file. And we focus on the information contained in the *.deps files.

Program MYCALLER

The main program simply calls an external routine MYSUPR.

      PROGRAM MYCALLER

      EXTERNAL MYSUBR

      CALL MYSUBR(3)

      END

We now store the output on STDOUT and STDERR in separate files.

$shell> f77crash/f77crash examples/mycaller.f > mycaller.crash 2> mycaller.deps           
$shell> cat mycaller.crash                                              
UNITSTATEMENT,0.6:0.12,0,60,program
TYPE,2.6:2.13,0,42,external
IDENTIFIER,4.6:4.9,0,24,call
CONSTANT,4.18:4.18,0,6,3
UNITSTATEMENT,6.6:6.8,0,37,end
EXTERNAL,2.15:2.20,mysubr
EXTERNAL,4.11:4.16,mysubr
PROGRAM,0.14:0.21,mycaller
$shell> cat mycaller.deps                                               
mycaller,PROGRAM,1,examples/mycaller.f
mycaller,CALLS,mysubr,examples/mycaller.f

From the content of mycaller.deps you see that mycaller.f defines a program and calls mysubr.

Subroutine MYSUBR

Depending on some condition MYSUPR either calls FOOor DUMMY

      SUBROUTINE MYSUBR( N )

      INTEGER  N

      EXTERNAL FOO, DUMMY

      IF( N .GT. 1 ) THEN
         CALL FOO( N-1 )
      ELSE
         CALL DUMMY
      END IF

      END

So relevant for the dependencies is:

$shell> f77crash/f77crash examples/mysubr.f > mysubr.crash 2> mysubr.deps               
$shell> cat mysubr.deps                                                 
mysubr,SUBROUTINE,1,examples/mysubr.f
mysubr,CALLS,foo,examples/mysubr.f
mysubr,CALLS,dummy,examples/mysubr.f

From the content of mysubr.deps you see that mysubr.f defines the subroutine mysubr and calls foo and dummy.

Subroutine FOO

FOO in turn calls MYSUBR

      SUBROUTINE FOO( N )

      INTEGER  N

      EXTERNAL MYSUBR

      CALL MYSUBR( N )

      END

So relevant for the dependencies is:

$shell> f77crash/f77crash examples/foo.f > foo.crash 2> foo.deps                  
$shell> cat foo.deps                                                    
foo,SUBROUTINE,1,examples/foo.f
foo,CALLS,mysubr,examples/foo.f

From the content of foo.deps you see that foo.f defines the subroutine foo and calls mysubr.

Subroutine DUMMY

Now DUMMY is lazy and doing exactly nothing.

      SUBROUTINE DUMMY
*
*     Bla, bla, bla
*
      END

So relevant for the dependencies is:

$shell> f77crash/f77crash examples/dummy.f > dummy.crash 2> dummy.deps                
$shell> cat dummy.deps                                                  
dummy,SUBROUTINE,1,examples/dummy.f

From the content of dummy.deps you see that dummy.f defines the subroutine dummy.

Create an Dependency Archive

We now have for all our source files a corresponding *.deps file. Next we accumulate them in a single archive. From this archive we later can create call and caller graphs for individual routines.

The archive gets created with the deparch tool.

$shell> ./deparch --create-archive=my.deparch --deps-path=.             

The created archive is called my.deparch and contains all the *.deps files found in the current directory (i.e. .).

Create a Call Graph

The deparch tool can also be used to extract call and caller graphs. The output is in a format that can be used as input for dot (from Graphviz).

Let us create a call tree for MYSUBR. We create a dot source file with

$shell> ./deparch --import-archive=my.deparch --extract-call=mysubr > mysubr.call                                         
$shell> cat mysubr.call                                                 
digraph mysubr_CallGraph {
    foo -> mysubr;
    mysubr -> dummy;
    mysubr -> foo;
    mysubr [URL="examples/mysubr.f.html#1" target="_top"];
    foo [URL="examples/foo.f.html#1" target="_top"];
    dummy [URL="examples/dummy.f.html#1" target="_top"];
}

Then we create a svg (Scalable Vector Graphics) file.

$shell> dot -Tsvg -o mysubr.call.svg mysubr.call                        

Which looks like that

mysubr_CallGraph foo foo mysubr mysubr foo->mysubr mysubr->foo dummy dummy mysubr->dummy

Note that the nodes are also linked with the corresponding source files.

Create a Caller Graph

In an analogous way we can create a caller graph:

$shell> ./deparch --import-archive=my.deparch --extract-caller=mysubr > mysubr.caller                                           
$shell> dot -Tsvg -o mysubr.caller.svg mysubr.caller                        

Resulting in

mysubr_CallerGraph foo foo mysubr mysubr foo->mysubr mysubr->foo mycaller mycaller mycaller->mysubr

Cross References in Listings to External Routines

By default cross references to external functions and subroutines are not created by f2html. For the mysubr.f example a warning gets issued:

$shell> ./f2html mysubr.crash examples/mysubr.f > mysubr.html               
WARNING: Cannot find external function/subroutine FOO (tag=foo)
WARNING: Cannot find external function/subroutine DUMMY (tag=dummy)
WARNING: Cannot find external function/subroutine FOO (tag=foo)
WARNING: Cannot find external function/subroutine DUMMY (tag=dummy)

In order to avoid this we also have to pass the dependency archive:

$shell> ./f2html mysubr.crash --deps-archive=my.deparch examples/mysubr.f > mysubr.html               

This gives

      SUBROUTINE MYSUBRN )

      INTEGER  N

      EXTERNAL FOODUMMY

      IFN .GT. 1 ) THEN
         CALL FOON-1 )
      ELSE
         CALL DUMMY
      END IF

      END

Note that links to external functions/subroutines are solid underlined.

Extracting Embedded Documentation

In most LAPACK source files the documentation of the code is embedded. The documentation typically consists of several sections. Usual at least the

following two:

Sometimes additional sections go more into detail on the mathematical background. With the LapackDoc tools this documentation can be extracted and presented in a nice HTML format.

Let's look at the source code of typical LAPACK function which we use for demonstration:

      SUBROUTINE DGETRF( M, N, A, LDA, IPIV, INFO )
*
*  -- LAPACK routine (version 3.2) --
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
*     November 2006
*
*     .. Scalar Arguments ..
      INTEGER            INFO, LDA, M, N
*     ..
*     .. Array Arguments ..
      INTEGER            IPIV( * )
      DOUBLE PRECISION   A( LDA, * )
*     ..
*
*  Purpose
*  =======
*
*  DGETRF computes an LU factorization of a general M-by-N matrix A
*  using partial pivoting with row interchanges.
*
*  The factorization has the form
*     A = P * L * U
*  where P is a permutation matrix, L is lower triangular with unit
*  diagonal elements (lower trapezoidal if m > n), and U is upper
*  triangular (upper trapezoidal if m < n).
*
*  This is the right-looking Level 3 BLAS version of the algorithm.
*
*  Arguments
*  =========
*
*  M       (input) INTEGER
*          The number of rows of the matrix A.  M >= 0.
*
*  N       (input) INTEGER
*          The number of columns of the matrix A.  N >= 0.
*
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
*          On entry, the M-by-N matrix to be factored.
*          On exit, the factors L and U from the factorization
*          A = P*L*U; the unit diagonal elements of L are not stored.
*
*  LDA     (input) INTEGER
*          The leading dimension of the array A.  LDA >= max(1,M).
*
*  IPIV    (output) INTEGER array, dimension (min(M,N))
*          The pivot indices; for 1 <= i <= min(M,N), row i of the
*          matrix was interchanged with row IPIV(i).
*
*  INFO    (output) INTEGER
*          = 0:  successful exit
*          < 0:  if INFO = -i, the i-th argument had an illegal value
*          > 0:  if INFO = i, U(i,i) is exactly zero. The factorization
*                has been completed, but the factor U is exactly
*                singular, and division by zero will occur if it is used
*                to solve a system of equations.
*
*  =====================================================================
*
*     .. Parameters ..
      DOUBLE PRECISION   ONE
      PARAMETER          ( ONE = 1.0D+0 )
*     ..
*     .. Local Scalars ..
      INTEGER            I, IINFO, J, JB, NB
*     ..
*     .. External Subroutines ..
      EXTERNAL           DGEMM, DGETF2, DLASWP, DTRSM, XERBLA
*     ..
*     .. External Functions ..
      INTEGER            ILAENV
      EXTERNAL           ILAENV
*     ..
*     .. Intrinsic Functions ..
      INTRINSIC          MAXMIN
*     ..
*     .. Executable Statements ..
*
*     Test the input parameters.
*
      INFO = 0
      IF( M.LT.0 ) THEN
         INFO = -1
      ELSE IF( N.LT.0 ) THEN
         INFO = -2
      ELSE IF( LDA.LT.MAX1, M ) ) THEN
         INFO = -4
      END IF
      IF( INFO.NE.0 ) THEN
         CALL XERBLA( 'DGETRF'-INFO )
         RETURN
      END IF
*
*     Quick return if possible
*
      IF( M.EQ.0 .OR. N.EQ.0 )
     $   RETURN
*
*     Determine the block size for this environment.
*
      NB = ILAENV( 1'DGETRF'' ', M, N, -1-1 )
      IF( NB.LE.1 .OR. NB.GE.MIN( M, N ) ) THEN
*
*        Use unblocked code.
*
         CALL DGETF2( M, N, A, LDA, IPIV, INFO )
      ELSE
*
*        Use blocked code.
*
         DO 20 J = 1MIN( M, N ), NB
            JB = MINMIN( M, N )-J+1, NB )
*
*           Factor diagonal and subdiagonal blocks and test for exact
*           singularity.
*
            CALL DGETF2( M-J+1, JB, A( J, J ), LDA, IPIV( J ), IINFO )
*
*           Adjust INFO and the pivot indices.
*
            IF( INFO.EQ.0 .AND. IINFO.GT.0 )
     $         INFO = IINFO + J - 1
            DO 10 I = J, MIN( M, J+JB-1 )
               IPIV( I ) = J - 1 + IPIV( I )
   10       CONTINUE
*
*           Apply interchanges to columns 1:J-1.
*
            CALL DLASWP( J-1, A, LDA, J, J+JB-1, IPIV, 1 )
*
            IF( J+JB.LE.N ) THEN
*
*              Apply interchanges to columns J+JB:N.
*
               CALL DLASWP( N-J-JB+1, A( 1, J+JB ), LDA, J, J+JB-1,
     $                      IPIV, 1 )
*
*              Compute block row of U.
*
               CALL DTRSM( 'Left''Lower''No transpose''Unit', JB,
     $                     N-J-JB+1, ONE, A( J, J ), LDA, A( J, J+JB ),
     $                     LDA )
               IF( J+JB.LE.M ) THEN
*
*                 Update trailing submatrix.
*
                  CALL DGEMM( 'No transpose''No transpose', M-J-JB+1,
     $                        N-J-JB+1, JB, -ONE, A( J+JB, J ), LDA,
     $                        A( J, J+JB ), LDA, ONE, A( J+JB, J+JB ),
     $                        LDA )
               END IF
            END IF
   20    CONTINUE
      END IF
      RETURN
*
*     End of DGETRF
*
      END

First we extract with f77crash all the information related to Fortran syntax and dependencies. That is necessary to determine in the Arguments section the referenced variable names.

$shell> f77crash/f77crash examples/dgetrf.f > dgetrf.crash 2>dgetrf.deps    

Then we extract the embedded documentation and create a HTML document.

$shell> ./xtractdoc --crashfile=dgetrf.crash examples/dgetrf.f > dgetrf.html                                           

Note that the variable names in the Arguments section are linked to the point of definition in the source code:

DGETRF

   November 2006

Purpose

DGETRF computes an LU factorization of a general M-by-N matrix A
using partial pivoting with row interchanges.

The factorization has the form
   A = P * L * U
where P is a permutation matrix, L is lower triangular with unit
diagonal elements (lower trapezoidal if m > n), and U is upper
triangular (upper trapezoidal if m < n).

This is the right-looking Level 3 BLAS version of the algorithm.

Arguments

M
(input) INTEGER
The number of rows of the matrix A.  M >= 0.
N
(input) INTEGER
The number of columns of the matrix A.  N >= 0.
A
(input/output) DOUBLE PRECISION array, dimension (LDA,N)
On entry, the M-by-N matrix to be factored.
On exit, the factors L and U from the factorization
A = P*L*U; the unit diagonal elements of L are not stored.
LDA
(input) INTEGER
The leading dimension of the array A.  LDA >= max(1,M).
IPIV
(output) INTEGER array, dimension (min(M,N))
The pivot indices; for 1 <= i <= min(M,N), row i of the
matrix was interchanged with row IPIV(i).
INFO
(output) INTEGER
= 0:  successful exit
< 0:  if INFO = -i, the i-th argument had an illegal value
> 0:  if INFO = i, U(i,i) is exactly zero. The factorization
      has been completed, but the factor U is exactly
      singular, and division by zero will occur if it is used
      to solve a system of equations.

Complete LAPACK Documentation: lapackdoc

All the tool we explain and introduce here are the ingredients of lapackdoc. The lapackdoc command line tool can be used for creating a full documentation of LAPACK 3.3.1 as shown in this demo. Features of the documentation are explained in this tour. On the install page we show how to get the tool up and running.