GCC Code Coverage Report
Directory: ./ Exec Total Coverage
File: phylmd/rrtm/tpm_distr.F90 Lines: 0 1 0.0 %
Date: 2023-06-30 12:56:34 Branches: 0 0 - %

Line Branch Exec Source
1
MODULE TPM_DISTR
2
3
USE PARKIND1  ,ONLY : JPIM     ,JPRB
4
5
IMPLICIT NONE
6
7
SAVE
8
9
!*    Variables describing distributed memory parallelization
10
11
INTEGER(KIND=JPIM) :: NPROC     ! Number of processors (NPRGPNS*NPRGPEW)
12
INTEGER(KIND=JPIM) :: NPRGPNS   ! No. of sets in N-S direction (grid-point space)
13
INTEGER(KIND=JPIM) :: NPRGPEW   ! No. of sets in E-W direction (grid-point space)
14
INTEGER(KIND=JPIM) :: NPRTRW    ! No. of sets in wave direction (spectral space)
15
INTEGER(KIND=JPIM) :: NPRTRV    ! NPROC/NPRTRW
16
INTEGER(KIND=JPIM) :: NPRTRNS   ! No. of sets in N-S direction (Fourier space)
17
                                ! (always equal to NPRTRW)
18
LOGICAL            :: LEQ_REGIONS ! TRUE - Use new eq_regions partitioning
19
                                  ! FALSE- Use old NPRGPNS x NPRGPEW partitioning
20
INTEGER(KIND=JPIM) :: MYPROC    ! My processor number
21
INTEGER(KIND=JPIM) :: MYSETW    ! My set number in wave direction (spectral space)
22
INTEGER(KIND=JPIM) :: MYSETV    ! My set number in field direction(S.S and F.S)
23
INTEGER(KIND=JPIM) :: NCOMBFLEN ! Size of communication buffer
24
25
INTEGER(KIND=JPIM) :: MTAGLETR   ! Tag
26
INTEGER(KIND=JPIM) :: MTAGML     ! Tag
27
INTEGER(KIND=JPIM) :: MTAGLG     ! Tag
28
INTEGER(KIND=JPIM) :: MTAGGL     ! Tag
29
INTEGER(KIND=JPIM) :: MTAGPART   ! Tag
30
INTEGER(KIND=JPIM) :: MTAGDISTSP ! Tag
31
INTEGER(KIND=JPIM) :: MTAGLM     ! Tag
32
INTEGER(KIND=JPIM) :: MTAGDISTGP ! Tag
33
34
INTEGER(KIND=JPIM) ,ALLOCATABLE :: NPRCIDS(:) ! Array containing the process ids
35
36
TYPE DISTR_TYPE
37
LOGICAL   :: LSPLIT             ! TRUE - latitudes are shared between a-sets
38
INTEGER(KIND=JPIM) :: NAPSETS   ! Number of apple sets at the poles. Default is zero.
39
40
! SPECTRAL SPACE
41
42
INTEGER(KIND=JPIM) :: NUMP      ! No. of spectral waves handled by this processor
43
INTEGER(KIND=JPIM) :: NSPEC     ! No. of complex spectral coefficients (on this PE)
44
INTEGER(KIND=JPIM) :: NSPEC2    ! 2*NSPEC
45
INTEGER(KIND=JPIM) :: NSPEC2MX  ! maximun NSPEC2 among all PEs
46
INTEGER(KIND=JPIM) :: NTPEC2
47
INTEGER(KIND=JPIM) :: NUMTP
48
49
50
51
INTEGER(KIND=JPIM) :: NSPOLEGL  ! No. of legendre polynomials on this PE
52
INTEGER(KIND=JPIM) :: NLEI3D    ! (NLEI3-1)/NPRTRW+1
53
54
INTEGER(KIND=JPIM) ,POINTER :: MYMS(:)    ! Wave numbers handled by this PE
55
INTEGER(KIND=JPIM) ,POINTER :: NUMPP(:)   ! No. of wave numbers each wave set is
56
                                 ! responsible for
57
INTEGER(KIND=JPIM) ,POINTER :: NPOSSP(:)  ! Not needed in transform?
58
INTEGER(KIND=JPIM) ,POINTER :: NPROCM(:)  ! Process that does the calc. for certain
59
                                 ! wavenumber M
60
INTEGER(KIND=JPIM) ,POINTER :: NDIM0G(:)  ! Defines partitioning of global spectral
61
                                 ! fields among PEs
