Versions Compared

Key

  • This line was added.
  • This line was removed.
  • Formatting was changed.
Table of Contents
minLevel1
maxLevel7
stylenone

Coding Style

Expand

Use uppercase for all Fortran instructions, variable names

Use lowercase for pre-compiler directives

Comments should be written in English only (uppercase & lowercase accepted)

Tabulations are forbidden (to be replaced by spaces at the beginning of line)

Use meaningful names for variables, in English, keep the same name throughout the code

Systematically indent your blocks (IF/END IF, DO/END DO, ...) in a homogeneous way for clarity of the code

In case of long IF/ELSE/END IF block, it is recommended to add comment like below: 

Code Block
languagefortran
  IF (A==0) THEN
!       my long block
!       ...
       ELSE ! A/=0
!       my second long block
!       ...
       END IF

Routine & file organisation

Expand

By default, one file contains only one subroutine or function, except when the understanding of the code is facilitated by grouping few procedures

The same rule applies for modules: one module per file, same name

For module several subroutines can be defined under the CONTAINS close

Header definition

Expand

Each source file should have the copyright notice

Each procedure needs to have a conforming header, containing by order of appearance:

  • A minimal description of the routine

  • The list of caller subroutines/functions

  • The list of called subroutines/functions

  • The SUBROUTINE/FUNCTION declaration with the list of dummy arguments, 5 per line, matching the call declaration

  • The used modules

  • The implicit_c.inc (IMPLICIT NONE)

  • The optional remaining global parameters and commons if any (for compatibility with the past)

  • The list of dummy arguments, one per line with its type, INTENT attribute, explicit bounds in case of array, a short description of the variable

  • The local variables

  • The source code

Info

Notes:

  1. The list of callers/callees is automatically generated

  2. implicit_f.inc must always be included. It automatically includes IMPLICIT NONE instruction, the definition of my_real (as REAL*8 for double precision or REAL*4 for single precision) and constant.inc which defines numerical constant variables like ZERO here

  3. Explicit bounds of all arrays are mandatory; the use of “*" is now forbidden for clarity

Example:

INTEGER IPARG(60, *)          Forbidden

INTEGER IPARG(NPARG, NGROUP)  Authorized

Comments

Expand

It is important to comment algorithms, especially when non straightforward coding is used

Comments are written in English

Comments respect Fortran90 standard. The use of "!" at beginning of line is preferred to "C" or "*"

Except for preprocessor directives, the following characters ',", \, /*, */, # are forbidden, even inside comments. Especially "\" is dangerous as it is interpreted as a continuation line by the preprocessor

 Example:

Code Block
languagefortran
! this is a legal comment
      A = A + B ! this one is also authorized in FORTRAN 90
      C = A + C ! next instruction ignored cause of this char \
      D = C + D

Modules

Expand

Module Format

Generic format of a Fortran90 module is as follows:     

Code Block
languagefortran
MODULE <module name>
  USE [other module list]
  #include "implicit_f.inc"
  <declaration section>
  CONTAINS
  <procedure definitions>
END MODULE <module name>

Naming Convention 

Module name is defined as follows: MODULENAME_MOD

With module file name: modulename_mod.F

Module file is placed at the same location as other files used by the option

Restart Variables

All the variables communicated between Starter and Engine are declared in module RESTART_MOD, used by subroutine ARRALLOC for their allocation, by RDRESB for their reading from RESTART file, then by RESOL_HEAD in which they are used as argument for RESOL subroutine. All these argument variables are then passed by argument to procedures called from RESOL, ...)

Interface definition

Fortran90 interface allows the compiler to do additional checks like coherency between argument types, attributes and number between calling and callee routines. It is required in some cases like when a procedure has a dummy argument with attribute ALLOCATABLE, POINTER, TARGET

In practice, it was introduced in few places of the code for routines which were called at several different places

Such coherency is automatically tested by QA static analysis tools (Forcheck).

And for pointer, good practice is to use derived data types instead of pointer directly

Therefore, the remaining use of interface is regarding routine with optional arguments

This feature should be spread in the code instead of adding additional “dummy” arguments

Memory Allocation

Shared Memory Programming (SMP) and memory allocation

For Radioss OpenRadioss Engine, OpenMP programming model is used for second level parallelization

By default any memory allocation done outside of a parallel section is shared between threads

Most of the parallel sections are started from RESOL. So for the need of a shared memory array, the simplest way is to declare it at the level of RESOL. It will be shared inside the different parallel sections started from RESOL, possibly passed by argument to routines called from RESOL

The same way, any variable defined in a common or module is shared by default

For pointer, notice that a single thread needs to allocate and deallocate it. The programmer has to manage synchronization in order to insure such a variable is allocated before being used by any other thread and no longer used before it is deallocatedSynchronization may be needed after the allocation and before the deallocation

