Fortran-DVM - detailed design (beginning)

Fortran-DVM compiler. Detailed design (continuation)
* 30 June 2000 *


5 Detailed description of compiler modules

5.1 Translating Fortran DVM constructs (module dvm.cpp)

The scheme of high level function call of the main module dvm.cpp is:

int main ( int
char
argc,
*argv[] );

The function processes the compilation parameters and sets compilation mode on. It initializes compiler data structures, calls the TranslateFileDVM( ) function to restructure parse tree according to the compilation mode, and calls the unparse( ) class SgFile member function for generating new source code from restructured internal form. The function returns 1 if the errors are detected in the program.

void TranslateFileDVM ( SgFile *f )

f - pointer to the program file

If the compilation mode is parallel program generating (–p option) then the TransFunc( ) function is called, otherwise the InsertDebugStat( ) function is called.

void TransFunc ( SgStatement *func )

func - pointer to the procedure header statement

The statements of procedure are scanned in lexical order until last statement of procedure.

Specification statements and directives processing.

A DISTRIBUTE directive is included in the list. The function builds the aligning trees processing ALIGN directives.

On scanning specification directives and statements, the Lib-DVM function calls for creating distributed arrays are generated and inserted in the program before first executable statement. The GenDistArray( ) function creates distributed arrays (Lib-DVM object) for array with DISTRIBUTE attribute and all arrays immediately or ultimately aligned with it.

Executable statements and directives processing.

The distributed array element references in assignment, CALL , arithmetical IF, logical IF, IF-THEN, ELSE_IF, and computed GOTO statements are linearized.

A DVM directive is replaced by sequence of Lib-DVM functions calls. When new statement is inserted in a program restructuring of the control graph (carrying or substituting label, replacement of logical IF statement by IF...THEN...ENDIF construct, and so on) is performed if necessary. The ReplaceContext( ), doAssignStmtAfter( ), InsertNewStatementAfter( ), InserNewStatementBefore( ) functions serve for inserting new statement in parse tree and restructuring it.

After processing last statement of procedure, the declaration statements for temporary variables used for argument passing, storing function value, buffering I/O, and addressing distributed arrays are created and inserted in specification part of procedure (DeclareVarDVM( )).

List of called functions:

TempVarDVM ChangeDistArrayRef
DeclareVarDVM ChangeDistArrayRef_Left
RTLInit DebugVarArrayRef
RTLExit DebugVarArrayRef_Left
BeginBlock ChangeArg_DistArrayRef
EndBlock DebugArg_VarArrayRef
GetAM ReplaceAssignByIf
GetVM ReplaceContext
doDisRuleArrays ParallelLoop
GenDistArray AddToGroupNameList
GenAlignArray AllocateArray
AlignTree AssignPointer
InsertNewStatementBefore CreateBoundGroup
InsertNewStatementAfter ShadowList
doAssignStmt Calculate
doAssignStmtAfter hasNewValueClause
doAssignTo_After StartBound
Extract_Stmt WaitBound
ContinueWithLabel SendBoun
RemoteAccessEnd CreateReductionGroup
GoRoundEntry ReductionList
BeginBLockForEntry StartRed
initMask WaitRed
ReplaceDoLabel ReductionVarsStart
Error doAlignRule
err RealignArray
addToStmtList RealignArr
ReplaceDoNestLabel_Above DistObjectRef
CloseDoInParLoop RedistributeArray
CloseParLoop control_list_open
EndParLoop ReplaceByIfStmt
EndPl InsertSendIOSTAT
isDoEndStmt InsertSendInquire
CloseLoop InsertSendInputList
DebugLoop IOcontrol
SeqLoopBegin TestIOList
SeqLoopEndInParLoop IO_ThroughBuffer
OverLoopAnalyze D_Skpbl
SeqLoopEnd D_Lnumb
DeleteObject D_Fname
OpenInterval St_Binter
CloseInterval St_Einter
Value St_Biof
lastStmtOfDo St_Eiof
AddRemoteAccess St_Eloop
RemoteVariableList BeginDebugFragment
RankOfSection EndDebugFragment
Rank ArrayHeader
isListOfArrays TypeControl
ReconfPS CreateTaskArray
InitGroups SetDoVar
InitHeap PSReference
hasOntoClause SearchDistArrayRef
DebugTaskRegion CloseTaskRegion
StartTask isParallelLoopEndStmt
StopAM CreateBG
doIfThenConstrForPrefetch LoadBg
InitRemoteGroups IsLIFReductionOp
INDLoopBegin IsReductionOp
IEXLoopAnalyse OffDoVarsOfNest
IndependentLoop  

void InsertDebugStat ( SgStatement *func )

func - pointer to the procedure header statement

The function generates the sequential program including Debugger and Performance Analyzer function calls. Parameters of compilation (-e… and -d…) control the process of new statement generating.

The statements of procedure are scanned in lexical order until last statement of procedure. The specification statements and directives are omitted.

If the user specify non-zero level of debugging in compiler run command, the statements containing expressions (assignment, CALL , arithmetical IF and so on) are surrounded by Debugger functions for controlling values of variables. The function inserts Debugger calls at the beginning and the end of each parallel and sequential loop and Performance Analyzer calls at the beginning and the end of each interval.

