source: LMDZ5/branches/testing/libf/phylmd/rrtm/tpm_distr.F90 @ 1999

Last change on this file since 1999 was 1999, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes r1920:1997 into testing branch

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 7.1 KB
Line 
1MODULE TPM_DISTR
2
3USE PARKIND1  ,ONLY : JPIM     ,JPRB
4
5IMPLICIT NONE
6
7SAVE
8
9!*    Variables describing distributed memory parallelization
10
11INTEGER(KIND=JPIM) :: NPROC     ! Number of processors (NPRGPNS*NPRGPEW)
12INTEGER(KIND=JPIM) :: NPRGPNS   ! No. of sets in N-S direction (grid-point space)
13INTEGER(KIND=JPIM) :: NPRGPEW   ! No. of sets in E-W direction (grid-point space)
14INTEGER(KIND=JPIM) :: NPRTRW    ! No. of sets in wave direction (spectral space)
15INTEGER(KIND=JPIM) :: NPRTRV    ! NPROC/NPRTRW
16INTEGER(KIND=JPIM) :: NPRTRNS   ! No. of sets in N-S direction (Fourier space)
17                                ! (always equal to NPRTRW)
18LOGICAL            :: LEQ_REGIONS ! TRUE - Use new eq_regions partitioning
19                                  ! FALSE- Use old NPRGPNS x NPRGPEW partitioning
20INTEGER(KIND=JPIM) :: MYPROC    ! My processor number
21INTEGER(KIND=JPIM) :: MYSETW    ! My set number in wave direction (spectral space)
22INTEGER(KIND=JPIM) :: MYSETV    ! My set number in field direction(S.S and F.S)
23INTEGER(KIND=JPIM) :: NCOMBFLEN ! Size of communication buffer
24
25INTEGER(KIND=JPIM) :: MTAGLETR   ! Tag
26INTEGER(KIND=JPIM) :: MTAGML     ! Tag
27INTEGER(KIND=JPIM) :: MTAGLG     ! Tag
28INTEGER(KIND=JPIM) :: MTAGGL     ! Tag
29INTEGER(KIND=JPIM) :: MTAGPART   ! Tag
30INTEGER(KIND=JPIM) :: MTAGDISTSP ! Tag
31INTEGER(KIND=JPIM) :: MTAGLM     ! Tag
32INTEGER(KIND=JPIM) :: MTAGDISTGP ! Tag
33 
34INTEGER(KIND=JPIM) ,ALLOCATABLE :: NPRCIDS(:) ! Array containing the process ids
35
36TYPE DISTR_TYPE
37LOGICAL   :: LSPLIT             ! TRUE - latitudes are shared between a-sets
38INTEGER(KIND=JPIM) :: NAPSETS   ! Number of apple sets at the poles. Default is zero.
39
40! SPECTRAL SPACE
41
42INTEGER(KIND=JPIM) :: NUMP      ! No. of spectral waves handled by this processor
43INTEGER(KIND=JPIM) :: NSPEC     ! No. of complex spectral coefficients (on this PE)
44INTEGER(KIND=JPIM) :: NSPEC2    ! 2*NSPEC
45INTEGER(KIND=JPIM) :: NSPEC2MX  ! maximun NSPEC2 among all PEs
46INTEGER(KIND=JPIM) :: NTPEC2
47INTEGER(KIND=JPIM) :: NUMTP
48
49
50
51INTEGER(KIND=JPIM) :: NSPOLEGL  ! No. of legendre polynomials on this PE
52INTEGER(KIND=JPIM) :: NLEI3D    ! (NLEI3-1)/NPRTRW+1
53
54INTEGER(KIND=JPIM) ,POINTER :: MYMS(:)    ! Wave numbers handled by this PE
55INTEGER(KIND=JPIM) ,POINTER :: NUMPP(:)   ! No. of wave numbers each wave set is
56                                 ! responsible for
57INTEGER(KIND=JPIM) ,POINTER :: NPOSSP(:)  ! Not needed in transform?
58INTEGER(KIND=JPIM) ,POINTER :: NPROCM(:)  ! Process that does the calc. for certain
59                                 ! wavenumber M
60INTEGER(KIND=JPIM) ,POINTER :: NDIM0G(:)  ! Defines partitioning of global spectral
61                                 ! fields among PEs
62
63INTEGER(KIND=JPIM) ,POINTER :: NASM0(:)  ! Address in a spectral array of (m, n=m)
64INTEGER(KIND=JPIM) ,POINTER :: NATM0(:)  ! Same as NASM0 but for NTMAX
65INTEGER(KIND=JPIM) ,POINTER :: NALLMS(:) ! Wave numbers for all a-set concatenated
66                                ! together to give all wave numbers in a-set
67                                ! order. Used when global spectral norms
68                                ! have to be gathered.
69INTEGER(KIND=JPIM) ,POINTER :: NPTRMS(:) ! Pointer to the first wave number of a given
70                                ! a-set in nallms array.
71
72
73! Legendre polynomials
74
75INTEGER(KIND=JPIM) ,POINTER :: NLATLS(:) ! First latitude for which each a-set calcul.
76INTEGER(KIND=JPIM) ,POINTER :: NLATLE(:) ! Last latitude for which each a-set calcul.
77
78INTEGER(KIND=JPIM) ,POINTER :: NPMT(:) ! Adress for legendre polynomial for
79                              ! given M (NTMAX)
80INTEGER(KIND=JPIM) ,POINTER :: NPMS(:) ! Adress for legendre polynomial for
81                              ! given M (NSMAX)
82INTEGER(KIND=JPIM) ,POINTER :: NPMG(:) ! Global version of NPMS
83
84! FOURIER SPACE
85
86INTEGER(KIND=JPIM) :: NDGL_FS ! Number of rows of latitudes for which this process is
87                     ! performing Fourier Space calculations
88
89INTEGER(KIND=JPIM) ,POINTER  :: NSTAGTF(:) ! Offset for specific latitude in
90                                  ! Fourier/gridpoint buffer
91INTEGER(KIND=JPIM) :: NLENGTF ! Second dimension of Fourier/gridpoint buffer
92                     ! (sum of (NLOEN+3) over local latitudes)
93
94INTEGER(KIND=JPIM) ,POINTER :: NULTPP(:) ! No of lats. for each wave_set  (F.S)
95INTEGER(KIND=JPIM) ,POINTER :: NPROCL(:) ! Process responsible for each lat. (F.S)
96INTEGER(KIND=JPIM) ,POINTER :: NPTRLS(:) ! Pointer to first lat. (F.S)
97
98INTEGER(KIND=JPIM) ,POINTER :: NSTAGT0B(:) ! Start adresses for segments within buffer
99                                  ! (according to processors to whom data
100                                  ! is going to be sent)
101INTEGER(KIND=JPIM) ,POINTER :: NSTAGT1B(:)
102INTEGER(KIND=JPIM) ,POINTER :: NPNTGTB0(:,:)
103INTEGER(KIND=JPIM) ,POINTER :: NPNTGTB1(:,:)
104INTEGER(KIND=JPIM) ,POINTER :: NLTSFTB(:) 
105
106INTEGER(KIND=JPIM) ,POINTER :: NLTSGTB(:)
107INTEGER(KIND=JPIM) ,POINTER :: MSTABF(:)
108
109INTEGER(KIND=JPIM) :: NLENGT0B
110INTEGER(KIND=JPIM) :: NLENGT1B
111
112! GRIDPOINT SPACE
113
114INTEGER(KIND=JPIM) :: NDGL_GP ! D%NLSTLAT(MY_REGION_NS)-D%NFRSTLOFF
115INTEGER(KIND=JPIM) ,POINTER :: NFRSTLAT(:) ! First lat of each a-set
116INTEGER(KIND=JPIM) ,POINTER :: NLSTLAT(:)  ! Last lat of each a-set
117INTEGER(KIND=JPIM) :: NFRSTLOFF ! Offset for first lat of own a-set
118                       ! i.e. NFRSTLOFF=NFRSTLAT(MYSETA)-1
119INTEGER(KIND=JPIM) ,POINTER :: NPTRLAT(:) ! Pointer to start of latitude
120INTEGER(KIND=JPIM) ,POINTER :: NPTRFRSTLAT(:) ! Pointer to the first latitude of each
121                                     ! a-set in NSTA and NONL arrays
122INTEGER(KIND=JPIM) ,POINTER :: NPTRLSTLAT(:) ! Pointer to the last latitude of each
123                                    ! a-set in NSTA and NONL arrays
124INTEGER(KIND=JPIM) :: NPTRFLOFF ! Offset for pointer to the first latitude of own a-set
125                       ! NSTA and NONL arrays, i.e. NPTRFRSTLAT(MYSETA)-1
126LOGICAL   ,POINTER :: LSPLITLAT(:) ! True if latitude is split over 2 a-sets
127
128!  NSTA(R%NDGL+NPRGPNS-1,NPRGPEW) :  Position of first grid column
129!             for the latitudes on a processor. The information is
130!             available for all processors. The b-sets are distinguished
131!             by the last dimension of NSTA(). The latitude band for
132!             each a-set is addressed by NPTRFRSTLAT(JASET),
133!             NPTRLSTLAT(JASET), and NPTRFLOFF=NPTRFRSTLAT(MYSETA) on
134!             this processors a-set. Each split latitude has two entries
135!             in NSTA(,:) which necessitates the rather complex
136!             addressing of NSTA(,:) and the overdimensioning of NSTA by
137!             NPRGPNS.
138!  NONL(R%NDGL+NPRGPNS-1,NPRGPEW)  :  Number of grid columns for
139!             the latitudes on a processor. Similar to NSTA() in data
140!             structure.
141INTEGER(KIND=JPIM) ,POINTER :: NSTA(:,:)
142INTEGER(KIND=JPIM) ,POINTER :: NONL(:,:)
143
144INTEGER(KIND=JPIM) :: NGPTOT   ! Total number of grid columns on this PE
145INTEGER(KIND=JPIM) :: NGPTOTG  ! Total number of grid columns on the Globe
146INTEGER(KIND=JPIM) :: NGPTOTMX ! Maximum number of grid columns on any of the PEs
147INTEGER(KIND=JPIM) ,POINTER :: NGPTOTL(:,:) ! Number of grid columns on each PE.
148
149END TYPE DISTR_TYPE
150
151TYPE(DISTR_TYPE),ALLOCATABLE,TARGET :: DISTR_RESOL(:)
152TYPE(DISTR_TYPE),POINTER     :: D
153
154END MODULE TPM_DISTR
155
156
157
158
159
160
161
Note: See TracBrowser for help on using the repository browser.