source: LMDZ6/trunk/libf/phylmd/ecrad/yom_ygfl.F90 @ 3981

Last change on this file since 3981 was 3908, checked in by idelkadi, 3 years ago

Online implementation of the radiative transfer code ECRAD in the LMDZ model.

  • Inclusion of the ecrad directory containing the sources of the ECRAD code
    • interface routine : radiation_scheme.F90
  • Adaptation of compilation scripts :
    • compilation under CPP key CPP_ECRAD
    • compilation with option "-rad ecard" or "-ecard true"
    • The "-rad old/rtm/ecran" build option will need to replace the "-rrtm true" and "-ecrad true" options in the future.
  • Runing LMDZ simulations with ecrad, you need :
    • logical key iflag_rrtm = 2 in physiq.def
    • namelist_ecrad (DefLists?)
    • the directory "data" containing the configuration files is temporarily placed in ../libfphylmd/ecrad/
  • Compilation and execution are tested in the 1D case. The repository under svn would allow to continue the implementation work: tests, verification of the results, ...
File size: 25.2 KB
Line 
1MODULE YOM_YGFL
2
3USE PARKIND1 , ONLY : JPIM, JPRB
4
5IMPLICIT NONE
6SAVE
7
8!-------------------------------------------------------------------------
9! Contains the descriptors of GFL arrays
10!-------------------------------------------------------------------------
11
12! JPGFL : Max number of GFL fields
13! JPNAMED_GFL : Number of currently pre-defined components of GFL
14! JPGHG : Number of greenhouse gas fields
15! JPGRG : Number of reactive gas fields
16! JPCHEM : Number of chemical species
17! JPAERO : Number of active aerosol fields
18! JPAEROUT: Number of output aerosol fields
19! JPUVP : Number of output from UV processor
20! JPTRAC : Number of tracers for diagnostics
21! JPERA40 : Number of ERA40 diagnostic fields
22! JPCH4S  : Number of added fields related to methane
23! JPNOGW  : Number of diagnostic fields for NORO GWD SCHEME
24! JPSLDIA : Number of SL dynamics diagnostic fields
25! JPCHEM_ASSIM : Maximum number of assimilated of chemical species
26!-------------------------------------------------------------------------
27
28INTEGER(KIND=JPIM), PARAMETER :: JPGFL=2163
29INTEGER(KIND=JPIM), PARAMETER :: JPNAMED_GFL=27
30INTEGER(KIND=JPIM), PARAMETER :: JPGHG=3
31INTEGER(KIND=JPIM), PARAMETER :: JPTRAC=10
32INTEGER(KIND=JPIM), PARAMETER :: JPCHEM=66
33INTEGER(KIND=JPIM), PARAMETER :: JPGRG=5       
34INTEGER(KIND=JPIM), PARAMETER :: JPCHEM_ASSIM=5
35INTEGER(KIND=JPIM), PARAMETER :: JPAERO=16
36INTEGER(KIND=JPIM), PARAMETER :: JPFORC=1800
37INTEGER(KIND=JPIM), PARAMETER :: JPERA40=14
38INTEGER(KIND=JPIM), PARAMETER :: JPSLDIA=7
39INTEGER(KIND=JPIM), PARAMETER :: JPEZDIAG=50
40INTEGER(KIND=JPIM), PARAMETER :: JPCH4S=2
41INTEGER(KIND=JPIM), PARAMETER :: JPNOGW=2
42INTEGER(KIND=JPIM), PARAMETER :: JPAEROUT=17
43INTEGER(KIND=JPIM), PARAMETER :: JPUVP=2
44INTEGER(KIND=JPIM), PARAMETER :: JPPHYS=8   
45INTEGER(KIND=JPIM), PARAMETER :: GRIB_CODE_GFL_PHYS=81  ! AJGDB hopefully harmless
46
47TYPE TYPE_GFL_COMP ! Individual field descriptor
48
49SEQUENCE ! daand: necessary to avoid memory corruption with gfortran 4.3.3
50
51CHARACTER(LEN=16)  :: CNAME     = ''        ! ARPEGE field name
52INTEGER(KIND=JPIM) :: IGRBCODE  = -999      ! GRIB code
53LOGICAL            :: LADV      = .FALSE.   ! Field advected or not
54LOGICAL            :: LADV5     = .FALSE.   ! Field advected without wind increments
55LOGICAL            :: LTDIABLIN = .FALSE.   ! Diabatic tendency is interpolated by lin. int.
56LOGICAL            :: LHORTURB  = .FALSE.   ! Horizontal part affected by 3D turbulence
57INTEGER(KIND=JPIM) :: NREQIN    = 0         ! 1 if field requiered in input, 0 if not, -1 if initialised
58                                            ! with a reference value REFVALI
59LOGICAL            :: LREQOUT   = .FALSE.   ! T if field requiered in output
60LOGICAL            :: LGPINGP   = .TRUE.    ! GP field input as GP
61LOGICAL            :: LGP       = .FALSE.   ! Field exists and of grid-point type
62LOGICAL            :: LSP       = .FALSE.   ! Field exists and of spectral type
63LOGICAL            :: LCDERS    = .FALSE.   ! Derivatives required (spectral only)
64LOGICAL            :: LACTIVE   = .FALSE.   ! Field in use
65LOGICAL            :: LTHERMACT = .FALSE.   ! Field thermodynamically active
66REAL(KIND=JPRB)    :: R         = 0.0_JPRB
67REAL(KIND=JPRB)    :: RCP       = 0.0_JPRB
68LOGICAL            :: LT9       = .FALSE.   ! Field in t-dt GFL
69LOGICAL            :: LT1       = .FALSE.   ! Field in t+dt GFL
70LOGICAL            :: LT5       = .FALSE.   ! Field in trajectory GFL
71LOGICAL            :: LPHY      = .FALSE.   ! Field in physics GFL
72LOGICAL            :: LPT       = .FALSE.   ! Field in PC phy. tend. GFL (GFLPT)
73LOGICAL            :: LTRAJIO   = .FALSE.   ! Field written to and from trajectory structure
74LOGICAL            :: LDIAG     = .FALSE.   ! Field is "diagnostic" at t; e.g. cloud fraction
75LOGICAL            :: LPC       = .FALSE.   ! Field in predictor/corrector time stepping (GFLPC)
76REAL(KIND=JPRB)    :: REFVALI   = 0.0_JPRB  ! Reference value for init, used in case NREQIN==-1
77! LAM specific attributes (Arome/Aladin)
78LOGICAL            :: LADJUST0  = .FALSE.   ! True if field is thermodynamically adjusted at t
79                                            ! (immediatly after inverse spectral transforms)
80LOGICAL            :: LADJUST1  = .FALSE.   ! True if field is thermodynamically adjusted at t+dt
81                                            ! (after SL interpolations and NL residuals)
82INTEGER(KIND=JPIM) :: NCOUPLING = 0         ! 1 if field is coupled by Davies relaxation, 0 if not,
83                                            ! -1 if coupled with reference value for coupling REFVALC
84REAL(KIND=JPRB)    :: REFVALC   = 0.0_JPRB  ! Reference value for coupling, used in case NCOUPLING==-1
85LOGICAL            :: LBIPER    = .FALSE.   ! True if field must be biperiodised inside the transforms
86! End LAM specific attributes (Arome/Aladin)
87CHARACTER(LEN=12)  :: CSLINT    = ''        ! S.L interpolaion "type"
88INTEGER(KIND=JPIM) :: MP        = -99999999 ! Basic field "pointer"
89INTEGER(KIND=JPIM) :: MPL       = -99999999 ! zonal derivative "pointer"
90INTEGER(KIND=JPIM) :: MPM       = -99999999 ! Meridional derivative "pointer"
91INTEGER(KIND=JPIM) :: MP9       = -99999999 ! Basic field "pointer" t-dt
92INTEGER(KIND=JPIM) :: MP9_PH    = -99999999 ! Basic field "pointer" for Physics
93INTEGER(KIND=JPIM) :: MP1       = -99999999 ! Basic field "pointer" t+dt
94INTEGER(KIND=JPIM) :: MP5       = -99999999 ! Basic field "pointer" trajectory
95INTEGER(KIND=JPIM) :: MP5L      = -99999999 ! zonal derivative "pointer" trajectory
96INTEGER(KIND=JPIM) :: MP5M      = -99999999 ! Meridional derivative "pointer" trajectory
97INTEGER(KIND=JPIM) :: MPSLP     = -99999999 ! Basic field "pointer" physics
98INTEGER(KIND=JPIM) :: MPSP      = -99999999 ! Basic field "pointer" spectral space
99INTEGER(KIND=JPIM) :: MP_SPL    = -99999999 ! Basic field "pointer" spline interpolation
100INTEGER(KIND=JPIM) :: MP_SL1    = -99999999 ! Basic field "pointer" in SLBUF1
101INTEGER(KIND=JPIM) :: MP_SLX    = -99999999 ! Basic field "pointer" in SLBUF1 for CPG_PT
102INTEGER(KIND=JPIM) :: MPPT      = -99999999 ! Physics tendency "pointer"
103INTEGER(KIND=JPIM) :: MPPC      = -99999999 ! Predictor/corrector auxiliary array "pointer"
104
105! daand: INTFLEX attributes
106LOGICAL            :: LWATER                ! TRUE for water species
107LOGICAL            :: LPRECIP               ! TRUE for precipitating water species
108REAL(KIND=JPRB)    :: RLZER                 ! Latent heat change at 0K
109
110! gems nl ext
111INTEGER(KIND=JPIM) :: NCOUPLO4              ! Coupled to CTM by OASIS4 intefrace
112LOGICAL            :: LASSIM                ! use as Control Variable (either monitored or assimilated)
113INTEGER(KIND=JPIM) :: IGRIBDV               ! GRIB code of deposition velocity
114INTEGER(KIND=JPIM) :: IGRIBTC               ! GRIB code of Total Column
115INTEGER(KIND=JPIM) :: IGRIBSFC              ! GRIB code of Surface Flux
116LOGICAL            :: LDIFF                 ! Diffusion  on
117LOGICAL            :: LCONV                 ! Convection on
118REAL(KIND=JPRB)    :: RMOLMASS              ! Molar Mass
119REAL(KIND=JPRB)    :: REFOLD                ! Efolding decay time
120REAL(KIND=JPRB)    :: HENRYA                ! Henry constant a
121REAL(KIND=JPRB)    :: HENRYB                ! Henry constant b
122LOGICAL            :: LNEGFIX               ! Cut off negative values in sugridug an
123LOGICAL            :: LMASSFIX              ! Correct mass error of sl advection in gpmodel (if LTRCMFIX)
124TYPE(TYPE_GFL_COMP),POINTER :: PREVIOUS     ! Pointer to previously def. field
125
126END TYPE TYPE_GFL_COMP
127
128TYPE TYPE_GFL_NAML ! Individual field descriptor for namelist input
129
130SEQUENCE ! daand: necessary to avoid memory corruption with gfortran 4.3.3
131
132CHARACTER(LEN=16)  :: CNAME     ! ARPEGE field name
133INTEGER(KIND=JPIM) :: IGRBCODE  ! GRIB code
134INTEGER(KIND=JPIM) :: NREQIN    ! 1 if field required in input, 0 if not, -1 if initialised
135                                ! with a reference value REFVALI
136REAL(KIND=JPRB) :: REFVALI      ! Reference value for initialisation, used in case NREQIN==-1
137LOGICAL :: LREQOUT              ! T if field requiered in output
138LOGICAL :: LGPINGP              ! GP field input as GP
139LOGICAL :: LGP                  ! Field exists and of grid-point type
140LOGICAL :: LSP                  ! Field exists and of spectral type
141LOGICAL :: LCDERS               ! Derivatives required (spectral only)
142LOGICAL :: LT9                  ! Field in t-dt GFL
143LOGICAL :: LT1                  ! Field in t+dt GFL
144LOGICAL :: LT5                  ! Field in trajectory GFL
145LOGICAL :: LPHY                 ! Field with physics tendencies GFL
146LOGICAL :: LPT                  ! Field in PC physics tendency GFLPT
147LOGICAL :: LTRAJIO              ! Field written to and from trajectory structure
148LOGICAL :: LDIAG                ! Field is "diagnostic" at t; e.g. cloud fraction
149LOGICAL :: LPC                  ! Field in predictor/corrector time stepping GFLPC
150LOGICAL :: LADV                 ! Field advected or not
151LOGICAL :: LADV5                ! Field advected without wind increments
152LOGICAL :: LINTLIN              ! Linear interpolation for field
153LOGICAL :: LTDIABLIN            ! Diabatic tendency is interpolated by linear int.
154LOGICAL :: LHORTURB             ! Horizontal part affected by 3D turbulence
155LOGICAL :: LQM                  ! quasi-monotonous interpolation for field
156LOGICAL :: LQMH                 ! quasi-monotonous interpolation in horizontal for field
157LOGICAL :: LQM3D                ! quasi-monotone interpolation applied directly in 3 dimensions
158LOGICAL :: LSLHD                ! Semi-lagrangian horizontal diffusion used for field
159LOGICAL :: LCOMAD               ! COMAD weights used for SL interpolation of field
160LOGICAL :: LHV                  ! Hermite vertical interpolation used for field (only ozone sofar)
161LOGICAL :: LVSPLIP              ! vertical spline interpolation used for field (only ozone sofar)
162INTEGER(KIND=JPIM) :: NCOUPLING ! 1 if field is coupled by Davies relaxation, 0 if not,
163                                ! -1 if coupled with reference value for coupling REFVALC
164REAL(KIND=JPRB) :: REFVALC      ! Reference value for coupling, used in case
165                                ! NCOUPLING==-1
166! gems nl ext
167INTEGER(KIND=JPIM)  :: NCOUPLO4 ! Coupled to CTM by OASIS4 intefrace =1 input,=2 in&output,=-1 none
168LOGICAL             :: LASSIM   ! use as Control Variable (either monitored or assimilated)
169INTEGER(KIND=JPIM)  :: IGRIBDV  ! GRIB code of deposition velocity
170INTEGER(KIND=JPIM)  :: IGRIBTC  ! GRIB code of Total Column
171INTEGER(KIND=JPIM)  :: IGRIBSFC ! GRIB code of Surface Flux
172LOGICAL             :: LDIFF    ! Diffusion  on
173LOGICAL             :: LCONV    ! Convection on
174LOGICAL             :: LNEGFIX  ! Cut off negative values in sugridug and callpar
175LOGICAL             :: LMASSFIX ! Correct mass error of sl advection in gpmodel (if LTRCMFIX)
176REAL(KIND=JPRB)     :: RMOLMASS ! Molar Mass
177REAL(KIND=JPRB)     :: REFOLD   ! Efolding  decay time
178REAL(KIND=JPRB)     :: HENRYA   ! Henry constant a
179REAL(KIND=JPRB)     :: HENRYB   ! Henry constant b
180
181END TYPE TYPE_GFL_NAML
182
183!-------------------------------------------------------------------------
184! Derived types for describing the GFL structure.
185!-------------------------------------------------------------------------
186! Modifications:
187! 03/07/09 C. Fischer - add Arome/Aladin attributes
188! 03/10/01 C. Moussy  - add Arome/Aladin attributes coupling
189! 03/10/31 M. Tudor   - add physics tendencies for predictor-corrector
190! 05/10/10 J. Haseler - switch for I/O to trajectory structure
191! 2004-Nov F. Vana    - update of CSLINT attribute
192! 20-Feb-2005 Vivoda  - 3TL Eul PC scheme (GFLPC)
193! 07/06/27 E. Holm    - TL/AD advection without wind increments LADV5
194! 12/04/08 J. Flemming - GFL attribute extention for GEMS
195! 22-Feb-11 F. Vana   - LTDIABLIN and LHORTURB
196! spring 2011 ECMWF   - LINTLIN
197! Nov. 2013           - LCOMAD
198! 2013-11, D. Degrauwe - INTFLEX attributes
199
200TYPE TYPE_GFLD
201
202SEQUENCE ! daand: necessary to avoid memory corruption with gfortran 4.3.3
203
204! Overall descriptor,dimensioning etc.
205INTEGER(KIND=JPIM) :: NUMFLDS     = 0  ! Number of GFL fields
206INTEGER(KIND=JPIM) :: NDERS       = 0  ! Number of horizontal derivatives fields
207INTEGER(KIND=JPIM) :: NUMSPFLDS   = 0  ! Number of spectrally represented GFL fields
208INTEGER(KIND=JPIM) :: NUMGPFLDS   = 0  ! Number of grid-point GFL fields
209INTEGER(KIND=JPIM) :: NUMFLDS9    = 0  ! Number of GFL fields in (t-dt) part
210INTEGER(KIND=JPIM) :: NUMFLDS1    = 0  ! Number of GFL fields in (t+dt) array
211INTEGER(KIND=JPIM) :: NUMSPFLDS1  = 0  ! Number of spectrally represented GFL fields (t+dt)
212INTEGER(KIND=JPIM) :: NUMFLDS5    = 0  ! Number of GFL fields (trajectory)
213INTEGER(KIND=JPIM) :: NUMFLDSPHY  = 0  ! Number of GFL fields (phys.)
214INTEGER(KIND=JPIM) :: NUMFLDS_SPL = 0  ! Number of GFL fields (S.L. spline interpolation)
215INTEGER(KIND=JPIM) :: NUMFLDS_SL1 = 0  ! Number of GFL fields in S.L. buffer 1
216INTEGER(KIND=JPIM) :: NUMFLDSPC   = 0  ! Number of GFL fields (predictor/corrector)
217INTEGER(KIND=JPIM) :: NDIM        = 0  ! Dimension of main array holding GFL fields(GFL)
218INTEGER(KIND=JPIM) :: NUMFLDSPT   = 0  ! Number of GFL fields (phy. tend.)
219INTEGER(KIND=JPIM) :: NDIM0       = 0  ! Dimension of t0 part of GFL
220INTEGER(KIND=JPIM) :: NDIM9       = 0  ! Dimension of t-dt part of GFL
221INTEGER(KIND=JPIM) :: NDIM1       = 0  ! Dimension of t+dt array (GFLT1)
222INTEGER(KIND=JPIM) :: NDIM5       = 0  ! Dimension of traj. GFL array (GFL5)
223INTEGER(KIND=JPIM) :: NDIMSLP     = 0  ! Diminsion of S.L. phys. GFL array (GFLSLP)
224INTEGER(KIND=JPIM) :: NDIM_SPL    = 0  ! Dim. of arrays holding GFL fields (S.L.spline int.)
225INTEGER(KIND=JPIM) :: NDIMPT      = 0  ! Dimension of phy. tend. GFL array (GFLPT)
226INTEGER(KIND=JPIM) :: NDIMPC      = 0  ! Dimension of iterative scheme auxiliary array (GFLPC)
227
228INTEGER(KIND=JPIM) :: NGFL_EXT
229INTEGER(KIND=JPIM) :: NGFL_FORC
230INTEGER(KIND=JPIM) :: NGFL_EZDIAG
231INTEGER(KIND=JPIM) :: NGHG
232INTEGER(KIND=JPIM) :: NTRAC
233INTEGER(KIND=JPIM) :: NGRG
234INTEGER(KIND=JPIM) :: NGRG_CPLO4
235INTEGER(KIND=JPIM) :: NGRG_ASSIM
236INTEGER(KIND=JPIM) :: NAERO
237INTEGER(KIND=JPIM) :: NACTAERO
238INTEGER(KIND=JPIM) :: NDDHAERO
239INTEGER(KIND=JPIM) :: NERA40
240INTEGER(KIND=JPIM) :: NNOGW
241INTEGER(KIND=JPIM) :: NAEROUT
242INTEGER(KIND=JPIM) :: NUVP
243INTEGER(KIND=JPIM) :: NSLDIA
244INTEGER(KIND=JPIM) :: NSLDIAGP
245INTEGER(KIND=JPIM) :: NGFL_PHYS
246LOGICAL :: LCO2SFC
247LOGICAL :: LCH4SFC
248LOGICAL :: LAEROSFC
249LOGICAL :: LFIRE
250LOGICAL :: LAERODIU
251LOGICAL :: LTRCMFIX       ! Activates tracer mass fixer
252LOGICAL :: LTRCMFIX_PS    ! Adjust pressure to conserve dry mass in mass fixer calculations
253LOGICAL :: LAEROUT
254LOGICAL :: LUVPOUT
255LOGICAL :: LCHEM
256
257INTEGER(KIND=JPIM) :: NGEMS   ! The total number of "GEMS" fields.
258INTEGER(KIND=JPIM) :: NCHEM
259INTEGER(KIND=JPIM) :: NCHEM_ASSIM
260INTEGER(KIND=JPIM) :: NCHEM_FLX
261INTEGER(KIND=JPIM) :: NCHEM_DV
262INTEGER(KIND=JPIM) :: NCHEM_TC
263INTEGER(KIND=JPIM) :: NCHEM_SCV
264
265!     ------------------------------------------------------------------
266!      Mass fixers
267!     ------------------------------------------------------------------
268INTEGER(KIND=JPIM) :: NNEGAFIX     ! Num of fields to apply -ve fixer
269INTEGER(KIND=JPIM) :: NOPTNEGFIX   ! 1: simple negative fixer (reset to 0)
270                                   ! 2: reset to local minimum
271
272LOGICAL :: LQM3DCONS      ! Bermejo & Staniforth quasi-monotone limiter with improved
273                          ! conservation option. When true, applied to all GFL s.t. LQM3D=true
274LOGICAL :: LADVNEGFIX              ! Activates negative fixer for advection
275LOGICAL :: LTRCMFBC                ! Activate Bermejo & Conde if true
276LOGICAL :: LTRCMFPR                ! Activate Priestley algorithm if true
277LOGICAL :: LTRCMFMG                ! Activate Mac Gregor's algorithm if true
278LOGICAL :: LEXTRADF                ! Extra diagnostics
279
280
281INTEGER(KIND=JPIM) :: NFLDSFIX     ! Number of fields to be fixed
282INTEGER(KIND=JPIM) :: NOPTMFIX     ! Bermejo & Conde fixer option for calculating its weight
283INTEGER(KIND=JPIM) :: NOPTVFE      ! Use Vertical FE in calculation of column mass total
284INTEGER(KIND=JPIM) :: NPMFIX       ! Parameter used in weight calculation
285INTEGER(KIND=JPIM) :: NMFDIAGLEV   ! Determines global diagnostic output level for fixer:
286                                   ! 0 - nothing, 1 - norms printed, 2 - norms + monotonicity
287INTEGER(KIND=JPIM) :: NMFIXFLDS(JPNAMED_GFL+JPGHG+JPGRG+JPCHEM+JPAERO+JPTRAC)
288                                   ! Index of fields to be corrected by mass fixers
289INTEGER(KIND=JPIM) :: NNEGFLDS(JPNAMED_GFL+JPGHG+JPGRG+JPCHEM+JPAERO+JPTRAC) 
290                                   ! Index of fields to be corrected by SL -ve fixer
291REAL(KIND=JPRB)    :: ZMFIXEPS     ! Threshold for mass fixing scheme
292
293TYPE(TYPE_GFL_COMP) :: YCOMP(JPGFL)    ! General descriptor of all components
294
295TYPE(TYPE_GFL_COMP),POINTER  :: YQ          => NULL() ! Specific humidity
296TYPE(TYPE_GFL_COMP),POINTER  :: YI          => NULL() ! Ice water
297TYPE(TYPE_GFL_COMP),POINTER  :: YL          => NULL() ! Liquid water
298TYPE(TYPE_GFL_COMP),POINTER  :: YLCONV      => NULL() ! Liquid water (CONV. PART)
299TYPE(TYPE_GFL_COMP),POINTER  :: YICONV      => NULL() ! Ice    water (CONV. PART)
300TYPE(TYPE_GFL_COMP),POINTER  :: YRCONV      => NULL() ! Rain         (CONV. PART)
301TYPE(TYPE_GFL_COMP),POINTER  :: YSCONV      => NULL() ! Snow         (CONV. PART)
302TYPE(TYPE_GFL_COMP),POINTER  :: YIRAD       => NULL() ! Radiative cloud Ice water
303TYPE(TYPE_GFL_COMP),POINTER  :: YLRAD       => NULL() ! Radiative cloud Liquid water
304TYPE(TYPE_GFL_COMP),POINTER  :: YS          => NULL() ! Snow
305TYPE(TYPE_GFL_COMP),POINTER  :: YR          => NULL() ! Rain
306TYPE(TYPE_GFL_COMP),POINTER  :: YG          => NULL() ! Graupel
307TYPE(TYPE_GFL_COMP),POINTER  :: YH          => NULL() ! Hail
308TYPE(TYPE_GFL_COMP),POINTER  :: YTKE        => NULL() ! Turbulent Kinetic Energy
309TYPE(TYPE_GFL_COMP),POINTER  :: YTTE        => NULL() ! Turbulent Total Energy
310TYPE(TYPE_GFL_COMP),POINTER  :: YEFB1       => NULL() ! First variable EFB scheme
311TYPE(TYPE_GFL_COMP),POINTER  :: YEFB2       => NULL() ! Second variable EFB scheme
312TYPE(TYPE_GFL_COMP),POINTER  :: YEFB3       => NULL() ! Third variable EFB scheme
313TYPE(TYPE_GFL_COMP),POINTER  :: YA          => NULL() ! Cloud fraction
314TYPE(TYPE_GFL_COMP),POINTER  :: YO3         => NULL() ! Ozone
315TYPE(TYPE_GFL_COMP),POINTER  :: YSRC        => NULL() ! Second-order flux for AROME s'rc'/2Sigma_s2 multiplied by Lambda_3
316TYPE(TYPE_GFL_COMP),POINTER  :: YMXL        => NULL() ! Prognostic mixing length
317TYPE(TYPE_GFL_COMP),POINTER  :: YSCC2       => NULL() ! Saturation deficit^2 for Tompkins
318TYPE(TYPE_GFL_COMP),POINTER  :: YGCCA       => NULL() ! Skewness for Tompkins
319TYPE(TYPE_GFL_COMP),POINTER  :: YCPF        => NULL() ! Convective precipitation flux
320TYPE(TYPE_GFL_COMP),POINTER  :: YSPF        => NULL() ! Stratiform precipitation flux
321TYPE(TYPE_GFL_COMP),POINTER  :: YCVGQ       => NULL() ! Moisture Convergence for french physics
322TYPE(TYPE_GFL_COMP),POINTER  :: YQVA        => NULL() ! total humidity variation
323TYPE(TYPE_GFL_COMP),POINTER  :: YGHG(:)     => NULL() ! Greenhouse Gases
324TYPE(TYPE_GFL_COMP),POINTER  :: YGRG(:)     => NULL() ! Reactive Gases
325TYPE(TYPE_GFL_COMP),POINTER  :: YCHEM(:)    => NULL() ! Chemistry
326TYPE(TYPE_GFL_COMP),POINTER  :: YGRGTEND(:) => NULL() ! Reactive Gases Tendecies
327TYPE(TYPE_GFL_COMP),POINTER  :: YAERO(:)    => NULL() ! Aerosols
328TYPE(TYPE_GFL_COMP),POINTER  :: YTRAC(:)    => NULL() ! tracers for diagnostics
329TYPE(TYPE_GFL_COMP),POINTER  :: YLRCH4      => NULL() ! CH4 loss rate (instantaneous field)
330TYPE(TYPE_GFL_COMP),POINTER  :: YCH4S       => NULL() ! CH4 atmospheric sink (accumulated field)
331TYPE(TYPE_GFL_COMP),POINTER  :: YFORC(:)    => NULL() ! large scale forcing
332TYPE(TYPE_GFL_COMP),POINTER  :: YEZDIAG(:)  => NULL() ! easy diagnostics
333TYPE(TYPE_GFL_COMP),POINTER  :: YERA40(:)   => NULL() ! ERA40 diagnostic fields
334TYPE(TYPE_GFL_COMP),POINTER  :: YNOGW(:)    => NULL() ! NORO GWD SCHEME
335TYPE(TYPE_GFL_COMP),POINTER  :: YSLDIA(:)   => NULL() ! SL dynamics diagnostics
336TYPE(TYPE_GFL_COMP),POINTER  :: YAEROUT(:)  => NULL() ! Aerosol outputs
337TYPE(TYPE_GFL_COMP),POINTER  :: YUVP(:)     => NULL() ! UV-processor output
338TYPE(TYPE_GFL_COMP),POINTER  :: YPHYS(:)    => NULL() ! PHYS output
339
340
341TYPE(TYPE_GFL_COMP),POINTER  :: YSDSAT      => NULL() ! Standard Deviation of the
342                                                      ! SATuration Depression (Sigma_s)
343TYPE(TYPE_GFL_COMP),POINTER  :: YCVV        => NULL() ! Convective Vertical Velocity
344TYPE(TYPE_GFL_COMP),POINTER  :: YRKTH       => NULL() ! Rasch-Kristjansson H tendency
345TYPE(TYPE_GFL_COMP),POINTER  :: YRKTQV      => NULL() ! Rasch-Kristjansson Qv tendency
346TYPE(TYPE_GFL_COMP),POINTER  :: YRKTQC      => NULL() ! Rasch-Kristjansson Qc tendency
347
348! Prognostic convection variables: add 6 named components
349TYPE(TYPE_GFL_COMP),POINTER  :: YUOM        => NULL() ! Updraught vert velocity
350TYPE(TYPE_GFL_COMP),POINTER  :: YUAL        => NULL() ! Updraught mesh fraction
351TYPE(TYPE_GFL_COMP),POINTER  :: YDOM        => NULL() ! Downdraught vert velocity
352TYPE(TYPE_GFL_COMP),POINTER  :: YDAL        => NULL() ! Downdraught mesh fraction
353TYPE(TYPE_GFL_COMP),POINTER  :: YUEN        => NULL() ! Updraught entrainment
354TYPE(TYPE_GFL_COMP),POINTER  :: YUNEBH      => NULL() ! pseudo-historic convective
355
356! Extra fields
357
358TYPE(TYPE_GFL_COMP),POINTER  :: YEXT(:)     => NULL() ! Extra fields
359
360TYPE(TYPE_GFL_NAML)  :: YQ_NL                 ! Specific humidity
361TYPE(TYPE_GFL_NAML)  :: YI_NL                 ! Ice water
362TYPE(TYPE_GFL_NAML)  :: YL_NL                 ! Liquid water
363TYPE(TYPE_GFL_NAML)  :: YLCONV_NL             ! Liquid water (CONV. PART)
364TYPE(TYPE_GFL_NAML)  :: YICONV_NL             ! Ice    water (CONV. PART)
365TYPE(TYPE_GFL_NAML)  :: YRCONV_NL             ! Rain         (CONV. PART)
366TYPE(TYPE_GFL_NAML)  :: YSCONV_NL             ! Snow         (CONV. PART)
367TYPE(TYPE_GFL_NAML)  :: YIRAD_NL              ! Radiative cloud Ice water
368TYPE(TYPE_GFL_NAML)  :: YLRAD_NL              ! Radiative cloud Liquid water
369TYPE(TYPE_GFL_NAML)  :: YS_NL                 ! Snow
370TYPE(TYPE_GFL_NAML)  :: YR_NL                 ! Rain
371TYPE(TYPE_GFL_NAML)  :: YG_NL                 ! Graupels
372TYPE(TYPE_GFL_NAML)  :: YH_NL                 ! Hail
373TYPE(TYPE_GFL_NAML)  :: YTKE_NL               ! Turbulent Kinetic Energy
374TYPE(TYPE_GFL_NAML)  :: YTTE_NL               ! Turbulent Total Energy
375TYPE(TYPE_GFL_NAML)  :: YEFB1_NL              ! First variable EFB scheme
376TYPE(TYPE_GFL_NAML)  :: YEFB2_NL              ! Second variable EFB scheme
377TYPE(TYPE_GFL_NAML)  :: YEFB3_NL              ! Third variable EFB scheme
378TYPE(TYPE_GFL_NAML)  :: YA_NL                 ! Cloud fraction
379TYPE(TYPE_GFL_NAML)  :: YO3_NL                ! Ozone
380TYPE(TYPE_GFL_NAML)  :: YSRC_NL               ! Second-order flux for AROME
381                                              ! s'rc'/2Sigma_s2
382                                              ! multiplied by Lambda_3
383TYPE(TYPE_GFL_NAML)  :: YMXL_NL               ! Prognostic mixing length
384TYPE(TYPE_GFL_NAML)  :: YSCC2_NL              ! Saturation deficit^2 for Tompkins
385TYPE(TYPE_GFL_NAML)  :: YGCCA_NL              ! Skewness for Tompkins
386TYPE(TYPE_GFL_NAML)  :: YCPF_NL               ! Convective precipitation flux
387TYPE(TYPE_GFL_NAML)  :: YSPF_NL               ! Stratiform precipitation flux
388TYPE(TYPE_GFL_NAML)  :: YCVGQ_NL              ! Moisture Convergence for french physics
389TYPE(TYPE_GFL_NAML)  :: YQVA_NL               ! Total humidity variation
390
391TYPE(TYPE_GFL_NAML)  :: YGHG_NL(JPGHG)        ! Greenhouse Gases
392TYPE(TYPE_GFL_NAML)  :: YGRG_NL(JPGRG)        ! Reactive Gases
393TYPE(TYPE_GFL_NAML)  :: YCHEM_NL(JPCHEM)      ! Chemical species
394TYPE(TYPE_GFL_NAML)  :: YGRGTEND_NL(JPGRG)    ! Reactive Gases Tendecies
395TYPE(TYPE_GFL_NAML)  :: YAERO_NL(JPAERO)      ! Aerosol fields
396TYPE(TYPE_GFL_NAML)  :: YTRAC_NL(JPTRAC)      ! Tracers for diagnostics
397TYPE(TYPE_GFL_NAML)  :: YERA40_NL(JPERA40)    ! ERA40 diagnostic fields
398TYPE(TYPE_GFL_NAML)  :: YNOGW_NL(JPNOGW)      ! NORO GWD SCHEME
399TYPE(TYPE_GFL_NAML)  :: YSLDIA_NL(JPSLDIA)    ! SL dynamics diagnostics
400TYPE(TYPE_GFL_NAML)  :: YLRCH4_NL             ! CH4 loss rate
401TYPE(TYPE_GFL_NAML)  :: YCH4S_NL              ! CH4 atmospheric sink
402TYPE(TYPE_GFL_NAML)  :: YAEROUT_NL(JPAEROUT)  ! Aerosol outputs
403TYPE(TYPE_GFL_NAML)  :: YUVP_NL(JPUVP)        ! UV-processor outputs
404TYPE(TYPE_GFL_NAML)  :: YRKTH_NL              ! Rasch-Kristjansson H tendency
405TYPE(TYPE_GFL_NAML)  :: YRKTQV_NL             ! Rasch-Kristjansson Qv tendency
406TYPE(TYPE_GFL_NAML)  :: YRKTQC_NL             ! Rasch-Kristjansson Qc tendency
407TYPE(TYPE_GFL_NAML)  :: YPHYS_NL(JPPHYS)      ! PHYS outputs
408
409! Extra fields
410TYPE(TYPE_GFL_NAML)  :: YSDSAT_NL             ! Standard Deviation of the
411                                              ! SATuration Depression (Sigma_s)
412TYPE(TYPE_GFL_NAML)  :: YCVV_NL               ! Convective Vertical Velocity
413TYPE(TYPE_GFL_NAML)  :: YFORC_NL(JPFORC)      ! Forcing precursor
414TYPE(TYPE_GFL_NAML)  :: YEZDIAG_NL(JPEZDIAG)  ! Easy diagnostics
415TYPE(TYPE_GFL_NAML)  :: YEXT_NL(JPGFL-JPNAMED_GFL-JPGHG-JPGRG-JPFORC-JPEZDIAG-JPAERO-JPTRAC-JPERA40-&
416 &                              JPNOGW-JPSLDIA-JPCH4S-JPAEROUT-JPUVP-JPCHEM-JPPHYS) ! Extra fields
417
418! Prognostic convection variables: 6 more namelist components
419TYPE(TYPE_GFL_NAML)  :: YUOM_NL               ! Updraught vert velocity
420TYPE(TYPE_GFL_NAML)  :: YUAL_NL               ! Updraught mesh fraction
421TYPE(TYPE_GFL_NAML)  :: YDOM_NL               ! Downdraught vert velocity
422TYPE(TYPE_GFL_NAML)  :: YDAL_NL               ! Downdraught mesh fraction
423TYPE(TYPE_GFL_NAML)  :: YUEN_NL               ! Updraught entrainment
424TYPE(TYPE_GFL_NAML)  :: YUNEBH_NL             ! Pseudi Hist Conv cloud fraction
425
426END TYPE TYPE_GFLD
427
428! GFL general descriptor
429TYPE(TYPE_GFLD), POINTER :: YGFL => NULL()
430
431END MODULE YOM_YGFL
Note: See TracBrowser for help on using the repository browser.