List of called functions:

TempVarDVM DebugVarArrayRef
RTLInit DebugVarArrayRef_Left
RTLExit DebugArg_VarArrayRef
InsertNewStatementBefore SkipParLoopNest
InsertNewStatementAfter ReplaceContext
doAssignStmtAfter ParallelLoop_Debug
Extract_Stmt isParallelLoopEndStmt
addToStmtList AddToGroupNameList
ReplaceDoNestLabel_Above CreateReductionGroup
CloseDoInParLoop ReductionList
CloseParLoop D_Lnumb
isDoEndStmt D_Fname
ReplaceFuncCall D_Skpbl
InitRemoteGroups D_Iter_ON
CloseLoop St_Binter
DebugLoop St_Einter
SeqLoopBegin St_Biof
SeqLoopEndInParLoop St_Eiof
OverLoopAnalyze St_Eloop
SeqLoopEnd DeclareVarDVM
OpenInterval DeleteObject
CloseInterval Error
Value err
initMask InitGroups
isLIFReductionOp IsReductionOp
IEXLoopAnalyze IndependentLoop_Debug
BeginDebugFragment SkipIndepLoopNest
EndDebugFragment DebugTaskRegion
INDReductionDebug CloseTaskRegion

void initialize ( )
This function initializes the variables of compiler used in the mode of generating Debugger and Performance Analyzer calls.

void initVariantNames ( )
This function initializes the table of variant tags.

void initLibNames ( )
This function initializes the Lib-DVM function name table.

void initDVM ( )
This function inserts the Lib-DVM function symbols in the Symbol Table.

void initMask ( )
This function cleans the mask of Lib-DVM function usage. The functions generating Lib-DVM library calls reset the corresponding mask element to 1. The declaration statement is created only for masked (used in procedure) Lib-DVM functions.

void TempVarDVM ( SgStatement *func )

func - pointer to the procedure header statement

The function puts in the Symbol Table the following symbols of reserved variables:

integer dvm000(...) - array for preparing arguments and storing Lib-DVM function results
integer hpf000(...) - array for preparing arguments and storing Lib-DVM function results
(it is used for HPF-DVM program only)
integer i0000m(0:0) - base for addressing distributed arrays of integer type
real r0000m(0:0) - base for addressing distributed arrays of real type
double precision d0000m(0:0) - base for addressing distributed arrays of double
precision type
logical l0000m(0:0) - base for addressing distributed arrays of logical type
complex c0000m(0:0) - base for addressing distributed arrays of complex type
integer i000io(1000) - buffer for I/O of distributed arrays of integer type
real r000io(1000) - buffer for I/O of distributed arrays of real type
double precision d000io(1000) - buffer for I/O of distributed arrays of double precision
type
logical l000io(1000) - buffer for I/O of distributed arrays of logical type
complex c000io(1000) - buffer for I/O of distributed arrays of complex type
integer idvm00 - do-variables of loops implementing I/O of
  idvm01 distributed arrays
  . . .  
  idvm07  
integer i000bf(...) - buffer for storing remote data of integer type
real r000bf(...) - buffer for storing remote data of real type
double precision d000bf(1000) - buffer for storing remote data of double precision type
logical l000bf(1000) - buffer for storing remote data of logical type
complex c000bf(1000) - buffer for storing remote data of complex type

void DeclareVarDVM ( SgStatement *lstat )

lstat - pointer to the statement

Creates the declaration statements of reserved variables used in procedure:

and inserts them in procedure after the statement lstat (last declaration statement or the statement preceding DATA statement). (See TempVarDVM( )).

5.1.1 Distributed array creation and remapping

void GenDistArray ( SgSymbol
int
SgExpression
SgStatement
*das,
idisars,
*ps
*stdis );
       
das - pointer to the symbol of distributed array
idisars - the mapping rules (distribution formats) are stored in the elements of reserved array
dvm000
: dvm000(idisars),
dvm000(idisars+1),...
ps - pointer to the processor array expression reference
stdis - pointer to the DISTRIBUTE statement

Generates the statements to create Lib-DVM object and allocates a memory for array declared with DISTRIBUTE attribute and for all the arrays immediately or ultimately aligned with it, and inserts these statements before first executable statement of the procedure.

void GenAlignArray ( align
align
int
int
*node,
*root,
nr
iaxis );
       
node - pointer to the alignment tree node that corresponds to the aligned array
root - pointer to the alignment tree node that corresponds to the array node is aligned with
nr - the number of aligning rules
iaxis - the aligning rules (AxisArray(nr), CoefArray(nr), ConstArray(nr)) are stored in the elements of reserved array
dvm000 : dvm000(iaxis),
dvm000(iaxis+1),...

Generates the statements to create Lib-DVM object and allocates a memory for array declared with ALIGN attribute and inserts these statements before first executable statement of the procedure.

void doAlignRule_1 ( int rank )

rank - rank of array

Generates the statements to initialize 3 arrays of aligning rules:

AxisArray(i) = 1
CoeffArray(i) = 1
ConstArray(i) = 1 , i=1, rank

