source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_parallel/mod_orchidee_para_var.F90 @ 8367

Last change on this file since 8367 was 6290, checked in by josefine.ghattas, 5 years ago

As done in [6289]: Moved protection if is_omp_root inside subroutine grid_allocate_glo. This is now done only on the allocation part in the subroutine, the first part must be done by all threads. This is needed to run in debug mode at Jean-Zay (intel 2019).

  • Property svn:keywords set to Date Revision HeadURL
File size: 11.3 KB
Line 
1! ================================================================================================================================
2!  MODULE       : mod_orchidee_para_var
3!
4!  CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6!  LICENCE      : IPSL (2006)
7!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF   This module contains public variables for parallelization and domain decomposition.
10!!
11!!\n DESCRIPTION:  This module contains public variables for parallelization and domain decomposition.
12!!                 The variables in here can be used by USE mod_orchidee_para. Only at some specific cases it it needed to
13!!                 use this module directly to avoid depencendy problems.
14!!
15!! RECENT CHANGE(S): None
16!!
17!! REFERENCE(S) : None
18!!
19!! SVN          :
20!! $HeadURL$
21!! $Date$
22!! $Revision$
23!! \n
24!_ ================================================================================================================================
25
26MODULE mod_orchidee_para_var
27
28  USE defprec
29
30  !
31  ! 1. Variables related to the MPI parallelization and the MPI horizontal domain decompostion.
32  !    These variables were previously declared in mod_orchidee_mpi_data
33  !
34
35  ! Type gricells mpi information
36  TYPE gridcells_info
37      ! MPI
38      INTEGER(i_std) :: nb_mpi_loc ! Number of gridcells in this processor
39      INTEGER(i_std) :: nb_mpi_global ! Global number of Gridcells
40      INTEGER(i_std), ALLOCATABLE :: nb_mpi_para(:) ! Number of gridcells in each proc
41      INTEGER(i_std), ALLOCATABLE :: begin_mpi_para(:) ! Starting gridcell in each proc
42      INTEGER(i_std), ALLOCATABLE :: end_mpi_para(:) ! Ending gridcell in each proc
43      ! OMP
44      INTEGER(i_std) :: nb_omp ! Number of gridcells in the current OpenMP thread
45      INTEGER(i_std) :: begin_omp ! Startging gridcell in each OpenMP thread
46  END TYPE gridcells_info
47
48  ! Unit for output messages
49  INTEGER(i_std), SAVE :: numout = 6
50  !$OMP THREADPRIVATE(numout)
51
52  INTEGER,SAVE :: mpi_size                                            !! Number of parallel processes
53  INTEGER,SAVE :: mpi_rank                                            !! my rank num
54  INTEGER,SAVE :: mpi_rank_root                                       !! rank of MPI root
55  LOGICAL,SAVE :: is_mpi_root                                         !! Only MPI root proc is true
56  LOGICAL,SAVE :: is_ok_mpi                                           
57
58  INTEGER(i_std),SAVE              :: nbp_mpi                         !! number of local continental points in each mpi group
59  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: nbp_mpi_para
60  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: nbp_mpi_para_begin
61  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: nbp_mpi_para_end 
62  TYPE(gridcells_info), SAVE :: nbp_para_info  ! Continental gridcells info
63  !$OMP THREADPRIVATE(nbp_para_info)
64
65  INTEGER,SAVE :: nbp_mpi_begin
66  INTEGER,SAVE :: nbp_mpi_end
67
68  ! i x j 2D points (not land points) index
69  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: ij_para_nb           ! Number of 2D points for each mpi_rank block
70  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: ij_para_begin        ! First 2D point for each mpi_rank block
71  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: ij_para_end          ! Last 2D point for each mpi_rank block
72  TYPE(gridcells_info), SAVE :: ij_para_info  ! 2D gridcells info
73  !$OMP THREADPRIVATE(ij_para_info)
74
75  ! i 2D index
76  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: ii_para_begin        ! First i index of 2D point for each mpi_rank block
77  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: ii_para_end          ! Last i index of 2D point for each mpi_rank block
78  ! j 2D index
79  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: jj_para_nb           ! Number of complete j lines for each mpi_rank block
80  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: jj_para_begin        ! First j index of 2D point for each mpi_rank block
81  INTEGER,SAVE,ALLOCATABLE,DIMENSION(:) :: jj_para_end          ! Last j index of 2D point for each mpi_rank block
82
83  INTEGER,SAVE :: ii_begin
84  INTEGER,SAVE :: ii_end
85  INTEGER,SAVE :: jj_begin
86  INTEGER,SAVE :: jj_end
87  INTEGER,SAVE :: jj_nb
88  INTEGER,SAVE :: ij_begin
89  INTEGER,SAVE :: ij_end
90  INTEGER,SAVE :: ij_nb
91
92  INTEGER,SAVE :: MPI_COMM_ORCH
93  INTEGER,SAVE :: MPI_REAL_ORCH
94  INTEGER,SAVE :: MPI_INT_ORCH
95  LOGICAL, SAVE :: cpl_lmdz
96
97  INTEGER,SAVE,ALLOCATABLE :: kindex_mpi (:)
98  INTEGER,SAVE             :: offset_mpi
99
100
101  !
102  ! 2. Variables related to the OpenMP paralelization and OpenMP horizontal domain decomposition
103  !    These variables were previously declared in mod_orchidee_omp_data
104  !
105
106  ! Check all OpenMP transferts in ORCHIDEE : use this flag to debug synchronism with OpenMP
107  LOGICAL, PARAMETER :: check_all_transfert=.FALSE.
108
109
110  INTEGER(i_std),SAVE :: omp_size
111  INTEGER(i_std),SAVE :: omp_rank
112  LOGICAL,SAVE :: is_omp_root                  !! Only OpenMP master thread is true
113  LOGICAL,SAVE :: is_ok_omp
114  !$OMP  THREADPRIVATE(omp_rank,is_omp_root)
115
116  INTEGER(i_std),SAVE,DIMENSION(:),ALLOCATABLE :: nbp_omp_para_nb
117  INTEGER(i_std),SAVE,DIMENSION(:),ALLOCATABLE :: nbp_omp_para_begin
118  INTEGER(i_std),SAVE,DIMENSION(:),ALLOCATABLE :: nbp_omp_para_end   
119
120  INTEGER(i_std),SAVE,DIMENSION(:),ALLOCATABLE :: ij_omp_para_nb
121  INTEGER(i_std),SAVE,DIMENSION(:),ALLOCATABLE :: ij_omp_para_begin
122  INTEGER(i_std),SAVE,DIMENSION(:),ALLOCATABLE :: ij_omp_para_end   
123
124  INTEGER(i_std),SAVE :: nbp_omp
125  INTEGER(i_std),SAVE :: nbp_omp_begin
126  INTEGER(i_std),SAVE :: nbp_omp_end
127  INTEGER(i_std),SAVE :: offset_omp
128
129  INTEGER(i_std),SAVE :: ij_omp_nb
130  INTEGER(i_std),SAVE :: ij_omp_begin
131  INTEGER(i_std),SAVE :: ij_omp_end
132  !$OMP  THREADPRIVATE(nbp_omp,nbp_omp_begin,nbp_omp_end,offset_omp)
133  !$OMP  THREADPRIVATE(ij_omp_nb,ij_omp_begin,ij_omp_end)
134
135  ! Flag for each OMP process for ORCHIDEE to verify synchronization if function Synchro_Omp is used
136  LOGICAL,SAVE,ALLOCATABLE :: proc_synchro_omp(:)
137
138  INTEGER, SAVE :: numout_omp = -1
139  !$OMP  THREADPRIVATE(numout_omp)
140
141  ! For debugging OpenMP processes : id of OMP function for each task.
142  ! If one task is not in the same function, we can see it.
143  INTEGER(i_std),SAVE,ALLOCATABLE,DIMENSION(:) :: omp_function
144  ! It is not SHARED.
145  ! List of values :
146  CHARACTER(LEN=28), PARAMETER :: omp_fct_name(-1:72) = (/ &
147       "Initialization              ", &
148       "Synchro_Omp                 ", &
149       "check_buffer_i              ", &
150       "check_buffer_r              ", &
151       "check_buffer_l              ", &
152       "bcast_omp_c                 ", &
153       "bcast_omp_i                 ", &
154       "bcast_omp_i1                ", &
155       "bcast_omp_i2                ", &
156       "bcast_omp_i3                ", &
157       "bcast_omp_i4                ", &
158       "bcast_omp_r                 ", &
159       "bcast_omp_r1                ", &
160       "bcast_omp_r2                ", &
161       "bcast_omp_r3                ", &
162       "bcast_omp_r4                ", &
163       "bcast_omp_l                 ", &
164       "bcast_omp_l1                ", &
165       "bcast_omp_l2                ", &
166       "bcast_omp_l3                ", &
167       "bcast_omp_l4                ", &
168       "scatter_omp_i               ", &
169       "scatter_omp_i1              ", &
170       "scatter_omp_i2              ", &
171       "scatter_omp_i3              ", &
172       "scatter_omp_r               ", &
173       "scatter_omp_r1              ", &
174       "scatter_omp_r2              ", &
175       "scatter_omp_r3              ", &
176       "scatter_omp_l               ", &
177       "scatter_omp_l1              ", &
178       "scatter_omp_l2              ", &
179       "scatter_omp_l3              ", &
180       "gather_omp_i0               ", &
181       "gather_omp_i                ", &
182       "gather_omp_i1               ", &
183       "gather_omp_i2               ", &
184       "gather_omp_i3               ", &
185       "gather_omp_r0               ", &
186       "gather_omp_r                ", &
187       "gather_omp_r1               ", &
188       "gather_omp_r2               ", &
189       "gather_omp_r3               ", &
190       "gather_omp_l0               ", &
191       "gather_omp_l                ", &
192       "gather_omp_l1               ", &
193       "gather_omp_l2               ", &
194       "gather_omp_l3               ", &
195       "reduce_sum_omp_i            ", &
196       "reduce_sum_omp_i1           ", &
197       "reduce_sum_omp_i2           ", &
198       "reduce_sum_omp_i3           ", &
199       "reduce_sum_omp_i4           ", &
200       "reduce_sum_omp_r            ", &
201       "reduce_sum_omp_r1           ", &
202       "reduce_sum_omp_r2           ", &
203       "reduce_sum_omp_r3           ", &
204       "reduce_sum_omp_r4           ", &
205       "orch_bcast_omp_cgen         ", &
206       "orch_bcast_omp_igen         ", &
207       "orch_bcast_omp_rgen         ", &
208       "orch_bcast_omp_lgen         ", &
209       "orch_scatter_omp_igen       ", &
210       "orch_scatter_omp_rgen       ", &
211       "orch_scatter_omp_lgen       ", &
212       "orch_gather_omp_simple_igen ", &
213       "orch_gather_omp_igen        ", &
214       "orch_gather_omp_simple_rgen ", &
215       "orch_gather_omp_rgen        ", &
216       "orch_gather_omp_simple_lgen ", &
217       "orch_gather_omp_lgen        ", &
218       "orch_reduce_sum_omp_igen    ", &
219       "orch_reduce_sum_omp_rgen    ", &
220       "check_buffer_c              " /)
221
222  ! Previous value for own omp_function
223  INTEGER, SAVE :: omp_previous
224  !$OMP  THREADPRIVATE(omp_previous)
225
226  !
227  !! 3. Variables previously declared in mod_orchide_para
228  !
229
230  INTEGER,SAVE :: nbp_loc                                             !! number of local continental points
231  !$OMP THREADPRIVATE(nbp_loc)
232  INTEGER,SAVE :: offset
233  !$OMP THREADPRIVATE(offset)
234
235  LOGICAL,SAVE :: is_root_prc = .FALSE.                               !! Only root proc for MPI and OpenMP is true
236  !$OMP THREADPRIVATE(is_root_prc)
237  !
238  !! Global grid arrays used by stomate and sechiba and available on each processor
239  !! They need to be broadcasted after initilisation of the parallelisation
240  !-
241  ! Dimensions
242  INTEGER(i_std),SAVE              :: iim_g                           !! Dimension of global fields for longitude
243  INTEGER(i_std),SAVE              :: jjm_g                           !! Dimension of global fields for latitude
244  INTEGER(i_std),SAVE              :: nbp_glo                         !! number of global continental points
245  ! Fields
246  !! index of land points on the 2D map
247  INTEGER(i_std),ALLOCATABLE,DIMENSION(:),SAVE   :: index_g
248  !-
249  !! indices of the 4 neighbours of each grid point (1=N, 2=E, 3=S, 4=W)
250  INTEGER(i_std),ALLOCATABLE,DIMENSION(:,:),SAVE :: neighbours_g
251  !-
252  ! Heading of the direction out of the grid box either through the vertex
253  ! of the mid-segment of the polygon.
254  !
255  REAL(r_std), ALLOCATABLE, DIMENSION(:,:), SAVE      :: headings_g
256  !
257  ! Length of segments of the polygon.
258  !
259  REAL(r_std), ALLOCATABLE, DIMENSION(:,:), SAVE      :: seglength_g
260  !
261  ! Area of the grid box
262  !
263  REAL(r_std), ALLOCATABLE, DIMENSION(:), SAVE        :: area_g
264  !
265  ! Coordinats of the vertices
266  !
267  REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:), SAVE    :: corners_g
268  !
269  ! TEMPORARY !!!!!
270  !
271  !! resolution at each grid point in m (1=E-W, 2=N-S)
272  REAL(r_std),ALLOCATABLE,DIMENSION(:,:),SAVE    :: resolution_g 
273  !-
274  !! Geographical coordinates
275  REAL(r_std),ALLOCATABLE,DIMENSION(:,:),SAVE    :: lalo_g
276  ! Global grid, for all process
277  REAL(r_std), ALLOCATABLE, DIMENSION(:,:), SAVE     :: lon_g, lat_g
278  !-
279  !! Fraction of continents
280  REAL(r_std),ALLOCATABLE,DIMENSION(:),SAVE      :: contfrac_g 
281  !
282END MODULE mod_orchidee_para_var
Note: See TracBrowser for help on using the repository browser.