next up previous contents index
Next: 5 The Compiler Driver Up: ADAPTOR Users Guide Previous: 3 Configuration Files   Contents   Index

Subsections


4 The Source-to-Source Translation \fbox{fadapt}

This section describes the use of the source-to-source translation and all the flags that can be used to drive the translation. An overview of all options is given in the appendix.


4.1 Call of fadapt

The names of the input files for the source-to-source translation are specified as command line arguments.

   fadapt <source_file_names>

More than one source file may be specified. The files are translated separately unless the -o option is used (see later this Section).

fadapt will accept files with the following suffixes as valid input source files:

   .f    .f9      .f90     .hpf

Attention: The source-to-source translation fadapt will not change any option for the translation depending on the file name. E.g. it does not assume automatically that files with the suffix .f90 use the free format.

If the translation is executed correctly, the following output source file will be generated:

       <source_file_name>_adp.f

With the -o option it is possible to specify an own name for the generated output file.

      fadapt <source_file> -o <output_file>

Attention: multiple source files will be concatenated in one temporary source file with the -o option. All source files together stand for one parallel program. There must not be more than one main program in the specified source files.

With the -od option it is possible to specify a directory into which the generated output files should be written. In this case, the output files will have the same name as the input files.


4.2 Translation Command

ADAPTOR supports currently the following translation commands:

   -fortran      &  Fortran translation 
   -hpf          &  HPF translation 
   -omp          &  OpenMP translation 
   -update       &  update translation 
   -instr        &  source code instrumentation
   -call         &  generates call graph
   -interface    &  generates interface file

4.2.1 Fortran Translation

By default (-fortran), the source-to-source translation fadapt is a full translation of Fortran programs running through all the phases of the ADAPTOR translation. The main features of this translation are:

The Fortran translation itself does not exploit any parallelism and might be not very useful on its own as it does in a certain sense only a lot of normalizations that are mainly needed for HPF translation. Nevertheless, it might be useful in the following situations:

It can be expected that in future versions the possibilities of the source-to-source translation for Fortran programs will be enriched with additional features.

4.2.2 HPF Translation

By the flag -hpf the user enables HPF compilation. In this case, the HPF mapping directives are used to generate parallel programs. The main principle is that every processor will only work on the data mapped to it. If the computations of one processor need data from other processors, synchronization and/or communication will be generated automatically.

The source-to-source translation fadapt supports HPF compilation by the following features:

Note: The flags -hpf and -omp do not imply that corresponding directives are enabled or disabled. OpenMP directives will also be parsed for HPF compilation but OpenMP parallelism will not be exploited for HPF translation, and the OpenMP runtime library will not be known at compile time.

4.2.3 OpenMP Translation

By the flag -omp the user enables OpenMP compilation. The OpenMP directives are used to map the computations to parallel threads.

Note: The flag -omp does not imply that corresponding directives are enabled or disabled. HPF directives will also be handled for OpenMP compilation but the mapping will be ignored completely. In certain situations, the HPF INDEPENDENT directive can improve the performance also for OpenMP programs (so why ignore it if it is available?).


4.2.4 Update Translation

By the flag -update ADAPTOR only runs through the analysis phases (parsing, semantic analysis) and unparsing phase for the generation of new source code. Phases regarding the translation of HPF and/or OpenMP parallelism are skipped. Nevertheless, in this mode transformation directives are resolved and profiling code is inserted.

4.2.5 Call Graph Generation

fadapt can also be used to generate a call graph for a given Fortran program. The call graph of a program gives information about which subroutine calls which other subroutine. It can be generated in the following way:

      fadapt -call *.f -o test.call

The output file will contain the following information:

CALL Hierarchy (User Nodes)
===========================
EXPL2
 . F1
 . SOL
 . DIFMX
 .  . SOL (+)
 . DIFL2
 .  . SOL (+)
 . G

4.2.6 Generation of Interfaces

For separate compilation it might be necessary that a subroutine or a function contains an INTERFACE block that specifies the parameter lists of all the subroutines or functions that are called.

For existing codes it might be rather tedious to insert corresponding INTERFACE specifications. A good solution is to use an interface file interface.h that will be included in all subroutines.

ADAPTOR can generate such an interface file automatically from all the given source files.

      fadapt -interface *.f -o interface.h