which are used as arguments of Lib-DVM function align( ).

int doAlignRule ( SgSymbol
SgStatement
int
*alignee,
*algn_st,
iaxis );
       
alignee - pointer to the symbol of aligned array
algn_st - pointer to the ALIGN statement
iaxis - index of reserved array dvm000 where the AxisArray(1) is stored

The function generates the statements to create arrays of aligning rules used as arguments of Lib-DVM function align( ).

The function returns the number of aligning rules (the length of align-source-list in ALIGN directive).

void AlignTree ( align *root )

root - pointer to the alignment tree root

Traverses the alignment tree and calls the function GenAlignArray() to create distributed array for each aligned array (node of tree).

int doDisRuleArrays ( SgExpression
SgExpression
*dist_format,
*aster );
dist_format - distribution format list
aster - pointer to the expression * or null pointer

The function generates the statements to create 2 arrays of mapping rules used as arguments (AxisArray, DistrParamArray) of distr( ) and redis( ) Lib-DVM functions.

The function returns the index of array element dvm000 storing the first mapping rule (AxisArray(1)).

void RedistributeArray ( SgSymbol
int
SgExpression
int
SgExpression
SgStatement
*das,
idisars,
*ps
sign
*dasref
*stdis );
       
das - pointer to the symbol of redistributed array
idisars - the mapping rules (distribution formats) are stored in the elements of reserved array
dvm000 : dvm000(idisars),
dvm000(idisars+1),...
       
ps - pointer to the processor array reference
sign - the flag that defines whether contents of redistributed array should be updated or not
dasref - pointer to the expression, that is redistributed array reference
stdis - pointer to the REDISTRIBUTE directive

Generates statement to redistribute the array:

dvm000(i) = redis(...)

and inserts it in procedure in place of REDISTRIBUTE directive.

For array specified by directive ALIGN and DISTRIBUTE of the form

*DVM$ DISTRIBUTE  :: …

the sequence of statements to create distributed array is produced.

void RealignArray ( SgSymbol
SgSymbol
int
int
int
SgStatement
*als,
*tgs,
iaxis
nr
new_sign,
*stal );
       
als - pointer to the symbol of realigned array
tgs - pointer to the symbol of the array, als is aligned with
iaxis - the aligning rules are stored in the elements of reserved array
dvm000 : dvm000(iaxis),
dvm000(iaxis+1),...
nr - the number of aligning rules
new_sign - the flag that defines whether the contents of realigned array should be updated or not
stal - pointer to the REALIGN directive

Generates statement to realign the array:

dvm000(i) = realn(...)

and inserts it in procedure in place of REALIGN directive.

void AllocateArray ( SgStatement
distribute_list
*stmt,
*distr );
stmt - pointer to the statement of ALLOCATE function call
distribute_list - DISTRIBUTE directive list

If the POINTER variable in left part of assignment statement stmt has DISTRIBUTE attribute then AllocDistArray( ) function is called, otherwise AllocAlignArray( ) function is called.

void AllocateDistArray ( SgSymbol
SgExpression
SgStatement
SgStatement
*p,
*desc,
*stdis
*stmt );
       
p - pointer to the symbol of POINTER variable
desc - pointer to the descriptor reference expression (descriptor - vector of the dimension sizes of dynamic array)
stdis - pointer to the DISTRIBUTE directive specifying p
stmt - pointer to the statement of ALLOCATE function call:
p = ALLOCATE(desc,...)

Generates the statements to create Lib-DVM object and allocates a memory for dynamic array declared with DISTRIBUTE attribute and for all the arrays immediately or ultimately aligned with it, and inserts these statements in procedure in place of statement stmt.

void AllocateAlignArray( SgSymbol
SgExpression
SgStatement
*p,
*desc,
*stmt );
       
p - pointer to the symbol of POINTER variable
desc - pointer to the descriptor reference expression
(descriptor - vector of the dimension sizes of dynamic array)
stmt - pointer to the statement of ALLOCATE function call:
p = ALLOCATE(desc,...)

The function generates the statements for creating distributed array declared with ALIGN and POINTER attributes and for the arrays aligned with it , and inserts these statements in procedure in place of statement stmt.

AlignTreeAlloc( ) and AlignAllocArray( ) are called.

void AlignTreeAlloc ( align *root )

root - pointer to the alignment tree root

Traverses the alignment tree and calls the function AlignAllocArray() to create distributed arrays for the nodes of tree that are corresponds to the aligned arrays not having POINTER attribute.

void AlignAllocArray( align
align
int
int
SgExpression
*node,
*root,
nr
iaxis
*desc );
node - pointer to the alignment tree node that corresponds to the aligned array with attribute POINTER
root - pointer to the alignment tree node that corresponds to the array node is aligned with
nr - the number of the aligning rules
iaxis - the aligning rules (AxisArray(nr), CoefArray(nr), ConstArray(nr)) are stored in the elements of reserved array
dvm000 : dvm000(iaxis),
dvm000(iaxis+1),...
desc - pointer to the descriptor reference expression (descriptor - vector of the dimension sizes of dynamic array)

