wiki:HowTo/FortranStandards

Version 19 (modified by mmcgrath, 11 years ago) (diff)

--

Orchidee Fortran style guide


Introduction

This is a working collaborative document which will outline standard working procedures and coding style for ORCHIDEE. Please make comments by logging into the wiki and editing the page code using the discussion markup, followed by your initials. Comments will then be reviewed and merged into the main text periodically.

Example:

Sample text
> I don't understand this at all (BB)
>> This needs further clarification (JB)

which will then appear in the document as:

Sample text

I don't understand this at all (BB)

This needs further clarification (JB)



Interfaces

Existing structure and interactions between module and subroutines and how to improve it


(1) For function/subroutine calls, there should only be five arguments per line.

CALL subroutine(arg1, arg2, arg3, arg4, arg5, &
                arg6, arg7, ... )

The reason is that subroutine arguments are not strictly checked, so when one is hunting for bugs, it's nice to be able to quickly check that all the arguments are in the right place.



Clarity

Layout of code for clarity to the reader, reminder about the commenting style and ensuring interaction with the documentation compiler (dOxygen)


(1) Related to point one, in the variable declaration of the subroutine, it's nice to have all the variables which are passed to/from to be in the same order as they are listed.

SUBROUTINE subroutine(arg1, arg2, arg3, arg4, arg5, &
                arg6, arg7, ... )

    !
    !! 0. Variable and parameter declaration
    !

    !
    !! 0.1 Input variables
    !
    INTEGER(i_std), INTENT(in)                                :: arg1         !! Domain size (unitless)
    REAL(r_std), INTENT (in)                                  :: arg2         !! Time step (s)
    REAL(r_std),DIMENSION (kjpindex), INTENT (in)             :: arg3         !! Downwelling short wave flux 
                                                  
   !
    !! 0.2 Output variables
    !
    INTEGER(i_std), INTENT(out)                               :: arg4         !! Domain size (unitless)
    REAL(r_std), INTENT (out)                                 :: arg5         !! Time step (s)
    REAL(r_std),DIMENSION (kjpindex), INTENT (out)            :: arg6         !! Downwellin

   !! 0.3 Modified variables
    !
    INTEGER(i_std), INTENT(inout)                             :: arg7         !! Domain size (unitless)


(2) Comment at end of loop: If there is a loop within a loop (nested loop), or a lengthy single loop, it is helpful to repeat the loop instructions as a comment next to the END statement, as so:

eta_3_surf = 0.0d0

DO j = 1, nlevels

    DO k = j, 1
        jfactor = jfactor * (1.0d0 - jomega(k))
    END DO ! k = j, 1

    eta_3_surf = eta_3_surf + (jomega_surf * jomega(j) * jfactor * sbsigma * temp_leaf_pres(j)**4.0d0)

END DO ! j = 1, nlevels


(3) Equations: Use brackets to improve readability (even though addition and subtraction are treated ahead of division and multiplication, it is easier for the reader to scan the equations if this is made explicit). Also, if the equation runs over several lines, try to break the expression at a close bracket or an addition/subtraction.

e.g. a = (b * i) + (c / n) is easier to read than a = b * i + c / n


(4) Line length: Although the maximum line length of Fortran90 is 132 characters, keep your code to less than 80 characters per line - this preserves the formatting for those who work with small terminal windows on their computer and when producing a printout.


(5) Use of space: Always indent the code within conditional statements or loops, but don't use tabs, as the formatting will not be preserved across platforms. NOTE: The emacs indent function works well for this, since it indents with spaces (even if you use the tab key).




Variable definitions

Choosing where and when to define particular variables; portability between compilers; allocation/de-allocation of arrays etc.




Debugging and speed optimisation

guidelines for making loops more efficient, eliminating dead code


(1) 'bavard' (chatterbox!): is an externalised parameter that can be used to determine the nature of WRITE statements in the code for monitoring and debugging. It is proposed that for the trunk code a uniform set of parameters is used to control the size of the output text files as appropriate to the task in hand.

For example:

IF bavard EQUALS 0 then no output

IF bavard => 1 then parameters used are reported

IF bavard => 2 then entering and leaving subroutines are reported


(2) If you are using an IF...ELSEIF....ENDIF loop, always make sure you include an ELSE statement at the end to catch any situation not covered in the other cases. This should be done even if the ELSE statement doesn't do anything, just so that other people know that nothing needs to be done in some cases. Too many bugs are found because an IF statement is not triggered due to something the programmer didn't think of. This is especially problematic when the programmer thinks to him/herself, "This value will always be in this range, so I don't have to consider other possibilities"...and then one day things change.

IF()THEN
  ! do something
  blah
ELSEIF()THEN
  ! do something else
  blah blah
ELSE
  ! do something, or not, but at least you should be aware of the possibility
ENDIF


(3) No compiler will catch all your bugs. Always use multiple compilers to check, including all the error flags. For example, I first compile locally with " gfortran -c -cpp -O0 -pg -g -Wall -ffpe-trap=invalid,zero -fbacktrace -fcheck=all -fbounds-check -pedantic". Then I compile on asterix with "ifort -c -cpp -g -O0 -debug -fpe0 -ftrapuv -traceback". I'm hoping to do it on Curie soon, too, since they have the NAG compiler there which is good with error checking.