This command generates a file interface.h. It contains an INTERFACE block with all subroutines of all source files.

      INTERFACE
      SUBROUTINE DIFMX (U, TX, TY, NP, T, MXRESUL)
      INTEGER*4 NP 
      REAL*8 U (0:NP,0:NP)
      REAL*8 TX (0:NP,0:NP)
      REAL*8 TY (0:NP,0:NP)
      REAL*8 MXRESUL 
      INTEGER*4 T 
      END

      SUBROUTINE DIFL2 (U, TX, TY, NP, T, L2RESUL)
      INTEGER*4 NP 
      REAL*8 U (0:NP,0:NP)
      REAL*8 TX (0:NP,0:NP)
      REAL*8 TY (0:NP,0:NP)
      REAL*8 L2RESUL 
      INTEGER*4 T 
      END

      SUBROUTINE SOL (U, TX, TY, NP, T)
      INTEGER*4 NP 
      REAL*8 U (0:NP,0:NP)
      REAL*8 TX (0:NP,0:NP)
      REAL*8 TY (0:NP,0:NP)
      REAL*8 T 
      END

      SUBROUTINE F1 (U, TX, TY, NP)
      INTEGER*4 NP 
      REAL*8 U (0:NP,0:NP)
      REAL*8 TX (0:NP,0:NP)
      REAL*8 TY (0:NP,0:NP)
      END

      SUBROUTINE F2 (U, TX, TY, NP)
      INTEGER*4 NP 
      REAL*8 U (0:NP,0:NP)
      REAL*8 TX (0:NP,0:NP)
      REAL*8 TY (0:NP,0:NP)
      END

      SUBROUTINE G (U, TX, TY, NP, T)
      INTEGER*4 NP 
      REAL*8 U (0:NP,0:NP)
      REAL*8 TX (0:NP,0:NP)
      REAL*8 TY (0:NP,0:NP)
      REAL*8 T 
      END

      END INTERFACE

4.3 General Options

4.3.1 Verbose and Help Information

The two flags -help and -settings are very useful to get information about the available options and about the default options of fadapt. The flag -help displays the list of all available options while the flag -settings prints the list of the default options. The default options depend on the installation and might vary for the different machines.

  -help            list all available options
  -settings        prints the list of the set options

The verbose flag -v should be used to get information about the progress of fadapt.

  -v               verbose

4.3.2 Warnings and Info Messages

By default, fadapt prints warning and information messages. They can be switched off by the following options:

  -w               does not print any warnings
  -noinfo          does not print any info messages


4.3.3 Protocol Files of Translation

fadapt generates protocol files according to the translation steps. By default, fadapt removes silently all these files except a warning or an error message have occurred in the translation step.

These files are very useful in situations where errors have been encountered. If an error occures within one phase, the translation will stop immediately after this phase.

The option -list will keep all intermediate protocol files.

      fadapt -list

The following protocol files will be generated:

 adaptor.def      (protocol file of semantic phase 1: make defs)
 adaptor.sem      (protocol file of semantic phase 2: sem checks)
 adaptor.cf       (protocol file of semantic phase 3: control flow)
 adaptor.dist     (protocol file of parallel phase 1: distribution)
 adaptor.normal   (protocol file of parallel phase 2: normalization)
 adaptor.auto     (protocol file of parallel phase 3: loop parallelization)
 adaptor.ovl      (protocol file of parallel phase 4: shadows)
 adaptor.ana      (protocol file of parallel phase 5: analysis)
 adaptor.arg      (protocol file of adaptor phase 1: arguments)
 adaptor.loop     (protocol file of adaptor phase 2: make loops)
 adaptor.home     (protocol file of adaptor phase 3: home determination)
 adaptor.local    (protocol file of adaptor phase 4: communication generation)
 adaptor.class    (protocol file of adaptor phase 5: classification)
 adaptor.opt      (protocol file of optimization phase 1: optimization)
 adaptor.ipa      (protocol file of optimization phase 2: interprocedural)
 adaptor.init     (protocol file of codegen phase 1: initial code)
 adaptor.code     (protocol file of codegen phase 2: code generation)
 adaptor.addr     (protocol file of codegen phase 3: addressing)
 adaptor.final    (protocol file of codegen phase 4: final code)

