LMDZ
yomgem.F90
Go to the documentation of this file.
1 MODULE yomgem
2 
3 USE parkind1 ,ONLY : jpim ,jprb
4 
5 IMPLICIT NONE
6 
7 SAVE
8 
9 ! ------------------------------------------------------------------
10 
11 !* * Number of grid points
12 
13 ! NGPTOT : Total number of grid columns on a PE
14 ! NGPTOT_CAP : Size of grid points arrays for ALADIN
15 ! NGPTOTMX : Maximum number of grid columns on any of the PEs
16 ! NGPTOTG : Total number of grid columns on the Globe
17 ! NGPTOTL(NPRGPNS,NPRGPEW) : Total number of grid columns on on eacch PE
18 
19 INTEGER(KIND=JPIM) :: ngptot
20 INTEGER(KIND=JPIM) :: ngptot_cap
21 INTEGER(KIND=JPIM) :: ngptotmx
22 INTEGER(KIND=JPIM) :: ngptotg
23 INTEGER(KIND=JPIM),ALLOCATABLE, TARGET :: ngptotl(:,:)
24 
25 ! ------------------------------------------------------------------
26 
27 !* * Defining the transformed sphere
28 
29 ! RMUCEN : MU OF THE POLE OF STRETCHING
30 ! RLOCEN : LONGITUDE OF THE POLE OF STRETCHING
31 ! RSTRET : STRETCHING FACTOR
32 ! NSTTYP : 1 = POLE OF STRETCHING, POLE OF THE COLLOCATION GRID
33 ! AT THE NORTHERN POLE OF THE REAL EARTH.
34 ! 2 = THE POLE OF STRETCHING IS ANYWHERE ON THE REAL EARTH
35 ! AND ON THE EQUATOR OF THE COLLOCATION GRID ON THE MERIDIAN PI.
36 ! THE EQUATOR OF THE COLLOCATION GRID IS TANGENT
37 ! TO A PARALLEL OF THE EARTH.
38 
39 ! NHTYP : 0 = regular grid
40 ! : 1 = number of points proportional to sqrt(1-mu**2)
41 ! : 2 = number of points read on namelist namrgri
42 
43 ! RNLGINC: increment to get non-linear grid
44 
45 ! R4JP inverse de delta(teta) approche a l'ordre 1
46 ! RC2P1 RSTRET*RSTRET+1.
47 ! RC2M1 RSTRET*RSTRET-1.
48 ! RCOR0 COMPONENT (0,0) OF CORIOLIS
49 ! RCOR1 COMPONENT (0,1) OF CORIOLIS
50 ! RCOR2 COMPONENT (1,1) OF CORIOLIS
51 
52 ! RCOLON(NGPTOT) cosine of longitude on transformed sphere
53 ! RSILON(NGPTOT) sine " " "
54 ! RINDX (NGPTOT) Longitude index
55 ! RINDY (NGPTOT) Latitude index
56 ! RATATH(NGPTOT) RA*TAN(THETA) on real sphere
57 ! RATATX(NGPTOT) Curvature term for LAM (for u eq.)
58 
59 ! NLOEN(NDGSAG:NDGENG) : number of active points on a parallel
60 ! NLOENG(NDGSAG:NDGENG) : global version of NLOEN
61 ! NMEN(NDGSAG:NDGENG) : associated cut-off wave number
62 ! NMENTC(NDGSAG:NDGENG) : same as NMEN but for truncation NTCMAX.
63 ! NMENG(NDGSAG:NDGENG) : global version of NMEN
64 ! NDGLU(0:MAX(NSMAX,NMSMAX)) : number of active points in an hemisphere
65 ! for a given wave number m
66 ! NSTAGP(NGPTOT) : start position of latitude data for boundary fields
67 ! NESTAGP(NGPTOT) : start position of latitude data for boundary fields
68 ! in extension zone (ALADIN).
69 ! NTSTAGP(NGPTOT) : start position of latitude data for boundary fields
70 ! in C+I+E zone (ALADIN).
71 
72 
73 ! REFLRHC : reference length for critical relative humidity (cloud scheme)
74 ! REFLKUO, REFLCAPE, REFLRHC are ONLY to be used in the SETUP
75 ! of TEQK and TEQC and TEQH
76 
77 ! TEQK : ratio between REFLKUO and the model equivalent mesh size
78 ! TEQC : ratio between REFLCAPE and the model equivalent mesh size
79 ! TEQH : ratio between REFLRHC and the model equivalent mesh size
80 
81 ! TEQK, TEQC, TEQH are to be used in the PHYSICS.
82 
83 REAL(KIND=JPRB) :: rmucen
84 REAL(KIND=JPRB) :: rlocen
85 REAL(KIND=JPRB) :: rstret
86 INTEGER(KIND=JPIM) :: nsttyp
87 INTEGER(KIND=JPIM) :: nhtyp
88 REAL(KIND=JPRB) :: rnlginc
89 REAL(KIND=JPRB) :: r4jp
90 REAL(KIND=JPRB) :: rc2p1
91 REAL(KIND=JPRB) :: rc2m1
92 REAL(KIND=JPRB) :: rcor0
93 REAL(KIND=JPRB) :: rcor1
94 REAL(KIND=JPRB) :: rcor2
95 REAL(KIND=JPRB),ALLOCATABLE:: rcolon(:)
96 REAL(KIND=JPRB),ALLOCATABLE:: rsilon(:)
97 REAL(KIND=JPRB),ALLOCATABLE:: rindx(:)
98 REAL(KIND=JPRB),ALLOCATABLE:: rindy(:)
99 REAL(KIND=JPRB),ALLOCATABLE:: ratath(:)
100 REAL(KIND=JPRB),ALLOCATABLE:: ratatx(:)
101 INTEGER(KIND=JPIM),ALLOCATABLE:: nloen(:)
102 INTEGER(KIND=JPIM),ALLOCATABLE,TARGET :: nloeng(:)
103 INTEGER(KIND=JPIM),ALLOCATABLE:: nmen(:)
104 INTEGER(KIND=JPIM),ALLOCATABLE:: nmentc(:)
105 INTEGER(KIND=JPIM),ALLOCATABLE:: nmeng(:)
106 INTEGER(KIND=JPIM),ALLOCATABLE:: ndglu(:)
107 INTEGER(KIND=JPIM),ALLOCATABLE:: nstagp(:)
108 INTEGER(KIND=JPIM),ALLOCATABLE:: nestagp(:)
109 INTEGER(KIND=JPIM),ALLOCATABLE:: ntstagp(:)
110 
111 ! ------------------------------------------------------------------
112 
113 !* * Defining the transformed sphere: physics input
114 
115 REAL(KIND=JPRB) :: reflrhc
116 REAL(KIND=JPRB) :: teqh
117 REAL(KIND=JPRB) :: reflkuo
118 REAL(KIND=JPRB) :: reflcape
119 REAL(KIND=JPRB) :: teqk
120 REAL(KIND=JPRB) :: teqc
121 
122 ! ------------------------------------------------------------------
123 
124 !* * DEFINING THE VERTICAL COORDINATE
125 
126 ! VP00 : REFERENCE PRESSURE FOR DEFINING VERTICAL COORDINATE
127 ! VALH : (0:NFLEVG)
128 ! VBH : (0:NFLEVG) : B of the vertical coordinate
129 ! VETAH : (0:NFLEVG) ; VERTICAL COORDINATE = VALH+VBH
130 ! VETAF : (0:NFLEVG+1) ; VERTICAL COORDINATE ON LAYERS.
131 ! VCUICO: is used to compute denominators of weights
132 ! for semi-Lagrangian vertical interpolations
133 ! applied to full-level variables.
134 ! VCUICOH:is used to compute denominators of weights
135 ! for semi-Lagrangian vertical interpolations
136 ! applied to half-level variables.
137 ! VRLEVX: REAL(NRLEVX)
138 ! NVAUTF: NVAUTF(VRLEVX*eta) is the number of the layer (full level)
139 ! immediately above "eta", and is bounded by 1 and nflevg-1.
140 ! NVAUTH: NVAUTH(VRLEVX*eta) is the number of the interlayer (half level)
141 ! immediately above "eta", and is bounded by 0 and nflevg-1.
142 ! VAH : (0:NFLEVG) ; =VALH*VP00
143 ! VC : (NFLEVG) ; =VAH(J)*VBH(J-1)-VAH(J-1)*VBH(J)
144 ! VDELB : (NFLEVG) ; =VBH(J)-VBH(J-1)
145 ! VDELA : (NFLEVG) ; =VAH(J)-VAH(J-1)
146 ! VAF : like VAH but at full levels.
147 ! VBF : like VBH but at full levels.
148 ! VRDETAH: 1/[Delta eta]
149 ! TOPPRES: REFERENCE "EVANESCENT" PRESSURE
150 ! TOPPRES allows to solve some calculations of singularities
151 ! when the top pressure of the model is zero (for ex. in
152 ! GPPREF, GPXYB, SUNHBMAT).
153 
154 ! WE HAVE THEN FOR THE HALF LEVEL PRESSURE : VAH + VBH*(SURFACE PRESSURE)
155 
156 ! NOTE THAT THE HALF LEVEL VALUE AT K+.5 IS VXXX(K)
157 ! (THE FULL LEVEL VALUES ARE FROM 1 TO NFLEVG)
158 
159 REAL(KIND=JPRB) :: vp00
160 REAL(KIND=JPRB),ALLOCATABLE:: valh(:)
161 REAL(KIND=JPRB),ALLOCATABLE:: vbh(:)
162 REAL(KIND=JPRB),ALLOCATABLE:: vetah(:)
163 REAL(KIND=JPRB),ALLOCATABLE:: vetaf(:)
164 REAL(KIND=JPRB),ALLOCATABLE:: vcuico(:,:)
165 REAL(KIND=JPRB),ALLOCATABLE:: vcuicoh(:,:)
166 REAL(KIND=JPRB) :: vrlevx
167 INTEGER(KIND=JPIM),ALLOCATABLE:: nvautf(:)
168 INTEGER(KIND=JPIM),ALLOCATABLE:: nvauth(:)
169 REAL(KIND=JPRB),ALLOCATABLE:: vah(:)
170 REAL(KIND=JPRB),ALLOCATABLE:: vc(:)
171 REAL(KIND=JPRB),ALLOCATABLE:: vdelb(:)
172 REAL(KIND=JPRB),ALLOCATABLE:: vdela(:)
173 REAL(KIND=JPRB),ALLOCATABLE:: vaf(:)
174 REAL(KIND=JPRB),ALLOCATABLE:: vbf(:)
175 REAL(KIND=JPRB),ALLOCATABLE:: vrdetah(:)
176 REAL(KIND=JPRB) :: toppres
177 
178 ! ------------------------------------------------------------------
179 
180 !* * Miscellaneous
181 
182 ! NBEEGP : ???
183 ! NBNEGP : ???
184 
185 INTEGER(KIND=JPIM) :: nbeegp
186 INTEGER(KIND=JPIM) :: nbnegp
187 
188 ! ------------------------------------------------------------------
189 !$OMP THREADPRIVATE(nbeegp,nbnegp,ngptot,ngptot_cap,ngptotg,ngptotmx,nhtyp,nsttyp,r4jp,rc2m1,rc2p1,rcor0)
190 !$OMP THREADPRIVATE(rcor1,rcor2,reflcape,reflkuo,reflrhc,rlocen,rmucen,rnlginc,rstret,teqc,teqh,teqk,toppres,vp00,vrlevx)
191 !$OMP THREADPRIVATE(ndglu,nestagp,ngptotl,nloen,nloeng,nmen,nmeng,nmentc,nstagp,ntstagp,nvautf,nvauth,ratath,ratatx)
192 !$OMP THREADPRIVATE(rcolon,rindx,rindy,rsilon,vaf,vah,valh,vbf,vbh,vc,vcuico,vcuicoh,vdela,vdelb,vetaf,vetah,vrdetah)
193 END MODULE yomgem
real(kind=jprb) rcor2
Definition: yomgem.F90:94
integer(kind=jpim), dimension(:,:), allocatable, target ngptotl
Definition: yomgem.F90:23
real(kind=jprb), dimension(:), allocatable vbf
Definition: yomgem.F90:174
integer(kind=jpim), dimension(:), allocatable nvauth
Definition: yomgem.F90:168
real(kind=jprb) rcor1
Definition: yomgem.F90:93
integer(kind=jpim), dimension(:), allocatable nstagp
Definition: yomgem.F90:107
real(kind=jprb), dimension(:), allocatable rindx
Definition: yomgem.F90:97
integer(kind=jpim), dimension(:), allocatable, target nloeng
Definition: yomgem.F90:102
real(kind=jprb) r4jp
Definition: yomgem.F90:89
integer(kind=jpim), dimension(:), allocatable ntstagp
Definition: yomgem.F90:109
real(kind=jprb) reflrhc
Definition: yomgem.F90:115
real(kind=jprb) vrlevx
Definition: yomgem.F90:166
integer(kind=jpim) ngptotmx
Definition: yomgem.F90:21
real(kind=jprb) rlocen
Definition: yomgem.F90:84
integer(kind=jpim), dimension(:), allocatable nvautf
Definition: yomgem.F90:167
real(kind=jprb), dimension(:), allocatable rcolon
Definition: yomgem.F90:95
real(kind=jprb) reflkuo
Definition: yomgem.F90:117
real(kind=jprb) rstret
Definition: yomgem.F90:85
real(kind=jprb), dimension(:,:), allocatable vcuico
Definition: yomgem.F90:164
real(kind=jprb), dimension(:), allocatable rsilon
Definition: yomgem.F90:96
real(kind=jprb), dimension(:), allocatable vetaf
Definition: yomgem.F90:163
integer(kind=jpim), dimension(:), allocatable nmen
Definition: yomgem.F90:103
integer(kind=jpim) ngptot_cap
Definition: yomgem.F90:20
real(kind=jprb), dimension(:), allocatable ratatx
Definition: yomgem.F90:100
integer(kind=jpim) nsttyp
Definition: yomgem.F90:86
Definition: yomgem.F90:1
integer(kind=jpim) ngptot
Definition: yomgem.F90:19
integer(kind=jpim), dimension(:), allocatable nestagp
Definition: yomgem.F90:108
real(kind=jprb), dimension(:), allocatable ratath
Definition: yomgem.F90:99
real(kind=jprb), dimension(:), allocatable vbh
Definition: yomgem.F90:161
real(kind=jprb) teqh
Definition: yomgem.F90:116
integer, parameter jprb
Definition: parkind1.F90:31
real(kind=jprb) rc2p1
Definition: yomgem.F90:90
real(kind=jprb), dimension(:), allocatable vdelb
Definition: yomgem.F90:171
real(kind=jprb), dimension(:), allocatable vdela
Definition: yomgem.F90:172
integer(kind=jpim) ngptotg
Definition: yomgem.F90:22
real(kind=jprb), dimension(:), allocatable vah
Definition: yomgem.F90:169
real(kind=jprb) rnlginc
Definition: yomgem.F90:88
real(kind=jprb) vp00
Definition: yomgem.F90:159
integer(kind=jpim), dimension(:), allocatable nmeng
Definition: yomgem.F90:105
integer(kind=jpim), dimension(:), allocatable nloen
Definition: yomgem.F90:101
real(kind=jprb) rmucen
Definition: yomgem.F90:83
real(kind=jprb), dimension(:), allocatable valh
Definition: yomgem.F90:160
real(kind=jprb) toppres
Definition: yomgem.F90:176
real(kind=jprb) reflcape
Definition: yomgem.F90:118
real(kind=jprb), dimension(:), allocatable rindy
Definition: yomgem.F90:98
real(kind=jprb), dimension(:), allocatable vetah
Definition: yomgem.F90:162
real(kind=jprb) rcor0
Definition: yomgem.F90:92
integer(kind=jpim) nbnegp
Definition: yomgem.F90:186
integer, parameter jpim
Definition: parkind1.F90:13
real(kind=jprb) teqc
Definition: yomgem.F90:120
integer(kind=jpim) nhtyp
Definition: yomgem.F90:87
real(kind=jprb), dimension(:), allocatable vaf
Definition: yomgem.F90:173
integer(kind=jpim), dimension(:), allocatable ndglu
Definition: yomgem.F90:106
real(kind=jprb), dimension(:), allocatable vrdetah
Definition: yomgem.F90:175
real(kind=jprb) teqk
Definition: yomgem.F90:119
integer(kind=jpim) nbeegp
Definition: yomgem.F90:185
real(kind=jprb) rc2m1
Definition: yomgem.F90:91
integer(kind=jpim), dimension(:), allocatable nmentc
Definition: yomgem.F90:104
real(kind=jprb), dimension(:), allocatable vc
Definition: yomgem.F90:170
real(kind=jprb), dimension(:,:), allocatable vcuicoh
Definition: yomgem.F90:165