GCC Code Coverage Report


Directory: ./
File: rad/type_gfls.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 0 1 0.0%
Branches: 0 2 0.0%

Line Branch Exec Source
1 MODULE TYPE_GFLS
2
3 USE PARKIND1 ,ONLY : JPIM ,JPRB
4
5 IMPLICIT NONE
6 SAVE
7
8 !-------------------------------------------------------------------------
9 ! Derived types for describing the GFL structure. The descriptors themselves
10 ! (YGFL and YGFLC) can be found in module yom_ygfl.F90.
11 !-------------------------------------------------------------------------
12 ! Modifications:
13 ! 03/07/09 C. Fischer - add Arome/Aladin attributes
14 ! 03/10/01 C. Moussy - add Arome/Aladin attributes coupling
15 ! 03/10/31 M. Tudor - add physics tendencies for predictor-corrector
16 ! 05/10/10 J. Haseler - switch for I/O to trajectory structure
17 ! 2004-Nov F. Vana - update of CSLINT attribute
18 ! 20-Feb-2005 Vivoda - 3TL Eul PC scheme (GFLPC)
19
20 TYPE TYPE_GFLD
21 ! Overall descriptor,dimensioning etc.
22 INTEGER(KIND=JPIM) :: NUMFLDS ! Number of GFL fields
23 INTEGER(KIND=JPIM) :: NDERS ! Number of horizontal derivatives fields
24 INTEGER(KIND=JPIM) :: NUMSPFLDS ! Number of spectrally represented GFL fields
25 INTEGER(KIND=JPIM) :: NUMGPFLDS ! Number of grid-point GFL fields
26 INTEGER(KIND=JPIM) :: NUMFLDS9 ! Number of GFL fields in (t-dt) part
27 INTEGER(KIND=JPIM) :: NUMFLDS1 ! Number of GFL fields in (t+dt) array
28 INTEGER(KIND=JPIM) :: NUMSPFLDS1 ! Number of spectrally represented GFL fields (t+dt)
29 INTEGER(KIND=JPIM) :: NUMFLDS5 ! Number of GFL fields (trajectory)
30 INTEGER(KIND=JPIM) :: NUMFLDSPHY ! Number of GFL fields (phys.)
31 INTEGER(KIND=JPIM) :: NUMFLDS_SPL ! Number of GFL fields (S.L. spline interpolation)
32 INTEGER(KIND=JPIM) :: NUMFLDS_SL1 ! Number of GFL fields in S.L. buffer 1
33 INTEGER(KIND=JPIM) :: NUMFLDSPC ! Number of GFL fields (predictor/corrector)
34 INTEGER(KIND=JPIM) :: NDIM ! Dimension of main array holding GFL fields(GFL)
35 INTEGER(KIND=JPIM) :: NUMFLDSPT ! Number of GFL fields (phy. tend.)
36 INTEGER(KIND=JPIM) :: NDIM0 ! Dimension of t0 part of GFL
37 INTEGER(KIND=JPIM) :: NDIM9 ! Dimension of t-dt part of GFL
38 INTEGER(KIND=JPIM) :: NDIM1 ! Dimension of t+dt array (GFLT1)
39 INTEGER(KIND=JPIM) :: NDIM5 ! Dimension of traj. GFL array (GFL5)
40 INTEGER(KIND=JPIM) :: NDIMSLP ! Diminsion of S.L. phys. GFL array (GFLSLP)
41 INTEGER(KIND=JPIM) :: NDIM_SPL ! Dim. of arrays holding GFL fields (S.L.spline int.)
42 INTEGER(KIND=JPIM) :: NDIMPT ! Dimension of phy. tend. GFL array (GFLPT)
43 INTEGER(KIND=JPIM) :: NDIMPC ! Dimension of iterative scheme auxiliary array (GFLPC)
44
45 END TYPE TYPE_GFLD
46
47 TYPE TYPE_GFL_COMP ! Individual field descriptor
48
49 CHARACTER(LEN=16) :: CNAME ! ARPEGE field name
50 INTEGER(KIND=JPIM) :: IGRBCODE ! GRIB code
51 LOGICAL :: LADV ! Field advected or not
52 INTEGER(KIND=JPIM) :: NREQIN ! 1 if field requiered in input, 0 if not, -1 if initialised
53 ! with a reference value REFVALI
54 LOGICAL :: LREQOUT ! T if field requiered in output
55 LOGICAL :: LGPINGP ! GP field input as GP
56 LOGICAL :: LGP ! Field exists and of grid-point type
57 LOGICAL :: LSP ! Field exists and of spectral type
58 LOGICAL :: LCDERS ! Derivatives required (spectral only)
59 LOGICAL :: LACTIVE ! Field in use
60 LOGICAL :: LTHERMACT ! Field thermodynamically active
61 REAL(KIND=JPRB) :: R
62 REAL(KIND=JPRB) :: RCP
63 LOGICAL :: LT9 ! Field in t-dt GFL
64 LOGICAL :: LT1 ! Field in t+dt GFL
65 LOGICAL :: LT5 ! Field in trajectory GFL
66 LOGICAL :: LPHY ! Field in physics GFL
67 LOGICAL :: LPT ! Field in PC phy. tend. GFL (GFLPT)
68 LOGICAL :: LTRAJIO ! Field written to and from trajectory structure
69 LOGICAL :: LPC ! Field in predictor/corrector time stepping (GFLPC)
70 REAL(KIND=JPRB) :: REFVALI ! Reference value for init, used in case NREQIN==-1
71 ! LAM specific attributes (Arome/Aladin)
72 LOGICAL :: LADJUST0 ! True if field is thermodynamically adjusted at t
73 ! (immediatly after inverse spectral transforms)
74 LOGICAL :: LADJUST1 ! True if field is thermodynamically adjusted at t+dt
75 ! (after SL interpolations and NL residuals)
76 INTEGER(KIND=JPIM) :: NCOUPLING ! 1 if field is coupled by Davies relaxation, 0 if not,
77 ! -1 if coupled with reference value for coupling REFVALC
78 REAL(KIND=JPRB) :: REFVALC ! Reference value for coupling, used in case NCOUPLING==-1
79 LOGICAL :: LBIPER ! True if field must be biperiodised inside the transforms
80 ! End LAM specific attributes (Arome/Aladin)
81 CHARACTER(LEN=12) :: CSLINT ! S.L interpolaion "type"
82 INTEGER(KIND=JPIM) :: MP ! Basic field "pointer"
83 INTEGER(KIND=JPIM) :: MPL ! zonal derivative "pointer"
84 INTEGER(KIND=JPIM) :: MPM ! Meridional derivative "pointer"
85 INTEGER(KIND=JPIM) :: MP9 ! Basic field "pointer" t-dt
86 INTEGER(KIND=JPIM) :: MP9_PH ! Basic field "pointer" for Physics
87 INTEGER(KIND=JPIM) :: MP1 ! Basic field "pointer" t+dt
88 INTEGER(KIND=JPIM) :: MP5 ! Basic field "pointer" trajectory
89 INTEGER(KIND=JPIM) :: MP5L ! zonal derivative "pointer" trajectory
90 INTEGER(KIND=JPIM) :: MP5M ! Meridional derivative "pointer" trajectory
91 INTEGER(KIND=JPIM) :: MPSLP ! Basic field "pointer" physics
92 INTEGER(KIND=JPIM) :: MPSP ! Basic field "pointer" spectral space
93 INTEGER(KIND=JPIM) :: MP_SPL ! Basic field "pointer" spline interpolation
94 INTEGER(KIND=JPIM) :: MP_SL1 ! Basic field "pointer" in SLBUF1
95 INTEGER(KIND=JPIM) :: MP_SLX ! Basic field "pointer" in SLBUF1 for CPG_PT
96 INTEGER(KIND=JPIM) :: MPPT ! Physics tendency "pointer"
97 INTEGER(KIND=JPIM) :: MPPC ! Predictor/corrector auxiliary array "pointer"
98
99 TYPE(TYPE_GFL_COMP),POINTER :: PREVIOUS ! Pointer to previously def. field
100
101 END TYPE TYPE_GFL_COMP
102
103 TYPE TYPE_GFL_NAML ! Individual field descriptor for namelist input
104
105 CHARACTER(LEN=16) :: CNAME ! ARPEGE field name
106 INTEGER(KIND=JPIM) :: IGRBCODE ! GRIB code
107 INTEGER(KIND=JPIM) :: NREQIN ! 1 if field required in input, 0 if not, -1 if initialised
108 ! with a reference value REFVALI
109 REAL(KIND=JPRB) :: REFVALI ! Reference value for initialisation, used in case NREQIN==-1
110 LOGICAL :: LREQOUT ! T if field requiered in output
111 LOGICAL :: LGPINGP ! GP field input as GP
112 LOGICAL :: LGP ! Field exists and of grid-point type
113 LOGICAL :: LSP ! Field exists and of spectral type
114 LOGICAL :: LCDERS ! Derivatives required (spectral only)
115 LOGICAL :: LT9 ! Field in t-dt GFL
116 LOGICAL :: LT1 ! Field in t+dt GFL
117 LOGICAL :: LT5 ! Field in trajectory GFL
118 LOGICAL :: LPHY ! Field with physics tendencies GFL
119 LOGICAL :: LPT ! Field in PC physics tendency GFLPT
120 LOGICAL :: LTRAJIO ! Field written to and from trajectory structure
121 LOGICAL :: LPC ! Field in predictor/corrector time stepping GFLPC
122 LOGICAL :: LADV ! Field advected or not
123
124 LOGICAL :: LQM ! quasi-monotonous interpolation for field
125 LOGICAL :: LQMH ! quasi-monotonous interpolation in horizontal for field
126 LOGICAL :: LSLHD ! Semi-lagrangian horizontal diffusion used for fiels
127 LOGICAL :: LRSPLINE ! 12 points spline interpolation used for field
128 LOGICAL :: LHV ! Hermite vertical interpolation used for field (only ozone sofar)
129 LOGICAL :: LVSPLIP ! vertical spline interpolation used for field (only ozone sofar)
130 INTEGER(KIND=JPIM) :: NCOUPLING ! 1 if field is coupled by Davies relaxation, 0 if not,
131 ! -1 if coupled with reference value for coupling REFVALC
132 REAL(KIND=JPRB) :: REFVALC ! Reference value for coupling, used in case
133 ! NCOUPLING==-1
134 END TYPE TYPE_GFL_NAML
135
136 !-------------------------------------------------------------------------
137 END MODULE TYPE_GFLS
138