These files can be deleted with the command \fbox{adapt.clean}.


4.3.4 Intermediate Files of Translation

It is possible to generate intermediate files of the source-to-source translation. This might be very convenient to understand in detail how the compiler has translated the input file and has taken advantage of the available data parallelism.

      fadapt -debug

The following files will be generated after the corresponding translation steps:

 cf_unparse.f     (source program after semantical analysis)
 normal_unparse.f (source program after normalization)
 ana_unparse.f    (source program after adaptor analysis)
 arg_unparse.f    (source program after arguments)
 loop_unparse.f   (source program after loop generation)
 home_unparse.f   (source program after home determination)
 local_unparse.f  (source program after localization)
 opt_unparse.f    (optimized source program before code generation)
 init_unparse.f   (initail code generation)
 code_unparse.f   (code generation for DALIB calls)
 addr_unparse.f   (localizing addresses and pseudo dynamic arrays)

These files can also be deleted with the command \fbox{adapt.clean}.


4.4 Options for the Input Source File

The command fadapt ... -settings will print all the current settings of the source-to-source translation. The following options are related to the input source file:

OPTIONS input source
  source format        : fixed form, 72 relevant columns [-fix 72])
  enabled directives   : !$ !HPF$ !ADP$ !TRA$ !$OMP
  INTEGER              : -> INTEGER*4 (input_int_size)
  REAL                 : -> REAL*4 (-sp, input_real_size)
  semantic checks      : strict

The input program can be any Fortran program with compiler directives. ADAPTOR supports the Fortran 90 standard and some Fortran 95 extensions. Syntax or semantical errors result in a termination of the translation. HPF and OpenMP directives as well as other compiler directives are handled like comments if the corresponding directives are not enabled. Otherwise they will be parsed and handled corresponding to their meaning.


4.4.1 Source Format of Input Files

Since fadapt is very flexible in handling Fortran sources for input and output, the user may choose between the fixed and free source format. For the fixed source format the user may specify also the number of relevant columns of the input file.

  [-fix <n>]         number of relevant columns in input file (default 72)
  [-fix 0]           free source format for input file only  
  [-extend]          extended source format for input/output file
  [-free]            free source format for input and output file

Note: The options -extend and -free apply for both, the input and the output source file (see also Section 4.5.2);

4.4.2 Enabling and Disabling Compiler Directives

ADAPTOR can parse the following compiler directives:

By default, ADAPTOR parses all directives. Syntactical or semantical errors will be recognized.

By the following options it is possible to disable compiler directives (and they are handled like usual comment lines):

     -off:ADP         disable !ADP$ directves
     -off:OMP         disable !$OMP directves
     -off:TRA         disable !TRA$ directves
     -off:HPF         disable !HPF$ directves
     -off:            disable conditional compilation

Generally speaking, any kind of compiler dircetive can be switched on or off by:

     -on:<DIR>  -off:<DIR>

Even for the HPF or OpenMP translation (see Section 4.2) all directives are enabled though HPF mapping will be ignored for OpenMP translation and parallel regions are serialized for HPF translation. But e.g. it might be useful to accept HPF directives like the HPF INDEPENDENT directive for OpenMP translation to allow better optimizations. But usually HPF diretives should be switched off for OpenMP compilation and vice versa.

4.4.3 Include Directories

INCLUDE statements in the Fortran source programs are also handled by ADAPTOR. The include files are assumed to be in the same directory where the input file is or in the directory where fadapt has been called. If they are in other directories, the name of the directory must be specified explicitly.

With the option -I<directory_name> additional directories can be specified where include files and module definition files are searched for. The current working directory and the directory with the input source file (usually the same) do not have to be specified explicitly.

      program RUN
      use M             ! module M defined in /home/user/x2/modules/M.hpf
      include 'data.h'  ! is file /home/user/x2/include/data.h
      ...
      end program

This program should be compiled with the following options:

   fadapt -I/home/user/x2/modules -I/home/user/x2/include ...

4.4.4 Default Size for INTEGER and REAL

For certain functionalities of the ADAPTOR runtime system it is absolutely necessary to know the exact sizes of the Fortran data types. This is especially true when ADAPTOR generates message passing commands to exchange data between MPI processes.