Generates the statements to create Lib-DVM object and allocates a memory for dynamic array declared with ALIGN attribute and inserts these statements in procedure in place of statement pointer = ALLOCATE(desc,...).

void ArrayHeader ( SgSymbol
int
*ar,
ind );
ar - pointer to the symbol of array
ind - 0, if ar is POINTER
  1, if ar is distributed array
  n, where dvm000(n) is reserved array element storing pointer to the abstract machine representation, if ar is TEMPLATE
  -1, if ar is declared as array with postponed distribution.

Adds the attribute (ARRAY_HEADER) to the symbol of distributed object ar (ind - is attribute value).

5.1.2 Distributed array referencing

void DistArrayRef ( SgExpression
int
SgStatement
*e,
modified
*st );
       
e - pointer to the array reference expression
modified - flag specifying whether array reference occurs in left or right part of assignment statement
st - pointer to the statement where the array reference occurs.

Linearizes distributed array element reference, that is, replaces reference

A(I1,I2, ..., IN)

by

where:

A - distributed array name,
base - i0000m, if A is of type integer
    r0000m, if A is of type real
    d0000m, if A is of type double precision
    c0000m, if A is of type complex
    l0000m, if A is of type logical

 

SgExpression *LinearForm ( SgSymbol
SgExpression
*ar,
*el );
ar - pointer to the symbol of distributed array
el - pointer to the subscript list (I1,I2, ..., IN) of array reference

Generates the expression

where A - distributed array name.

void ChangeDistArrayRef ( SgExpression *e )

e - pointer to the expression

Traverses the expression e and linearizes each distributed array element reference (calls DistArrayRef( )).

void ChangeDistArrayRef_Left ( SgExpression *e )

e - pointer to the expression

Traverses the expression e in left part of assignment statement and linearizes distributed array element reference (calls DistArrayRef( )).

void ChangeArg_DistArrayRef ( SgExpression *ele )

ele - pointer to the expression that is an actual argument of procedure

Traverses the expression ele and linearizes distributed array element references, except whole array reference.

void DebugVarArrayRef( SgExpression
SgStatement
*e,
*stmt );
e - pointer to the expression
stmt - pointer to the statement that contains the expression e

The function traverses the expression e and linearizes each distributed array element reference (calling DistArrayRef( )). If debugging compilation mode is set on, the function inserts the statements before stmt to check values of the variables during the execution in debugging mode.

void DebugVarArrayRef_Left ( SgExpression
SgStatement
SgStatement
*e,
*stmt
*stcur );
       
e - pointer to the expression in left part of assignment statement
stmt - pointer to the assignment statement that contains the expression e
stcur - pointer to the statement after which new statements should be inserted.

The function traverses the expression e and linearizes each distributed array element reference. If debugging compilation mode is set on, this function inserts the Debugger calls after stcur and after stmt to check values of the variables during the execution in debugging mode.

void DebugArg_VarArrayRef ( SgExpression
SgStatement
*ele,
*stmt );
ele - pointer to the expression that is an actual argument of procedure
stmt - pointer to the statement that contains the expression e

The function traverses the expression e and linearizes each distributed array element reference except whole array reference. If debugging compilation mode is set on, the function inserts the statements before stmt to check values of the variables during the execution in debugging mode.

5.1.3 Parallel loop

void ParallelLoop ( SgStatement *stmt )

stmt - pointer to the PARALLEL directive

The parallel loop:

*DVM$ PARALLEL (I1, ..., In)  ON  A(…)...
      DO  label   I1 = ...
        .   .   .
      DO  label   In = ...
         loop-body
label CONTINUE 

is translated into

      [ ACROSS-block-1 ]
      [ REDUCTION-block-1 ]
* creating parallel loop
      ipl = crtpl(n)
      [ SHADOW-RENEW-block-1 ]
      [ SHADOW-START-block ]
      [ SHADOW-WAIT-block ]
* mapping parallel loop                                   (1)
      it = mappl(ipl,A,...)
      [ SHADOW-RENEW-block-2 ]
      [ REDUCTION-block-2 ]
      [ REMOTE-ACCESS-block ]
* inquiry of continuation of parallel loop execution
lab1  if(dopl(ipl) .eq. 0)  go to  lab2
      DO  label   I1 = ...
        .   .   .
      DO  label   In = ...
         loop-body
label CONTINUE 
      go to lab1
* terminating parallel loop
lab2  it = endpl(ipl)
      [ ACROSS-block-2 ]
      [ REDUCTION-block-3 ]

The function generates and inserts in procedure all the statements preceding the DO nest. In addition, the initial, end and step value of do-variables in parallel DO-nest are changed. The statements following end statement of parallel loop:

label CONTINUE

are generated by TransFunc( ) when this statement is processing.

If debugging compilation mode is set on, the CALL statements:

call dbegpl(...)
call  diter(...)
call  dendl(...)

are created and inserted in block (1) before IF statement, before first statement of parallel loop body, and after the statement

go to lab1

correspondingly.

If compilation mode is performance analyzing, the CALL statements:

call bploop(...)
call  eloop(...)

are created and inserted before the first and after the last statement of the block (1).

The following functions are called to create blocks implementing ACROSS, SHADOW_RENEW, REDUCTION, and REMOTE_ACCESS specifications:

DepList
ShadowList
doIfForReduction
ReductionList
RemoteVariableList

void ParallelLoop_Debug ( SgStatement *stmt )

stmt - pointer to the PARALLEL directive

If debugging compilation mode is set on, the CALL statements:

call dbegpl(...)
call  diter(...)

are created and inserted before the DO loop nest and before the first statement of parallel loop body correspondingly. This function generates the REDUCTION-block-1 and REDUCTION-block-2 if necessary.

If compilation mode is performance analyzing, the CALL statements:

call bploop(...)
call  eloop(...)

is created and inserted before and after the DO loop nest.

void ReductionList ( SgExpression
SgExpression
SgStatement
SgStatement
SgStatement
*el,
*gref
*st
*stmt1
*stmt2 );
       
el - reduction list
gref - pointer to the reduction group reference expression
st - pointer to the PARALLEL directive with REDUCTION clause containing the reduction list el
stmt1 - pointer to the statement after which the new statements is inserted
stmt2 - pointer to the statement after which the new statements is inserted

Generates and inserts in procedure the statements:

* creating reduction
      dvm000(irv) = crtrgf(reduction-function, red-var,…)
* including reduction in reduction group
      dvm000(i) = insred(gref,dvm000(irv),…)

for each reduction in reduction list el. The first statement is inserted after stmt1 and the second one after stmt2.

void ShadowList ( SgExpression
SgStatement
SgExpression
*el,
*st
*gref );
       
el - renewee-list
st - pointer to the PARALLEL directive with SHADOW_RENEW clause or to the SHADOW_GROUP directive containing the renewee-list el
gref - pointer to the shadow group reference expression

Generates and inserts in procedure the statement:

* including shadow edge in the group
      dvm000(i) = inssh(gref,array,...)

for each array in the renewee-list.

void RemoteVariableList ( SgSymbol
SgExpression
SgStatement
*group
*rml,
*stmt );
       
group - pointer to the symbol of group
rml - array reference list
stmt - pointer to the PARALLEL directive with REMOTE_ACCESS clause or to the REMOTE_ACCESS directive containing the array reference list rml

The function generates and inserts in procedure the statements to read remote data in buffer (REMOTE-ACCESS-block).

1) In case of synchronous REMOTE_ACCESS specification the following statements are generated:

{
* creating buffer array
      it = crtrbl(array-header,buffer-header,…)
* starting load of buffer array
      it = loadrb(buffer-header,0)
* waiting for completion of loading buffer array
      it = waitrb(buffer-header)
* correcting coefficient CNB of buffer array elements addressing,
* where NB is rank of buffer array
      buffer-header(NB+2) = buffer-header(NB+1)- 
     *                      buffer-header(NB)*buffer-header(NB+3) - 
     *                      buffer-header(3)*buffer-header(2*NB+2)
}...   for each remote-access reference

2) In case of asynchronous REMOTE_ACCESS specification (with group RMG) the following statements are generated:

         IF (RMG(2) .EQ. 0) THEN
    {
*        creating buffer array
         it = crtrbl(array-header,buffer-header,…)
*        correcting coefficient CNB of buffer array elements addressing
         buffer-header(NB+2) = buffer-header(NB+1)- 
     *                         buffer-header(NB)*buffer-header(NB+3) - 
     *                         buffer-header(3)*buffer-header(2*NB+2)
*        starting load of buffer array
         it = loadrb(buffer-header,0)
*        waiting for completion of loading buffer array
         it = waitrb(buffer-header)
*        including buffer array in group RMG
         it = insrb(RMG(1),buffer-header)
    }...   for each remote-access reference
      ELSE
         IF (RMG(3) .EQ. 1) THEN
*        waiting for completion of loading all the buffer arrays of group
            it = waitbg(RMG(1))
            RMG(3) = 0
         ENDIF
      ENDIF

5.2 Translating input/output statements (module io.cpp)

The compiler module io.cpp involves the functions to translate input/output statements.

In DVM model, input, output and other operations with external files are executed by single processor ( I/O processor ), which is determined by Run-Time System. I/O of a replicated variable deals with variable copy allocated on I/O processor. I/O of a distributed array deals with buffer array allocated on I/O processor. Input data are sent to all other processors owing the variables of input list. When the distributed array is output, data are transferred into the buffer from other processors owing elements of the array.

int TestIOList ( SgExpression
SgStatement
*iol,
*stmt );
iol - I/O item list
stmt - pointer to the I/O statement

The function analyzes input/output item list. If there are not any distributed array references in the list, the function returns 1, and 0 otherwise.

Calls ImplicitLoopTest( ) , IOitemTest( ).

int ImplicitLoopTest( SgExpression
SgStatement
*eim,
*stmt );
eim - pointer to the implicit loop
stmt - pointer to the I/O statement

The function analyzes item list of implicit loop. If there are no distributed array references in the list, the function returns 1, and 0 otherwise.

int IOitemTest ( SgExpression
SgStatement
*e,
*stmt );
e - pointer to item of I/O list
stmt - pointer to the I/O statement

If the I/O item is not a distributed array reference this function returns 1, and 0 otherwise.