62
63
INTEGER(KIND=JPIM) ,POINTER :: NASM0(:)  ! Address in a spectral array of (m, n=m)
64
INTEGER(KIND=JPIM) ,POINTER :: NATM0(:)  ! Same as NASM0 but for NTMAX
65
INTEGER(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.
69
INTEGER(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
75
INTEGER(KIND=JPIM) ,POINTER :: NLATLS(:) ! First latitude for which each a-set calcul.
76
INTEGER(KIND=JPIM) ,POINTER :: NLATLE(:) ! Last latitude for which each a-set calcul.
77
78
INTEGER(KIND=JPIM) ,POINTER :: NPMT(:) ! Adress for legendre polynomial for
79
                              ! given M (NTMAX)
80
INTEGER(KIND=JPIM) ,POINTER :: NPMS(:) ! Adress for legendre polynomial for
81
                              ! given M (NSMAX)
82
INTEGER(KIND=JPIM) ,POINTER :: NPMG(:) ! Global version of NPMS
83
84
! FOURIER SPACE
85
86
INTEGER(KIND=JPIM) :: NDGL_FS ! Number of rows of latitudes for which this process is
87
                     ! performing Fourier Space calculations
88
89
INTEGER(KIND=JPIM) ,POINTER  :: NSTAGTF(:) ! Offset for specific latitude in
90
                                  ! Fourier/gridpoint buffer
91
INTEGER(KIND=JPIM) :: NLENGTF ! Second dimension of Fourier/gridpoint buffer
92
                     ! (sum of (NLOEN+3) over local latitudes)
93
94
INTEGER(KIND=JPIM) ,POINTER :: NULTPP(:) ! No of lats. for each wave_set  (F.S)
95
INTEGER(KIND=JPIM) ,POINTER :: NPROCL(:) ! Process responsible for each lat. (F.S)
96
INTEGER(KIND=JPIM) ,POINTER :: NPTRLS(:) ! Pointer to first lat. (F.S)
97
98
INTEGER(KIND=JPIM) ,POINTER :: NSTAGT0B(:) ! Start adresses for segments within buffer
99
                                  ! (according to processors to whom data
100
                                  ! is going to be sent)
101
INTEGER(KIND=JPIM) ,POINTER :: NSTAGT1B(:)
102
INTEGER(KIND=JPIM) ,POINTER :: NPNTGTB0(:,:)
103
INTEGER(KIND=JPIM) ,POINTER :: NPNTGTB1(:,:)
104
INTEGER(KIND=JPIM) ,POINTER :: NLTSFTB(:)
105
106
INTEGER(KIND=JPIM) ,POINTER :: NLTSGTB(:)
107
INTEGER(KIND=JPIM) ,POINTER :: MSTABF(:)
108
109
INTEGER(KIND=JPIM) :: NLENGT0B
110
INTEGER(KIND=JPIM) :: NLENGT1B
111
112
! GRIDPOINT SPACE
113
114
INTEGER(KIND=JPIM) :: NDGL_GP ! D%NLSTLAT(MY_REGION_NS)-D%NFRSTLOFF
115
INTEGER(KIND=JPIM) ,POINTER :: NFRSTLAT(:) ! First lat of each a-set
116
INTEGER(KIND=JPIM) ,POINTER :: NLSTLAT(:)  ! Last lat of each a-set
117
INTEGER(KIND=JPIM) :: NFRSTLOFF ! Offset for first lat of own a-set
118
                       ! i.e. NFRSTLOFF=NFRSTLAT(MYSETA)-1
119
INTEGER(KIND=JPIM) ,POINTER :: NPTRLAT(:) ! Pointer to start of latitude
120
INTEGER(KIND=JPIM) ,POINTER :: NPTRFRSTLAT(:) ! Pointer to the first latitude of each
121
                                     ! a-set in NSTA and NONL arrays
122
INTEGER(KIND=JPIM) ,POINTER :: NPTRLSTLAT(:) ! Pointer to the last latitude of each
123
                                    ! a-set in NSTA and NONL arrays
124
INTEGER(KIND=JPIM) :: NPTRFLOFF ! Offset for pointer to the first latitude of own a-set
125
                       ! NSTA and NONL arrays, i.e. NPTRFRSTLAT(MYSETA)-1
126
LOGICAL   ,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.
141
INTEGER(KIND=JPIM) ,POINTER :: NSTA(:,:)
142
INTEGER(KIND=JPIM) ,POINTER :: NONL(:,:)
143
144
INTEGER(KIND=JPIM) :: NGPTOT   ! Total number of grid columns on this PE
145
INTEGER(KIND=JPIM) :: NGPTOTG  ! Total number of grid columns on the Globe
146
INTEGER(KIND=JPIM) :: NGPTOTMX ! Maximum number of grid columns on any of the PEs
147
INTEGER(KIND=JPIM) ,POINTER :: NGPTOTL(:,:) ! Number of grid columns on each PE.
148
149
END TYPE DISTR_TYPE
150
151
TYPE(DISTR_TYPE),ALLOCATABLE,TARGET :: DISTR_RESOL(:)
152
TYPE(DISTR_TYPE),POINTER     :: D
153
154
!$OMP THREADPRIVATE(d,leq_regions,mtagdistgp,mtagdistsp,mtaggl,mtagletr)
155
!$OMP THREADPRIVATE(mtaglg,mtaglm,mtagml,mtagpart,myproc,mysetv,mysetw)
156
!$OMP THREADPRIVATE(ncombflen,nprgpew,nprgpns,nproc,nprtrns,nprtrv,nprtrw)
157
158
!$OMP THREADPRIVATE(distr_resol)
159
160
END MODULE TPM_DISTR
161
162
163
164
165
166
167