ADAPTOR supports the kind argument of Fortran 90 and the extended type specifications.

      integer, parameter :: IKIND = 4, RKIND = 8
      ...
      integer (kind=IKIND) :: I, J
      real (kind=RKIND)    :: X, Y
      ...
      integer*4            :: K1, K2
      real*8               :: Z1, Z2

The default size of INTEGER and REAL variables are specified in the configuration file by the options input_int_size and input_real_size.

      integer I, J
      real C, D

Note: Due to the Fortran-C interface of the ADAPTOR runtime system, their values should match the values sizeof(int) (is default_int_size in the configuration file) and sizeof(float) (is default_real_size).

The flag -dp will handle REAL variables as if they have been specified as DOUBLE PRECISION. Only in this case, variables of the type REAL and DOUBLE PRECISION will have the same size.

      -sp        REAL is treated as single precision (default)
      -dp        REAL is treated as DOUBLE PRECISION


4.4.5 Semantical Checks

During the semantic analyis, fadapt checks whether the number of actual arguments is equal to the number of dummy arguments. Also the correct rank of arrays and the correct types are checked.

      real A(6,6), B(5)
      ...
      call SUB (A, B)
      ...
      subroutine SUB (X, Y, Z)
      real X(36), Z
      integer Y(5)
      ...
      end

This example might give at least 3 semantical errors:

If the flag nostrict is switched on, only warnings will be given and the translation is continued.

   [-nostrict]

fadapt is more restrictive with its semantical checks than most FORTRAN 77 compilers usually are. The flag disables serious error messages for this kind of errors. But the user should be careful in any case as there might arise other problems, especially for distributed arrays.


4.5 Options for the Output Source File

The following options are related to the output source file:

OPTIONS output source
  source_update        : 0
  target language      : Fortran 90 [-F90]
  source format        : fixed form, 72 relevant columns [-strip 72])
  INTEGER              : INTEGER*4 (fortran_int_size)
  REAL                 : REAL*4    (fortran_real_size)


4.5.1 Choosing the Target Language

By the following flags the language of the output program can be specified:

  -F77        FORTRAN 77
  -F90        Fortran 90
  -F95        Fortran 95

If the target Fortran compiler only supports FORTRAN77, -F77 must be specified.

For portability reasons, the general strategy of fadapt is to generate FORTRAN 77 programs. Therefore, the array operations are translated to serial loops and the dynamic arrays will be simulated by pseudo-dynamic arrays in the generated programs.

Until now, some Fortran 90 features cannot be translated to FORTRAN 77 by fadapt. This includes especially modules, contained subroutines, generic procedures, overloading of operators, derived types, and pointers. If one of these features is used, the target compiler must be a Fortran 90 compiler. The same is true for certain Fortran 95 extensions.

Attention: The functionality of the input language is restricted if the target language is not Fortran 90 or Fortran 95. If the flag -F77 is set, fadapt will check that the generated programs can still be compiled by a FORTRAN 77 compiler.


4.5.2 Source Format of the Output File

The source format of the output file can be in fixed format or in free format. The number of relevant columns for the output file is very important as it must be set according to the facilities of the used native Fortran compiler. Otherwise a typical error message like the following one will appear:

  Line 162  Error message # 1139
    Perhaps missing RPARENT before ENDOFST
     --  [unexpected end of statement]

If this happens, a smaller number of column characters must be specified by using the strip option.

  [-strip <n>]       fixed source format with n relevant charcters
  [-strip 0]         free source format for output file
  [-extend]          extended source format for input/output file
  [-free]            free source format for input and output file

Note: The options -extend and -free apply for both, the input and the output source file (see also Section 4.4.1). The number of relevant characters for the extended source format is usually 132, but can be specified in the configuration file by the variable extend_length.


4.5.3 Keeping Old Source Code Lines

By default, the source-to-source translation fadapt generates a complete new source program. Comment lines of the input source will no longer exist in the new generated code. Even unchanged source code lines will be rewritten in some kind of pretty-print. In some situations, the output of the source-to-source translation fadapt might be used for further purposes and the new source code should be the same as the old one as far as possible. This is now supported.

        -keep=none   keep nothing of input source
    -keep=comments   keep comments of input source
         -keep=yes   keep unchanged lines of input source
         -keep=all   keep all of input source
       -keep=debug   keep all of input source and comment new code

