1 |
C $Header: /u/gcmpack/MITgcm/pkg/oasis/oasis_partition_def.F,v 1.0 2005/07/18 23:05:09 gianamria sannino Exp $ |
2 |
C $Name: $ |
3 |
cgm( |
4 |
#include "CPP_EEOPTIONS.h" |
5 |
cgm) |
6 |
cc#include "OASIS_OPTIONS.h" |
7 |
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
8 |
CBOP 0 |
9 |
C !ROUTINE: OASIS_PARTITION_DEF |
10 |
|
11 |
C !INTERFACE: |
12 |
SUBROUTINE OASIS_PARTITION_DEF |
13 |
|
14 |
|
15 |
C !DESCRIPTION: |
16 |
C Routine to ??? da inserire |
17 |
|
18 |
C !USES: |
19 |
|
20 |
c USE mod_kinds_model |
21 |
USE mod_prism_proto |
22 |
USE mod_prism_def_partition_proto |
23 |
c USE mod_prism_put_proto |
24 |
c USE mod_prism_get_proto |
25 |
c USE mod_prism_grids_writing |
26 |
|
27 |
IMPLICIT NONE |
28 |
c |
29 |
#include "SIZE.h" |
30 |
#include "EEPARAMS.h" |
31 |
#include "EESUPPORT.h" |
32 |
#include "PARAMS.h" |
33 |
#include "GRID.h" |
34 |
cgm( |
35 |
#include "OASIS.h" |
36 |
cc#include "OASIS_PARAMS.h" |
37 |
cgm) |
38 |
|
39 |
C !LOCAL VARIABLES: |
40 |
c INTEGER myThid |
41 |
INTEGER, DIMENSION(:), ALLOCATABLE :: il_paral ! Decomposition for each proc |
42 |
INTEGER :: ig_nsegments ! Number of segments of process decomposition |
43 |
INTEGER :: ig_parsize ! Size of array decomposition |
44 |
INTEGER :: ib |
45 |
INTEGER :: iOff, jOff, myOffset |
46 |
CHARACTER(len=80), PARAMETER :: cdec='BOX' |
47 |
|
48 |
! |
49 |
! Refer to oasis/psmile/prism/modules/mod_prism_proto.F90 for integer value |
50 |
! of clim_xxxx parameters |
51 |
! |
52 |
IF ( .NOT. ll_comparal .AND. mpiMyId.eq.0) THEN |
53 |
! Monoprocess mitgcm, or parallel mitgcm with only master process involved |
54 |
! in coupling: the entire field will be exchanged by the process. |
55 |
WRITE(il_mparout,*)'A monoprocess mitgm, or a parallel' |
56 |
WRITE(il_mparout,*)'mitgcm with only the master process' |
57 |
WRITE(il_mparout,*)'involved in the coupling is running' |
58 |
WRITE(il_mparout,*)'' |
59 |
ig_nsegments = 1 |
60 |
ig_parsize = 3 |
61 |
ALLOCATE(il_paral(ig_parsize)) |
62 |
! |
63 |
il_paral ( clim_strategy ) = clim_serial |
64 |
il_paral ( clim_offset ) = 0 |
65 |
il_paral ( clim_length ) = Nx*Ny |
66 |
il_length = Nx*Ny |
67 |
! |
68 |
CALL prism_def_partition_proto (il_part_id, il_paral, ierror) |
69 |
DEALLOCATE(il_paral) |
70 |
! |
71 |
ELSE |
72 |
! Parallel atm with all process involved in the coupling |
73 |
WRITE(il_mparout,*)'A parallel mitgcm with all processes' |
74 |
WRITE(il_mparout,*)'involved in the coupling is running' |
75 |
WRITE(il_mparout,*)'' |
76 |
|
77 |
! |
78 |
IF (cdec .EQ. 'APPLE') THEN |
79 |
! Each process is responsible for a part of field defined by |
80 |
! the number of grid points and the offset of the first point |
81 |
! |
82 |
WRITE (il_mparout,*) 'APPLE partitioning' |
83 |
WRITE (il_mparout,*) '' |
84 |
ig_nsegments = 1 |
85 |
ig_parsize = 3 |
86 |
ALLOCATE(il_paral(ig_parsize)) |
87 |
! |
88 |
IF (mpiMyId .LT. (il_nbcplproc-1)) THEN |
89 |
il_paral ( clim_strategy ) = clim_apple |
90 |
il_paral ( clim_length ) = Nx*Ny/il_nbcplproc |
91 |
il_paral ( clim_offset ) = mpiMyId*(Nx*Ny/il_nbcplproc) |
92 |
ELSE |
93 |
il_paral ( clim_strategy ) = clim_apple |
94 |
il_paral ( clim_length ) = |
95 |
&Nx*Ny-(mpiMyId*(Nx*Ny/il_nbcplproc)) |
96 |
il_paral ( clim_offset ) = |
97 |
&mpiMyId*(Nx*Ny/il_nbcplproc) |
98 |
ENDIF |
99 |
il_length = il_paral(clim_length) |
100 |
! |
101 |
CALL prism_def_partition_proto (il_part_id, il_paral, ierror) |
102 |
DEALLOCATE(il_paral) |
103 |
! |
104 |
ELSE IF (cdec .EQ. 'BOX') THEN |
105 |
! Each process is responsible for a rectangular box (here nPx*nPy |
106 |
! processors treat sNx*sNy points |
107 |
! |
108 |
WRITE (il_mparout,*) 'BOX partitioning' |
109 |
WRITE (il_mparout,*) '' |
110 |
ig_nsegments = sNy |
111 |
ig_parsize = 5 |
112 |
ALLOCATE(il_paral(ig_parsize)) |
113 |
c |
114 |
c |
115 |
iOff = mpiMyId / nPy |
116 |
jOff = mod (mpiMyId,nPy) |
117 |
myOffset = (jOff * Nx * sNy) + (iOff * sNx) |
118 |
c------------------------------------------------------- |
119 |
WRITE(il_mparout,*)'ig_parsize',ig_parsize |
120 |
! |
121 |
|
122 |
il_paral ( clim_strategy ) = clim_box |
123 |
il_paral ( clim_LdX ) = Nx |
124 |
il_paral ( clim_offset ) = myOffset |
125 |
il_paral ( clim_sizeX ) = sNx |
126 |
il_paral ( clim_sizeY ) = sNy |
127 |
|
128 |
|
129 |
il_length = il_paral(clim_sizeX) * il_paral(clim_sizeY) |
130 |
! |
131 |
CALL prism_def_partition_proto (il_part_id, il_paral, ierror) |
132 |
DEALLOCATE(il_paral) |
133 |
! |
134 |
ELSE |
135 |
WRITE (il_mparout,*) 'incorrect decomposition ' |
136 |
ENDIF |
137 |
ENDIF |
138 |
|
139 |
WRITE (il_mparout,*) ' End of partition def' |
140 |
WRITE (il_mparout,*) ' --------------------' |
141 |
WRITE (il_mparout,*) '' |
142 |
|
143 |
return |
144 |
end |