int Iocontrol ( SgExpression
SgExpression
int
*e,
*ioc[]
type );
       
e - control information list
ioc - array of I/O control parameters
type - variant tag of I/O statement(PRINT_STAT, WRITE_STAT, READ_STAT)

The function analyzes the control information list of the data transfer statement and assigns the value of control parameters (UNIT, FMT, ERR, and so on) to the elements of array ioc[]. If there are some syntax errors it returns 0, else 1.

int control_list1 ( SgExpression
SgExpression
*e,
*ioc[] );
e - control information list
ioc - array of I/O control parameters

The function analyzes the control information list of the BACKSPACE, REWIND and ENDFILE statement and assigns the value of control parameters (UNIT, ERR, and so on) to the elements of array ioc[]. If there are some syntax errors it returns 0, else 1.

int control_list_open ( SgExpression
SgExpression
*e,
*ioc[] );
e - control information list
ioc - array of I/O control parameters

The function analyzes the control information list of the OPEN, CLOSE and INQUIRE statement and assigns the value of control parameters (UNIT, ERR, and so on) to the elements of array ioc[]. If there are some syntax errors it returns 0, else 1.

void IO_ThroughBuffer( SgSymbol
SgStatement
*ar,
*stmt );
e - pointer to the symbol of distributed array
stmt - pointer to the I/O statement

In case of I/O of distributed array the memory is allocated in user program for I/O buffer.

Let A(N1,N2,...,Nk) is distributed array of rank k, BUF(L) - vector of the same type as array A (named i000io if A is of type integer, or r000io if A is of type real,...).

The function replaces a statement I/O of A by the sequence of statements according to the following scheme:

input:

IF(tstio( ) .ne. 0 ) READ (...) (BUF(j), j = 1, N1 * ...*Nn * m)
  n >= 1
copying-array-section (BUF(1 : N1 * ...*Nn * m),
  n >= 1
  A(1: N1,...,1:Nn , In+1 +1: In+1 +m , In+2 +1, ..., Ik +1) )
    n >= 1   n+1 <= k   n+2 <= k  

output:

copying-array-section (BUF(1 : N1 * ...*Nn * m),
  n >= 1
  A(1: N1,...,1:Nn , In+1 +1: In+1 +m , In+2 +1, ..., Ik +1) )
    n >= 1   n+1 <= k   n+2 <= k  
IF(tstio( ) .ne. 0 ) WRITE (...) (BUF(j), j = 1, N1 * ...*Nn * m)
  n >= 1

label CONTINUE

The operation of copying-array-section is implemented by Lib-DVM function arrcpy( ).

5.3 Restructuring parse tree (module stmt.cpp)

The functions for restructuring parse tree compose the module stmt.cpp.

void InsertNewStatementAfter( SgStatement
SgStatement
SgStatement
*stat,
*current
*cp );
       
stat - pointer to the inserted statement
current - pointer to the statement after which stat is inserted
cp - pointer to the control parent for stat

The statement stat is inserted in the parse tree (program) after statement current and its control parent is cp.

void InsertNewStatementBefore( SgStatement
SgStatement
*stat,
*current );
stat - pointer to the inserted statement
current - pointer to the statement before which stat is inserted

The statement stat is inserted in the parse tree (program) before statement current.

void doAssignStmt ( SgExpression *re )

re - pointer to the expression that is the right part of the assignment statement

Creates the assignment statement with right part re :

dvm000(i) = re

and inserts it before the statement pointed by global variable where.

SgExpression *LeftPart_AssignStmt ( SgExpression *re )

re - pointer to the expression that is the right part of the assignment statement

Creates the assign statement with right part re :

dvm000(i) = re

and inserts it before the statement where (global variable). The function returns left part of this statement.

void doAssignTo ( SgExpression
SgExpression
*le,
*re );
le - pointer to the expression that is the left part of the assignment statement
re - pointer to the expression that is the right part of the assignment statement

Creates the assignment statement:

le = re

and inserts it before the statement where (global variable).

void doAssignTo_After ( SgExpression
SgExpression
*le,
*re );
le - pointer to the expression that is the left part of the assignment statement
re - pointer to the expression that is the right part of the assignment statement

Creates the assign statement:

le = re

and inserts it after current statement cur_st (global variable).

void doAssignStmtAfter( SgExpression *re );
re - pointer to the expression that is the right part of the assignment statement

Creates the assignment statement with right part re :

dvm000(i) = re

and inserts it after the current statement cur_st (global variable).

void doAssignStmtBefore( SgExpression
SgStatement
*re,
*current );
re - pointer to the expression that is the right part of the assignment statement
current - pointer to the statement

Creates the assign statement with right part re :

dvm000(i) = re

and inserts it before the statement current.

void Extract_Stmt ( SgStatement *st )

st - pointer to the statement

Removes the statement st from the parse tree.

void ReplaceByIfStmt ( SgStatement *st )

st - pointer to the statement

Replaces the statement st by IF statement:

IF (tstio( ) .NE. 0) st

void ReplaceDoNestLabel( SgStatement
SgLabel
*last_st,
*new_lab );
last_st - pointer to the statement ending DO statement nest
new_lab - pointer to the new label