ADAPTOR keeps internal track of changed and new source code lines and by this way it knows about unchanged input source lines. As this feature is rather new, it should only be used if -update has been chosen as translation command (see Section 4.2.4).

!     Example showing the ADAPTOR keep facility
      PROGRAM test
!     variables
      INTEGER, DIMENSION (10) :: A   ! my array
!     initialization
      A = 0
      END PROGRAM test

Note: The input source format and the output source format must be the same if the keep flag has been enabled (see Section 4.4.1 and Section 4.5.2).


4.5.4 Include Files

While fadapt can deal without any problems with included files in the input program, the include structure is usually lost for the generated output file. By default, the source-to-source translation fadapt generates an output source file that contains also the included files. I.e., the original INCLUDE lines of the input source program are no more visible. This is okay as long as the generated output files are only used as intermediate files before the native Fortran compilation follows. If you want to use fadapt for updating Fortran programs (e.g. code instrumentation) and keeping the old source code, you have the choice between the following flags:

       -incl=never   include never files
    -incl=modified   include modified files
      -incl=always   include always files
         -incl=new   include new files
      -incl=newmod   include new modified files

The following example should demonstrate the different modi of the handling of INCLUDE statements for the generated output file. The source-to-source translation lets the definitions in the file data.h unchanged while the array statement in code.h will be modified.

                       ! data.h            ! code.h
 PROGRAM sourcetest
 include 'data.h'      INTEGER x           read *, x
 include 'init.h'      INTEGER y(2)        y = x + 1
 END PROGRAM                               print *, y

Some remarks:

4.5.5 Default Size of INTEGER and REAL

The default size of INTEGER and REAL variables for the generated output file are specified in the configuration file by the options output_int_size and output_real_size.

      integer*4 I, J             integer I, J
      real*4 C, D                real C, D

Note: The values of output_int_size and output_real_size should correspond to the values that are assumed by the target Fortran compiler.

4.5.6 Renaming of Main Program

There is the possibility to translate a main program to a subroutine with a certain name by the following option:

    -submain APPL_MAIN

       program TEST              subroutine APPL_MAIN ()
       ...                       ...
       end program TEST          end subroutine

By this feature, it might be possible to write own main programs that do some initializations, then call the subroutine APPL_MAIN and do some final steps after program termination.

4.6 Options for the Translation


4.6.1 Automatic Loop Parallelization

fadapt can identify independent DO loops. Independent loops that have not the INDEPENDENT directive will be considered like independent loops. Furthermore, scalar reduction variables are identified properly.

   [-auto]          ! tries to identify INDEPENDENT do loops
   [-noauto]        ! disables automatic loop parallelization

If the automatic loop parallelization is switched on, ADAPTOR will also inform about loops that could not be proven to be INDEPENDENT.

      program TEST
      integer :: I
      integer, parameter :: N = 100
      real, dimension (N) :: A
      real :: X, T
      T = 0.0
      do I = 1, N
         X = 1.0 / real (I)
         T = T + X
      end do
      do I = 1, N
         A(I) = real (I) * T
      end do
      do I = 1, N
         A(I) = A(I) * 2.0
      end do
      end program

fadapt -auto auto.f
...
INFO at line 7 (auto.f) : X becomes NEW var in serial DO loop
INFO at line 7 (auto.f) : T becomes REDUCTION var (SUM) in DO loop
INFO at line 7 (auto.f) : DO loop is now INDEPENDENT
INFO at line 11 (auto.f) : DO loop is now INDEPENDENT
INFO at line 14 (auto.f) : DO loop is now INDEPENDENT

!hpf$ independent, new (X), reduction (sum:T)
      do I=1,N ! line=7
         X = 1.0/REAL(I,%val(0)) ! line=8
         reduce (SUM,T,X) (private) ! line=9
      end do ! line=10
!hpf$ independent
      do I=1,N 
         A(I) = REAL(I)*T 
      end do 
!hpf$ independent 
      do I=1,N 
         A(I) = A(I)*2.0 ! line=15
      end do ! line=16


4.6.2 Instrumentation for Profiling