The !$OMP THREADPRIVATE directive THREADPRIVATE directive overrides default behavior by creating thread local storage variables

Array Aliasing

Expand

Dynamic memory allocation mechanism

Large arrays should be allocatable arrays: Avoid using pointer when possible, and do not use automatic arrays. Arrays should be explicitly deallocated as soon as possible

Developers are required to check the success of the allocation 

For large arrays it is preferred to print a specific message, with some advice for the user, or at least the option concerned by this failure   

Nevertheless, there are macros that will check and print a generic error message

  • MY_ALLOCATE needs the file my_allocate.inc to be included and the module MESSAGE_MOD to be used

  • It is still mandatory to call DEALLOCATE;

  • MY_ALLOCATE2D and MY_ALLOCATE3D to be used for respectively 2 and 3 dimensional arrays.

See my_allocate.inc in GitHub for the definitions

Global Memory

Memory allocation of global data structures, arrays and derived data types, should be done at the highest level, in LECTUR for Starter, in RADIOSS2 or RESOL for Engine

It is advised to use derived data type with structure of arrays. This way it is possible to declare the variable at the upper level, gather the allocation of array members in a dedicated subroutine, then use the variable in procedures called at lower level without losing traceability

Local Memory

In a procedure, local variable allocation method depends on its size:

The size is known and limited to a multiple of MVSIZ

Automatic allocation in the stack is ok

The size is not known or larger than times MVSIZ

It is then too large to use automatic allocation in the stack. It is therefore needed to use dynamic allocation in the heap

Automatic Allocated arrays go into Stack

ALLOCATED ARRAYS go into Heap

One should take care to reduce Stacksize usage to a reasonable size.

Stacksize is hardcoded under Windows

It is allowed to use MY_ALLOCATE at the beginning of a routine provided matching DEALLOCATE is done at the end of this routine

In case of multiple calls to MY_ALLOCATE, a call to DEALLOCATE must be applied to the variable used in the last previous call to MY_ALLOCATE to avoid a memory hole and need for a garbage collector

Local Memory Example:

code

languagefortran
CALL MY_ALLOCATE(VAR1)
      CALL MY_ALLOCATE(VAR2)
C…
      DEALLOCATE(VAR2)
C…
      CALL MY_ALLOCATE(VAR3)
C…
      DEALLOCATE(VAR3)
C…
      DEALLOCATE(VAR1)
Expand

Description

Here we discuss different arguments of a procedure referencing the same memory locations. The compiler won’t be able to detect in the procedure that different argument variables reference one or more identical memory locations. Such a situation is particularly dangerous because of compiler optimization. Even if compilers are not forbidden it, if both variables are modified inside the procedure this could lead to unpredictable results. Potential conflicts or dependencies won’t be detected

Code Example:

Code Block
languagefortran
PROGRAM OVERMAIN
C------------------------------------------
       IMPLICIT NONE
C------------------------------------------
       PARAMETER (MAXLEN = 40)
       INTEGER BUFFER(MAXLEN),I,I1,LEN
C------------------------------------------
       I1 = 10
       LEN = 22
       DO I = 1, LEN
         BUFFER(I1+I-1) = I
       ENDDO
       print *,’init : buffer =’,(BUFFER(I1+I-1),I=1,LEN)
       CALL SHIFTI1(BUFFER,BUFFER(I1),I1,LEN) ! potential overlap
       print *,’result: buffer =’,(BUFFER(I1+I-1),I=1,LEN)
       STOP
       END

       SUBROUTINE SHIFTI1(BUFFER,TAB,I1,LEN)
C------------------------------------------
       IMPLICIT NONE
C------------------------------------------
       INTEGER BUFFER(*),TAB(*),I1,LEN
C------------------------------------------
       INTEGER I,LEN0,I10
C------------------------------------------
       LEN0 = 19
       I10 = I1 - LEN + LEN0
       DO I = 1, LEN
         BUFFER(I10+I-1) = TAB(I) ! true overlap
       ENDDO
       I1 = I10
       RETURN
       END

Tested on SGI O200 IRIX 6.4: output:

Code Block
languagebash
skippy 61% f77 -O2 -c *.F
overmain.F:
shifti1.F:
skippy 62% f77 -O2 -o overlaps *.o
skippy 63% overlaps
init : buffer =
1 2 3 4 5 6
7 8 9 10 11 12
13 14 15 16 17 18
19 20 21 22
result: buffer =
1 2 6 4 5 6
10 8 9 10 14 12
13 14 18 16 17 18
22 20 21 22
Conclusion: Array aliasing is forbidden when the variable is modified inside the procedure
Note
Note

Array aliasing is forbidden when the variable is modified inside the procedure: two dummy arguments should not point to the same memory location

Example:

CALL MYROUTINE(A(1:8), A(7:10)) is not accepted because A(7) and A(8) are common to two dummy arguments