The domain decomposition in Parallel PHOENICS is usually handled automatically. The directions chosen will depend on the grid size, solver settings and number of cells used. The decomposition will be made in such a way as to minimise the data exchange between processors.
Each subdomain is assigned to a different parallel processor, and each subdomain is enlarged at each adjoining end by the addition of two columns, rows or slabs (planes) of cells. These additional 'overlap' or 'halo' cells are used to store field values from the adjacent subdomains so as to facilitate data exchange between subdomains during the parallel computation.
Loops in which indices are restricted to the current cell and its' immediate neighbours will work without any change.
The ground coding of loops will require special attention if:
The reason is that Parallel PHOENICS interprets each loop as referring to the current subdomain, including 'halo' cells. Such coding is likely to occur in Group 19 or Group 11.
This is an example of a GROUND file which includes coding in Group 19 Section 6 which sums up the gas volume over the whole field within the main IZ loop of PHOENICS. Ground coding in other groups and sections is not shown because it did not require modification for use with Parallel PHOENICS.
Head of GROUND file
SUBROUTINE GROUND
INCLUDE '/phoenics/d_includ/farray'
INCLUDE '/phoenics/d_includ/satear'
INCLUDE '/phoenics/d_includ/grdloc'
INCLUDE '/phoenics/d_includ/satgrd'
INCLUDE '/phoenics/d_includ/grdear'
INCLUDE '/phoenics/d_includ/grdbfc'
INCLUDE '/phoenics/d_includ/parear'
LOGICAL INPARDOM
Group 19 Section 6 Coding
Parallel-specific code is in red.
196 CONTINUE C * ------------------- SECTION 6 ---- Finish of iz slab. C C... Calculate overall 'free' volume L0VL=L0F(VOL) IF(IZ.EQ.1) VOLSUM=0. ! Initialise on first Z slab DO IX=1,NX ! loop over slab DO IY=1,NY I=(IX-1)*NY+IY IF(.NOT.SLD(I)) THEN ! skip any solid cells IF(NPROC.GT.1) THEN IF(INPARDOM(IX,IY,IZ)) VOLSUM=VOLSUM+F(L0VL+I) ELSE VOLSUM=VOLSUM+F(L0VL+I) ENDIF ENDIF ENDDO ENDDO IF(NPROC.GT.1) CALL GLSUM(VOLSUM) C IF(IZ.EQ.NZ.AND.MYID.EQ.0) THEN ! print at last slab from master CALL WRIT40('The total free volume in the domain is (m^3)') CALL WRIT1R('VOLUME ',VOLSUM) ENDIF RETURN
The foregoing coding includes the use of various parallel utilities such as
This example shows how to sum up the sources, in this case of mass, over all patches to find the total mass inflow.
The problem lies in that on each processor the sequence of patches may be different, as not all patches will exist on all processors. However, when summing across processors the loop indices must be in step, otherwise the summation will fail and the run will stall.
In the example code, the following variables and routines are used:
Head of GROUND file
SUBROUTINE GROUND INCLUDE '/phoenics/d_includ/farray' INCLUDE '/phoeclos/d_includ/d_earth/parvar' INCLUDE '/phoenics/d_includ/satear' INCLUDE '/phoenics/d_includ/grdloc' INCLUDE '/phoenics/d_includ/satgrd' INCLUDE '/phoenics/d_includ/grdear' INCLUDE '/phoenics/d_includ/grdbfc' INCLUDE '/phoenics/d_includ/parear'Group 19 Section 7 Coding
Parallel-specific code is in red.
197 CONTINUE C * ------------------- SECTION 7 ---- Finish of sweep. C... Calculate overall mass-inflow IF(NPROC.GT.1) THEN ILIM=GD_NUMPAT ELSE ILIM=NUMPAT ENDIF FMASIN=0.0 DO I=1,ILIM ! loop over global or local patches IF(NPROC.GT.1) THEN IR=GD_INDPAT(I,1) ! get local index IR for global patch no I ELSE IR=I ! in sequential, local and global are the same! ENDIF IF(NPROC.GT.1) THEN CALL PGETCV(I,R1,GCO,GVAL) ! get GO and VAL for Mass ELSE CALL GETCOV(NAMPAT(IR),R1,GCO,GVAL) ! get GO and VAL for Mass ENDIF IF(QEQ(GVAL,-999.)) CYCLE ! no COVAL for mass so skip to next patch IF(IR.LT.0) THEN SORCE=0.0 ! patch does not exist on this processor ELSE CALL GETSO(IR,R1,SORCE) ! get mass source for local patch IR ENDIF IF(NPROC.GT.1) CALL GLSUM(SORCE) ! sum over all processors IF(SORCE.GT.0.0) THEN ! mass inflow FMASIN=FMASIN+SORCE ! sum mass ENDIF ENDDO IF(MYID.EQ.0) THEN ! print on master CALL WRIT40('The total mass inflow is (kg/s)') CALL WRIT1R('MASSIN ',FMASIN) ENDIF
A selection of the utility subroutines employed in the PHOENICS Parallel Interface is listed below.
SUBROUTINE LGSUM_AND(VAR) - It gives the Global AND of LOGICAL variable VAR among Working Processors.
SUBROUTINE LGSUM_OR(VAR) - It gives the Global OR of LOGICAL variable VAR among Working Processors.
SUBROUTINE DGSUM2(VAR1,VAR2) - It calculates the Global Sum Of VAR1 & VAR2 among Working Processors. Data type: REAL*8.
SUBROUTINE DGSUM3(VAR1,VAR2,VAR3) - It calculates the Global Sum Of VAR1, VAR2 & VAR3 among Working Processors. Data type: REAL*8.
SUBROUTINE DGSUMN(DATA, N) - It calculates the Global Sum Of n REAL*8 values across Processors. Data type: REAL*8. Max n is 256 !!
SUBROUTINE RGSUMN(DATA, N) - It calculates the Global Sum Of n REAL*4 values across all Working Processors. Max n is 256 !!
SUBROUTINE GLSUM(VAR) - It calculates the Global Sum Of VAR among Working Processors. Data type REAL*4.
SUBROUTINE GLSUM2(VAR1,VAR2) - It calculates The Global Sum Of VAR1 & VAR2 among Working Processors. Data type: REAL*4.
SUBROUTINE GLSUM4(VAR1,VAR2,VAR3,VAR4) - It calculates The Global Sum Of VAR1 & VAR2 & VAR3 & VAR4 among Working Processors. Data type: REAL*4.
SUBROUTINE GLNXYZ(NIX,NIY,NIZ) - It returns the global size of the whole-domain grid when each domain is of size NIX, NIY and NIZ.
LOGICAL FUNCTION INPARDOM(IX,IY,IZ) - returns .FALSE. if the cell (IX,IY,IZ) is a 'halo' cell, and .TRUE. otherwise.
PGETCV(iglob,ivar,coef,val) - this returns the COefficient and VALue for variable ivar for global patch iglob. If the coefficient is returned as -999.0, no COVAL exists for this variable at this patch.
The following routines are useful for distributing data from the master processor to all the slave processors, often after having been read at the start of the run.
SUBROUTINE RTFSII(data) - Processor 0 broadcasts INTEGER 'data' to the other processors.
SUBROUTINE RTFAII(data,size) - Processor 0 broadcasts INTEGER 'data', size 'size' to the other processors.
SUBROUTINE RTFARI(data,size) - Processor 0 broadcasts REAL 'data', size 'size' to the other processors.
SUBROUTINE RTFALI(data,size) - Processor 0 broadcasts Logical 'data', size 'size' to the other processors.
SUBROUTINE RTFACI(data,size) - Processor 0 broadcasts character 'data', size 'size' to the other processors.
SUBROUTINE RTVACI(data,size,nchar) - Processor 0 broadcasts an array of CHARACTER*nchar 'data', size 'size' to the other processors.
For detailed advice on how to ensure specific GROUND routines are compatible with parallel operation, please contact CHAM User Support.