fadapt generates at every entry and exit of a subprogram a call to the DALIB runtime system. This allows the performance analysis and tracing of subprograms at runtime (see [Bra04b]) and can provide the stack of subprogram calls in case of a run time error.

!     start_region (region_id, region_name, region_kind,
!                   file_name, file_id, line_start)
      call DALIB_start_region (-1,'GHOST3',0,'hydflo.hpf',2,684)
      ...
!     end_region (region_id, region_name, line_stop)
      call DALIB_end_region (-1,'GHOST3',739)

The first argument of these calls is the region id which has to be unique for the region. The value -1 indicates that the region id will be given automatically at runtime where as unique identification the filename (fourth argument) and the start line (sixth argument) will be taken. This approach has a certain overhead (string comparisons for every entry and exit of a region) but works correctly.

It is also possible to give already an unique region id at compile time that avoids the overhead of string comparisons. But in case of separate compilation of multiple files the user has to pay attention that the same region id is not given twice. This will be supported by a region information file (rif) that has to be specified for the compilation of all source files.

    fadapt -rif[=<filename>] ...

If only the flag -rif is specified, fadapt takes the file RIF by default as its region information file. Otherwise it takes the file filename for it. For the first compilation, this file will be created automatically. For all further compilations the region information file is read and fadapt will give unique region identifications for the compiled source program that do not conflict with other region identifications that have been given within previous compilations. In the output program the calls will now look like this:

      call DALIB_start_region (22,'GHOST3',0,'hydflo.hpf',0,684)
      ...
      call DALIB_end_region (22,'GHOST3',739)

By default, fadapt generates profile calls for every subprogram. Unfortunately, the calls for entering and leaving of regions can still cause a certain overhead that becomes annoying for very small subprograms called within loops. The overhead of the calls might also become larger for performance monitoring as performance counters are read and their values need some preparation. Therefore it is necessary to provide a mechanism to enable or disable the profiling calls for subprograms.

For the source-to-source translation fadapt there are two flags that disable or enable the generation of profile calls.

     -noprof:SUB      ! switches off the generation of profile calls
     -prof:SUB        ! switches on the generation of profile calls (enable)