Replaces the label of DO statement nest, which is ended with last_st, by new_lab and inserts CONTINUE statement.

        DO 1 I1 = 1,N1                     DO   new_lab   I1 = 1,N1
        DO 1 I2 = 1,N2                     DO   new_lab   I2 = 1,N2
           .   .   .           =>                   .   .   .       
        DO 1 Ik = 1,Nk                     DO   new_lab   Ik = 1,Nk
           .   .   .                                .   .   . 
  1     last-statement               1     last-statement   
                                   new_lab CONTINUE
void ReplaceDoNestLabel_Above ( SgStatement
SgStatement
SgLabel
*last_st,
*from_st,
*new_lab );
       
last_st - pointer to the statement ending DO statement nest
from_st - pointer to the statement
new_lab - pointer to the new label

Replaces the label of those DO statements, that are located prior statement from_st and ended with statement last_st, by new_lab and inserts CONTINUE statement.

    DO 1 I1 = 1,N1                            DO new_lab  I1 = 1,N1
        .  .   .                                  .   .   .       
      DO 1 Ik = 1,Nk                             DO  new_lab  Ik = 1,Nk
CDVM$ PARALLEL (J1,...,Jm) ON ...    =>    CDVM$ PARALLEL (J1,...,Jm) ON ...
      DO 1 J1 = 1,N1                             DO  1    J1 = 1,N1
        .   .   .                                 .   .   .          
      DO 1 Jm = 1,Nm                             DO    1    Jm = 1,Nm
        .   .   .                                 .   .   . 
1     last_statement                       1     last_statement
                                         new_lab CONTINUE
void ReplaceDoLabel ( SgStatement
SgLabel
*last_st,
*new_lab );
last_st - pointer to the last statement of DO construct
new_lab - pointer to the new label

Replaces the label of DO statement by new_lab and inserts CONTINUE statement.

      DO  1  I = 1,N                       DO  new_lab  I = 1,N
          .   .   .          =>                .   .   . 
1    last-statement                  1     last-statement
                                           new_lab CONTINUE

void ReplaceContext ( SgStatement *stmt )

stmt - pointer to the statement

If the statement stmt or logical IF statement including it is last statement of DO-loop body, the function replaces the label of DO statements nest and inserts CONTINUE statement (ReplaceDoNestLabel(stmt)). If the control parent of statement stmt is logical IF statement, this function replaces it with IF_THEN construct.

void LogIf_to_IfThen ( SgStatement *stmt )

stmt - pointer to the statement

Replaces logical IF statement:

IF ( condition ) stmt

by construct:

IF ( condition ) THEN
stmt
ENDIF

SgStatement *doIfThenConstr ( SgSymbol *ar )

ar - pointer to the symbol of array

Creates construct:

IF ( ar(1) .EQ. 0) THEN
ENDIF

and returns the pointer to IF statement.

int isDoEndStmt ( SgStatement *stmt )

stmt - pointer to the statement

If the statement stmt is the last statement of DO loop body, the function returns 1 else it returns 0.

SgStatement *lastStmtOfDo ( SgStatement *stdo )

stdo - pointer to the DO statement

Returns the pointer to the last statement of DO loop body.

int isParallelLoopEndStmt ( SgStatement *stmt )

stmt - pointer to the statement

If the statement stmt is the last statement of parallel loop, the function returns 1 else it returns 0.

5.4 Translating HPF-DVM constructs (module hpf.cpp)

The module hpf.cpp is intended for translating constructs of HPF-DVM language.

5.4.1 Processing distributed array references in HPF-DVM

int SearchDistArrayRef ( SgExpression
SgStatement
*e,
*stmt );
e - pointer to the expression
stmt - pointer to the statement which contains the expression e

This function looks the expression e for distributed array references, adds the attribute REMOTE_VARIABLE to the reference, generates statements for loading the value of each distributed array element into buffer, and inserted them before statement stmt (calls BufferDistArrayRef( )).

If there are distributed array references in expression e, it returns 1, else – 0.

The function is called from TransFunc( ) when an executable statement outside the range of INDEPENDENT loop is processing.

void BufferDistArrayRef ( SgExpression
SgStatement
*e,
*stmt );
e - pointer to the distributed array element reference
stmt - pointer to the statement which contains the expression e

Generates statements for loading the value of distributed array element to buffer and inserting them before statement stmt, adds the attribute REMOTE_VARIABLE to distributed array reference e.

SgExpression *IND_ModifiedDistArrayRef( SgExpression
SgStatement
*e,
*st );
e - pointer to the distributed array element reference
st - pointer to the assignment statement which contains the expression e

The function analyzes the distributed array element reference in left part of assignment statement whether that may be used as target for mapping index space of INDEPENDENT loop nest. It returns the target or NULL.

The function is called from DistArrayRef( ) when an assignment statement inside the range of INDEPENDENT loop is processing.

void *IND_UsedDistArrayRef( SgExpression
SgStatement
*e,
*st );
e - pointer to the distributed array element reference
st - pointer to the assignment statement which contains the expression e