More convenient is the use of ADAPTOR specific directives in the source file that disable the generation of the profile calls (in case of -prof or enable their generation (in case of -noprof. This directive must appear as a definition statement in the subprogram.

      subroutine SUB1 (...)           function F (...)
!adp$ noprofiling               !adp$ profiling 
      ...                             ...
      end subroutine                  end function

Furthermore, ADAPTOR allows to generate profile calls for certain user-defined regions in the program. It provides a directive that must appear before a statement that should be profiled (e.g. a subroutine call or a DO loop) or two directives to be set before and after a block of statements.

!adp$ profile <region_name>
      <stmt>
      ...
!adp$ profile <region_name> begin
      <code lines>
!adp$ end profile <region_name>

All these directives must appear in the execution part of the program. The user-defined name of the region makes it possible to identify performance monitoring information with the corresponding source code region more easily. The region name itself does not have to be unique. It should be noted that fadapt will also give unique region identifications automatically for such regions if the flag -rif[=filename] is enabled.

      call DALIB_start_region (16,'TIME_CYCLE',1,'hydflo.hpf',0,251)
      ...
      call DALIB_stop_region (16,'TIME_CYCLE',282)

4.6.3 Generation of Array Descriptors

An array descriptor is a record that contains all relevant information regarding the shape and mapping of an array.

      -dsp=no       ! disables the generation of array descriptors
      -dsp=auto     ! generates array descriptors where necessary
      -dsp=array    ! generates array descriptor for every array
      -dsp=all      ! introduces descriptors also for scalars

Here are some general rules when array descriptors should be used:

!adp$ NODESCRIPTOR
!adp$ NODESCRIPTOR :: A, B, C
!adp$ DESCRIPTOR   :: X, Y, Z


4.6.4 Pseudo-Dynamic Arrays

ADAPTOR supports pseudo-dynamic arrays where ADAPTOR manages memory allocation by its own runtime system.

      -pseudo=no
      -pseudo=auto
      -pseudo=all

Here are some general rules when pseudo-dynamic arrays should be used:

4.6.5 Passing of Array Descriptors to Subprograms

      -args=single
      -args=double

Here are some general rules when subroutine arguments should be doubled:

4.6.6 Compiler Optimization

A lot of compiler optimizations have already been implemented (e.g. automatic detection of overlap areas, inlining of cshift, loop fusion).

   [-O]            ! optimization is switched on
   [-noopt]        ! no optimization

By default, all optimizations are switched on.

4.7 Options for the OpenMP Translation

The execution model decides how ADAPTOR maps the parallel regions of the OpenMP program.

          -sm   model = SM Thread Model
          -cb   model = CB Cache Blocking

By default, ADAPTOR handles parallel regions like serial code. Synchronization is ignored.

In the shared memory model, parallel regions are executed by the available threads. This corresponds to the usual OpenMP execution model.

In the blocking model, the parallel region is executed by one processor that emulates a number of threads specified at runtime. As for the emulation the code is executed for each thread in a serial manner, synchronization between the threads is not allowed. On the other hand, in this model race conditions are respected and therefore less synchronization might be necessary.

4.8 Options for the HPF Translation


4.8.1 Choosing the Execution Model

The execution model decides how ADAPTOR handles the abstract HPF processors.

          -dm   model = DM MessPass Model
          -sm   model = SM Thread Model
          -cb   model = CB Cache Blocking

By default, ADAPTOR chooses a serial model. This implies that ADAPTOR will ignore all HPF mapping directives.

In the distributed memory model, every abstract processor becomes an own process. Exchanging of data is handled via messsage passing (MPI).

In the thread model, every abstract processor becomes an on thread.

In the cache mode, all abstract processors are emulated by one physical processor.

All the models can be combined, .e.g. -dm -cb becomes a model where the abstract processors are mapped to processes where every process emulates a subset of abstract processors.

After the compilation of the new generated source file linking must be done with the correct library of the DALIB runtime system.

4.8.2 Default Distributions

If the user does not give any layout or distribution directive for an array in his data parallel program, a default distribution will be chosen. The following options are intended for selecting a strategy for the default distribution (a more detailled description can be found in the ADAPTOR Language Reference Manual[Bra03a]).

Scalar variables will always be replicated.

  -ddr      default distribution of arrays is replicated
  -ddb      default distribution of arrays is block distribution
            along the last dimension

4.8.3 Maximal Number of Distributed Dimensions

Although a data parallel program has been written that can take advantage of many distributed dimensions, it might be useful for smaller machines to distribute only one or two dimensions. The generated code will usually be faster.

  -d <n>    specifies the maximal number of distributed dimensions

The effect of this option is that every distributed array with more than n distributed dimensions will only be distributed along the last n of these dimensions.

      real A (n,n,n)
!hpf$ distribute A(block,block,block)
      ....

For -d 1 this directive will be treated as follows:

      real A (n,n,n)
!hpf$ distribute A(*,*,block)
      ....

4.8.4 HPF Distribution of Dummy Arguments

At runtime, the distribution of the actual arguments will be matched against the distribution of the dummy arguments. By default, a redistribution takes place if there is a mismatch.

As in many user programs no redistributions take place at all, some additional overhead for matching distributions can be avoided. fadapt provides the following switches:

   [-safety 2]      ! runtime checks, does redistributions if necessary
   [-safety 1]      ! runtime checks, but no redistribution
   [-safety 0]      ! no runtime checks

The default value is safety 2.

Attention: If the safety value is 0 or 1, there will be no redistributions at subroutine boundaries. In case of safety 1 there are runtime checks that verify correct distributions of the dummy arguments. In case of safety 0, there are no checks at all, the generated programs will contain less calls to the runtime system.

      subroutine SUB (A,N)
      integer N
      real A(N,N)
!hpf$ distribute A(block,block)
      ...
      end subroutine SUB
      ...
      real A(N,N), B(N,N)
!hpf$ distribute A(block,block)
!hpf$ distribute B(cyclic,cyclic)
      ...
      call SUB (A,N)  ! always okay as no redistribution necessary
      call SUB (B,N)  ! redistribution with -safety 2
                      ! runtime error with -safety 1
                      ! unpredictable behavior with -safety 0

Note: The runtime checks will always be done in the called routine. There a no checks within the calling routine.

4.8.5 Shared Arrays

ADAPTOR supports shared arrays (see [Bra97]). Distributed arrays can be made shared by default with the following flag:

   [-shared]    ! distributed arrays without any replication are shared

4.8.6 Global Arrays

A global array will be allocated on each processor with the same size as it is allocated on a single processor. This is also true for mapped arrays, but the work distribution is still driven by the mapping directives.

   [-global]   ! distributed arrays are full allocated on each processor

Attention: This array layout might result in vaste of memory.

Common arrays and local arrays of a fixed size are often considered to be static. As they become dynamic as soon as they are distributed, this flag helps to let these arrays remain static.


4.9 Options in Source File

Most of the flags for the source-to-source translation can be overwritten directly in the source file that is compiled. This approach makes sure that one certain file or one certain routine is always compiled in the same way.

!ADP$ FLAGS -auto -no_vector -sm -free

This approach is also very useful when different source files of one application should be compiled in different ways.

The following options cannot be used:

All other options cannot be changed in this way.


4.10 Configuration File

The configuration of the tool fadapt can be set via a configuration file (see Section 3. In the following, the possible entries for the configuration file are described.

4.10.1 Fortran-C Interface

As the ADAPTOR runtime system is written in C, it is essential for the source-to-source translation to know what the sizes of the following C data types are:

   int            default_int_size  = sizeof (int)
   float          default_real_size = sizeof (float)
   void *         default_addr_size = sizeof (void *)

Though fadapt itself is written in C and there is no problem to determine the corresponding values on its own, the values can be set in the configuration file. This approach allows cross compilation where fadapt runs on the compile server and the DALIB is used on the compute server or parallel machine.

   default_int_size=4         ! default integer length is 4 bytes
   default_real_size=8        ! default real length is 8 bytes
   default_addr_size=4        ! default size of one address is 4 bytes

4.10.2 Fortran Sizes of INTEGER and REAL

fadapt has to know the default size of integer values and real values in the input source file.

      INTEGER I, J
      REAL C, D

The entries in the configuration file are:

input_int_size=4
input_real_size=4

Also the default size of integer values and real values for the output file can be specified in this way. Their sizes should match exactly the sizes the target Fortran compiler of the ADAPTOR installation expects. The correct values will be determined automatically during the installation of ADAPTOR.

output_int_size=4
output_real_size=4

4.10.3 Supported Data Types

In the configuration file it can be specified which Fortran data types are supported by the target Fortran compiler. The tool will give error messages for unsupported types. Usually, these entries are set automatically during the installation for the specified target Fortran compiler and should not be changed.

supported_integer_1=1
supported_integer_2=1
supported_integer_4=1
supported_integer_8=1
supported_integer_16=0
supported_logical_1=1
supported_logical_2=1
supported_logical_4=1
supported_logical_8=1
supported_real_4=1
supported_real_8=1
supported_real_16=0

4.10.4 Information about the Target Fortran Compiler

Some entries in the configuration file will be determined automatically during the installation. Their values are related to the target Fortran compiler and should not be changed.

target_language=FORTRAN_90

IOSTAT_EOF= -1
COMPLEX_ALIGN= 0
DCOMPLEX_ALIGN= 0
DOUBLE_ALIGN= 0
FORTRAN_POINTER0_SIZE=4
FORTRAN_POINTER1_SIZE=44
FORTRAN_POINTER2_SIZE=56

extend_length=132

Note: As the source-to-source translation depends on some features of the target Fortran compiler, it might not be safe to exchange the target Fortran compiler without a reconfiguration of the ADAPTOR system.

4.10.5 Definition of New Options

It is possible to define new command line options as a collection of single options, e.g. ADAPTOR uses already the following abbreviations:

-G=-v -debug -list
-HPF=-off:TRA -off:OMP -off: -hpf
-OMP=-off:TRA -off:HPF -omp
-OMP_SIM=-off:TRA -off:HPF -omp -submain=APPL_MAIN

Hint: New defined options itself cannot be used again as options on the right hand side.


next up previous contents index
Next: 5 The Compiler Driver Up: ADAPTOR Users Guide Previous: 3 Configuration Files   Contents   Index
Thomas Brandes 2004-03-19