The function determines the kind of reference and includes it in the list (IND_refs) which is processed by function RemoteVariableListIND( ). The function calls function IND_DistArrayRef( ) to linearize the reference.

The function is called from DistArrayRef( ) when an executable statement inside the range of INDEPENDENT loop is processing.

void *IND_DistArrayRef( SgExpression
SgStatement
IND_ref_list
*e,
*st
*el );
       
e - pointer to the distributed array element reference
st - pointer to the assignment statement which contains the expression e
el - pointer to the element of reference list

Linearizes distributed array element reference in right part of assignment statement, that is, replaces the reference

A(I1,I2, ..., IN)

by

where:

HeaderCopy - array of coefficients to address the distributed array element which are calculated as linear function of array header elements
base - i0000m , if A is of type integer
r0000m , if A is of type real
d0000m , if A is of type double precision
c0000m , if A is of type complex
l0000m , if A is of type logical

5.4.2 INDEPENDENT loop

void IndependentLoop ( SgStatement *stmt )

stmt - pointer to the INDEPENDENT directive

The INDEPENDENT loop nest:

*HPF$ INDEPENDENT
      DO  label   I1 = ...
        .   .   .
*HPF$ INDEPENDENT
      DO  label   In = ...
         loop-body
label CONTINUE 

is translated into

* creating parallel loop
      ipl = crtpl(n)
* mapping parallel loop
      it = mappl(ipl,...)
      [ inquiry-block ]
* inquiry of continuation of parallel loop execution
lab1  if(dopl(ipl) .eq. 0)  go to  lab2                            (2)
      DO  label   I1 = ...
        .   .   .
      DO  label   In = ...
         loop-body
label CONTINUE 
      go to lab1
* terminating parallel loop
lab2  it = endpl(ipl)

The function generates and inserts in procedure all the statements preceding the DO nest exempt inquiry-block. Besides, the initial, end and step value of do-variables in parallel DO-nest are changed. The statements following last statement of parallel loop are generated by TransFunc( ) when it is processing. The inquiry-block is created by function RemoteVariableListIND( ).

If compilation mode is set on debugging, the CALL statements:

call dbegpl(...)
call  diter(...)
call  dendl(...)

are created and inserted in block (2) before IF statement, before first statement of parallel loop body, and after the statement

go to lab1

correspondingly.

If compilation mode is set on performance analyzing, the CALL statements:

call bploop(...)
call  eloop(...)

are created and inserted before the first and after the last statement of the block (2).

void IndependentLoop_Debug ( SgStatement *stmt )

stmt - pointer to the INDEPENDENT directive

If compilation mode is set on debugging, the CALL statements:

call dbegpl(...)
call  diter(...)

are created and inserted before the DO loop nest and before the first statement of parallel loop body correspondingly.

If compilation mode is set on performance analyzing, the CALL statements:

call bploop(...)
call  eloop(...)

is created and inserted before and after the DO loop nest.

void RemoteVariableListIND ( )
If distributed array references occur in right part of assignment statements inside INDEPENDENT loop body, the following block of statements to read remote data is generated:

      ishg = 0
      ibg  = 0
{
* inquiring about kind of accessing distributed array element(s)
      kind = rmkind(array-header,buffer-header,…,
     *                              low-shadow-array,high-shadow-array) 
      IF (kind .EQ. 4) THEN
         IF (ishg .EQ. 0) THEN
*        creating remote data buffers group 
             ibg = crtbg(0,1)
         ENDIF
*        including buffer array in group RMG
         it = insrb(ibg, buffer-header)
*        calculating coefficients of array elements addressing
*        NB is rank of buffer array
         header-copy(1)   = buffer-header(2)
                      .   .   .
         header-copy(NB-1) = buffer-header(NB)
         header-copy(NB)   = 1
         header-copy(NB+1) = buffer-header(NB+1)- 
     *                      buffer-header(NB)*buffer-header(NB+3) - 
     *                      buffer-header(3)*buffer-header(2*NB+2)
         ELSE
            IF (kind .NE. 1) THEN
               IF (ishg .EQ. 0) THEN
*              creating shadow edges group 
                  ishg = crtshg(0)
               ENDIF
*              including shadow edge in the group 
*              (with corner elements or not)
               IF (kind .EQ. 2) THEN
                  it = inssh(ishg,array-header,low-shadow-array,
     *                                         high-shadow-array,0)
               ELSE
                  it = inssh(ishg,array-header,low-shadow-array,
     *                                         high-shadow-array,1)
            ENDIF
*        calculating coefficients of array elements addressing
         header-copy(1)   = f1(array-header,IkN)
                      .   .   .
         header-copy(NB)   = f1(array-header,Ik1)
         header-copy(NB+1) = f2(buffer-header(2:N+1),I1,,IN)
         ENDIF
}...   for each occured distributed array reference
* renewing shadow edges group 
         IF (ishg .NE. 0) THEN
            it = strtsh(ishg)
            it = waitsh(ishg)
         ENDIF
* loading remote data buffers group 
        IF (ibg .NE. 0) THEN
            it = loadbg(ibg,1)
            it = waitbg(ibg)
        ENDIF

This block (inquiry-block) is inserted before first DO statement of INDEPENDENT loop nest.