source: LMDZ6/trunk/libf/phylmdiso/phys_output_var_mod.F90 @ 4703

Last change on this file since 4703 was 4703, checked in by Laurent Fairhead, 9 months ago

Moving around some variable declarations to their right place

File size: 13.5 KB
Line 
1!
2! phys_local_var_mod.F90 1327 2010-03-17 15:33:56Z idelkadi $
3
4MODULE phys_output_var_mod
5
6  USE dimphy
7  ! Variables outputs pour les ecritures des sorties
8  !======================================================================
9  !
10  !
11  !======================================================================
12  ! Declaration des variables
13
14  REAL, SAVE, ALLOCATABLE :: snow_o(:), zfra_o(:)
15  !$OMP THREADPRIVATE(snow_o, zfra_o)
16  REAL, SAVE, ALLOCATABLE :: sza_o(:) ! solar zenithal angle
17  !$OMP THREADPRIVATE(sza_o)
18  INTEGER, SAVE, ALLOCATABLE ::  itau_con(:)       ! Nombre de pas ou rflag <= 1
19  !$OMP THREADPRIVATE(itau_con)
20  REAL, SAVE, ALLOCATABLE :: bils_ec(:) ! Contribution of energy conservation
21  REAL, SAVE, ALLOCATABLE :: bils_ech(:) ! Contribution of energy conservation
22  REAL, SAVE, ALLOCATABLE :: bils_tke(:) ! Contribution of energy conservation
23  REAL, SAVE, ALLOCATABLE :: bils_diss(:) ! Contribution of energy conservation
24  REAL, SAVE, ALLOCATABLE :: bils_kinetic(:) ! bilan de chaleur au sol, kinetic
25  REAL, SAVE, ALLOCATABLE :: bils_enthalp(:) ! bilan de chaleur au sol
26  REAL, SAVE, ALLOCATABLE :: bils_latent(:) ! bilan de chaleur au sol
27  !$OMP THREADPRIVATE(bils_ec,bils_ech,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
28  ! output variables for energy conservation tests, computed in add_phys_tend
29  REAL, SAVE, ALLOCATABLE :: d_qw_col(:)      ! watter vapour mass budget for each column (kg/m2/s)
30  REAL, SAVE, ALLOCATABLE :: d_ql_col(:)      ! liquid watter mass budget for each column (kg/m2/s)
31  REAL, SAVE, ALLOCATABLE :: d_qs_col(:)      ! cloud ice mass budget for each column (kg/m2/s)
32  REAL, SAVE, ALLOCATABLE :: d_qbs_col(:)     ! blowing snow mass budget for each column (kg/m2/s)
33  REAL, SAVE, ALLOCATABLE :: d_qt_col(:)      ! total watter mass budget for each column (kg/m2/s)
34  REAL, SAVE, ALLOCATABLE :: d_ek_col(:)      ! kinetic energy budget for each column (W/m2)
35  REAL, SAVE, ALLOCATABLE :: d_h_dair_col(:)  ! enthalpy budget of dry air for each column (W/m2)
36  REAL, SAVE, ALLOCATABLE :: d_h_qw_col(:)    ! enthalpy budget of watter vapour for each column (W/m2)
37  REAL, SAVE, ALLOCATABLE :: d_h_ql_col(:)    ! enthalpy budget of liquid watter for each column (W/m2)
38  REAL, SAVE, ALLOCATABLE :: d_h_qs_col(:)    ! enthalpy budget of cloud ice  for each column (W/m2)
39  REAL, SAVE, ALLOCATABLE :: d_h_qbs_col(:)    ! enthalpy budget of blowing snow for each column (W/m2)
40  REAL, SAVE, ALLOCATABLE :: d_h_col(:)       ! total enthalpy budget for each column (W/m2)
41  !$OMP THREADPRIVATE(d_qw_col, d_ql_col, d_qs_col, d_qbs_col, d_qt_col, d_ek_col, d_h_dair_col)
42  !$OMP THREADPRIVATE(d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_qbs_col, d_h_col)
43
44  ! Outputs used in cloudth_vert to extract the moments of the horizontal and
45  ! vertical PDFs
46  REAL, SAVE, ALLOCATABLE :: cloudth_sth(:,:),cloudth_senv(:,:)
47  !$OMP THREADPRIVATE(cloudth_sth,cloudth_senv)
48  REAL, SAVE, ALLOCATABLE :: cloudth_sigmath(:,:),cloudth_sigmaenv(:,:)
49  !$OMP THREADPRIVATE(cloudth_sigmath,cloudth_sigmaenv)
50
51! Marine
52! Variables de sortie du simulateur AIRS
53
54  REAL, SAVE, ALLOCATABLE :: map_prop_hc(:),map_prop_hist(:),alt_tropo(:)
55  !$OMP THREADPRIVATE(map_prop_hc,map_prop_hist,alt_tropo)
56  REAL, SAVE, ALLOCATABLE :: map_emis_hc(:),map_iwp_hc(:),map_deltaz_hc(:), &
57                       map_pcld_hc(:),map_tcld_hc(:)
58  !$OMP THREADPRIVATE(map_emis_hc,map_iwp_hc,map_deltaz_hc,map_pcld_hc,map_tcld_hc)
59  REAL, SAVE, ALLOCATABLE :: map_emis_hist(:),map_iwp_hist(:),map_deltaz_hist(:),map_rad_hist(:)         
60  !$OMP THREADPRIVATE(map_emis_hist,map_iwp_hist,map_deltaz_hist,map_rad_hist)
61  REAL, SAVE, ALLOCATABLE :: map_ntot(:),map_hc(:),map_hist(:)
62  REAL, SAVE, ALLOCATABLE :: map_Cb(:),map_ThCi(:),map_Anv(:)
63  !$OMP THREADPRIVATE(map_ntot,map_hc,map_hist,map_Cb,map_ThCi,map_Anv)
64  REAL, SAVE, ALLOCATABLE :: map_emis_Cb(:),map_pcld_Cb(:),map_tcld_Cb(:)
65  REAL, SAVE, ALLOCATABLE :: map_emis_ThCi(:),map_pcld_ThCi(:),map_tcld_ThCi(:)
66  !$OMP THREADPRIVATE(map_emis_Cb,map_pcld_Cb,map_tcld_Cb,map_emis_ThCi)
67  REAL, SAVE, ALLOCATABLE :: map_emis_Anv(:),map_pcld_Anv(:),map_tcld_Anv(:)
68  !$OMP THREADPRIVATE(map_pcld_ThCi,map_tcld_ThCi,map_emis_Anv,map_pcld_Anv,map_tcld_Anv)
69
70  ! variables deplacees de phys_local_var_mod
71  REAL, SAVE, ALLOCATABLE :: scdnc(:,:)
72  !$OMP THREADPRIVATE(scdnc)
73  REAL, SAVE, ALLOCATABLE :: cldncl(:)
74  !$OMP THREADPRIVATE(cldncl)
75  REAL, SAVE, ALLOCATABLE :: reffclwtop(:)
76  !$OMP THREADPRIVATE(reffclwtop)
77  REAL, SAVE, ALLOCATABLE :: lcc(:)
78  !$OMP THREADPRIVATE(lcc)
79  REAL, SAVE, ALLOCATABLE :: reffclws(:,:)
80  !$OMP THREADPRIVATE(reffclws)
81  REAL, SAVE, ALLOCATABLE :: reffclwc(:,:)
82  !$OMP THREADPRIVATE(reffclwc)
83  REAL, SAVE, ALLOCATABLE :: cldnvi(:)
84  !$OMP THREADPRIVATE(cldnvi)
85  REAL, SAVE, ALLOCATABLE :: lcc3d(:,:)
86  !$OMP THREADPRIVATE(lcc3d)
87  REAL, SAVE, ALLOCATABLE :: lcc3dcon(:,:)
88  !$OMP THREADPRIVATE(lcc3dcon)
89  REAL, SAVE, ALLOCATABLE :: lcc3dstra(:,:)
90  !$OMP THREADPRIVATE(lcc3dstra)
91  REAL, SAVE, ALLOCATABLE :: icc3dcon(:,:)
92  !$OMP THREADPRIVATE(icc3dcon)
93  REAL, SAVE, ALLOCATABLE :: icc3dstra(:,:)
94  !$OMP THREADPRIVATE(icc3dstra) 
95   
96
97  ! ug Plein de variables venues de phys_output_mod
98  INTEGER, PARAMETER                           :: nfiles = 10
99  LOGICAL, DIMENSION(nfiles), SAVE             :: clef_files
100  LOGICAL, DIMENSION(nfiles), SAVE             :: clef_stations
101  INTEGER, DIMENSION(nfiles), SAVE             :: lev_files
102  INTEGER, DIMENSION(nfiles), SAVE             :: nid_files
103  INTEGER, DIMENSION(nfiles), SAVE  :: nnid_files
104  !$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files)
105  INTEGER, DIMENSION(nfiles), SAVE :: nnhorim
106
107  INTEGER, DIMENSION(nfiles), SAVE :: nhorim, nvertm
108  INTEGER, DIMENSION(nfiles), SAVE :: nvertap, nvertbp, nvertAlt
109  REAL, DIMENSION(nfiles), SAVE                :: zoutm
110  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE   :: type_ecri
111  !$OMP THREADPRIVATE(nnhorim, nhorim, nvertm, zoutm,type_ecri)
112  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: type_ecri_files, phys_out_filetypes
113  !$OMP THREADPRIVATE(type_ecri_files, phys_out_filetypes)
114  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: phys_out_filenames
115  !$OMP THREADPRIVATE(phys_out_filenames)
116
117  ! swaero_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
118  ! swaerofree_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
119  ! dryaod_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
120  !--OB: this needs to be set to TRUE by default and changed back to FALSE after first radiation call
121  !--    and corrected back to TRUE based on output requests
122  LOGICAL, SAVE                                :: swaerofree_diag=.TRUE.
123  LOGICAL, SAVE                                :: swaero_diag=.TRUE.
124  LOGICAL, SAVE                                :: dryaod_diag=.TRUE.
125  !$OMP THREADPRIVATE(swaerofree_diag, swaero_diag, dryaod_diag)
126  ! ok_4xCO2atm : flag indicates if it is necessary to do a second call of
127  ! radiation code with a 4xCO2 or another different GES to assess SW/LW
128  ! in this case
129  !--IM: as for swaero_diag or dryaod_diag this needs to be set to TRUE by default and
130  !--    changed back to FALSE after first radiation call and corrected back to TRUE
131  !--    based on output requests
132  LOGICAL, SAVE                                :: ok_4xCO2atm=.TRUE.
133  !$OMP THREADPRIVATE(ok_4xCO2atm)
134
135  INTEGER, SAVE:: levmin(nfiles) = 1
136  INTEGER, SAVE:: levmax(nfiles)
137  !$OMP THREADPRIVATE(levmin, levmax)
138
139  REAL, SAVE                :: zdtime_moy
140  !$OMP THREADPRIVATE(zdtime_moy)
141
142  LOGICAL, SAVE :: vars_defined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL
143
144  REAL, allocatable:: zustr_gwd_hines(:), zvstr_gwd_hines(:) ! (klon)
145  REAL, allocatable:: zustr_gwd_front(:), zvstr_gwd_front(:) ! (klon)
146  REAL, allocatable:: zustr_gwd_rando(:), zvstr_gwd_rando(:) ! (klon)
147  !$OMP THREADPRIVATE(zustr_gwd_hines, zvstr_gwd_hines)
148  !$OMP THREADPRIVATE(zustr_gwd_front, zvstr_gwd_front)
149  !$OMP THREADPRIVATE(zustr_gwd_rando, zvstr_gwd_rando)
150
151  TYPE ctrl_out
152     INTEGER,DIMENSION(nfiles)            :: flag
153     CHARACTER(len=20)                    :: name
154     CHARACTER(len=150)                   :: description
155     CHARACTER(len=20)                    :: unit
156     CHARACTER(len=20),DIMENSION(nfiles)  :: type_ecrit
157  END TYPE ctrl_out
158
159  REAL, SAVE, ALLOCATABLE :: sens_prec_liq_o(:,:), sens_prec_sol_o(:,:)
160  REAL, SAVE, ALLOCATABLE :: lat_prec_liq_o(:,:), lat_prec_sol_o(:,:)
161 !$OMP THREADPRIVATE(sens_prec_liq_o, sens_prec_sol_o,lat_prec_liq_o,lat_prec_sol_o)
162
163  ! Ocean-atmosphere interface, subskin ocean and near-surface ocean:
164 
165  REAL, SAVE, ALLOCATABLE:: tkt(:) ! (klon)
166  ! épaisseur (m) de la couche de diffusion thermique (microlayer)
167  ! cool skin thickness
168
169  REAL, SAVE, ALLOCATABLE:: tks(:) ! (klon)
170  ! épaisseur (m) de la couche de diffusion de masse (microlayer)
171 
172  REAL, SAVE, ALLOCATABLE:: taur(:) ! (klon) momentum flux due to rain, in Pa
173
174  REAL, SAVE, ALLOCATABLE:: sss(:) ! (klon)
175  ! bulk salinity of the surface layer of the ocean, in ppt
176 
177  !$OMP THREADPRIVATE(tkt, tks, taur, sss)
178
179CONTAINS
180
181  !======================================================================
182  SUBROUTINE phys_output_var_init
183    use dimphy
184    use config_ocean_skin_m, only: activate_ocean_skin
185
186    IMPLICIT NONE
187
188    include "clesphys.h"
189
190    !------------------------------------------------
191
192    allocate(snow_o(klon), zfra_o(klon))
193    allocate(sza_o(klon) )
194    allocate(itau_con(klon))
195    allocate(sens_prec_liq_o(klon,2))
196    allocate(sens_prec_sol_o(klon,2))
197    allocate(lat_prec_liq_o(klon,2))
198    allocate(lat_prec_sol_o(klon,2))
199    sens_prec_liq_o = 0.0 ; sens_prec_sol_o = 0.0
200    lat_prec_liq_o = 0.0 ; lat_prec_sol_o = 0.0
201
202    allocate (bils_ec(klon),bils_ech(klon),bils_tke(klon),bils_diss(klon),bils_kinetic(klon),bils_enthalp(klon),bils_latent(klon))
203    allocate (d_qw_col(klon), d_ql_col(klon), d_qs_col(klon), d_qbs_col(klon), d_qt_col(klon), d_ek_col(klon), d_h_dair_col(klon) &
204  &         , d_h_qw_col(klon), d_h_ql_col(klon), d_h_qs_col(klon), d_h_qbs_col(klon), d_h_col(klon))
205    d_qw_col=0. ; d_ql_col=0. ; d_qs_col=0. ; d_qbs_col=0. ; d_qt_col=0. ; d_ek_col=0. ; d_h_dair_col =0.
206    d_h_qw_col=0. ; d_h_ql_col=0. ; d_h_qs_col=0. ; d_h_qbs_col=0. ; d_h_col=0.
207
208    ! Outputs used in cloudth_vert
209    allocate(cloudth_sth(klon,klev))
210    allocate(cloudth_senv(klon,klev))
211    cloudth_sth = 0. ; cloudth_senv = 0.
212    allocate(cloudth_sigmath(klon,klev))
213    allocate(cloudth_sigmaenv(klon,klev))
214    cloudth_sigmath = 0. ; cloudth_sigmaenv = 0.
215
216! Marine
217! Variables de sortie simulateur AIRS
218
219!     if (ok_airs) then
220      allocate (map_prop_hc(klon),map_prop_hist(klon))
221      allocate (alt_tropo(klon))
222      allocate (map_emis_hc(klon),map_iwp_hc(klon),map_deltaz_hc(klon))
223      allocate (map_pcld_hc(klon),map_tcld_hc(klon))
224      allocate (map_emis_hist(klon),map_iwp_hist(klon),map_deltaz_hist(klon))
225      allocate (map_rad_hist(klon))
226      allocate (map_ntot(klon),map_hc(klon),map_hist(klon))
227      allocate (map_Cb(klon),map_ThCi(klon),map_Anv(klon))
228      allocate (map_emis_Cb(klon),map_pcld_Cb(klon),map_tcld_Cb(klon))
229      allocate (map_emis_ThCi(klon),map_pcld_ThCi(klon),map_tcld_ThCi(klon))
230      allocate (map_emis_Anv(klon),map_pcld_Anv(klon),map_tcld_Anv(klon))
231!     endif
232
233    IF (ok_hines) allocate(zustr_gwd_hines(klon), zvstr_gwd_hines(klon))
234    IF (.not.ok_hines.and.ok_gwd_rando) &
235                  allocate(zustr_gwd_front(klon), zvstr_gwd_front(klon))
236    IF (ok_gwd_rando) allocate(zustr_gwd_rando(klon), zvstr_gwd_rando(klon))
237
238    if (activate_ocean_skin >= 1) allocate(tkt(klon), tks(klon), taur(klon), &
239         sss(klon))
240
241! Sorties de lmdz_cloud_optics_pro
242    ALLOCATE(scdnc(klon, klev))
243    ALLOCATE(cldncl(klon))
244    ALLOCATE(reffclwtop(klon))
245    ALLOCATE(lcc(klon))
246    ALLOCATE(reffclws(klon, klev))
247    ALLOCATE(reffclwc(klon, klev))
248    ALLOCATE(cldnvi(klon))
249    ALLOCATE(lcc3d(klon, klev))
250    ALLOCATE(lcc3dcon(klon, klev))
251    ALLOCATE(lcc3dstra(klon, klev))
252    ALLOCATE(icc3dcon(klon, klev))
253    ALLOCATE(icc3dstra(klon, klev))
254
255  END SUBROUTINE phys_output_var_init
256
257  !======================================================================
258  SUBROUTINE phys_output_var_end
259    USE dimphy
260    IMPLICIT NONE
261
262    include "clesphys.h"
263
264    deallocate(snow_o,zfra_o,itau_con)
265    deallocate(sza_o)
266    deallocate (bils_ec,bils_ech,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
267    deallocate (d_qw_col, d_ql_col, d_qs_col, d_qbs_col, d_qt_col, d_ek_col, d_h_dair_col &
268  &           , d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_qbs_col, d_h_col)
269
270    ! Outputs used in cloudth_vert
271    deallocate(cloudth_sth)
272    deallocate(cloudth_senv)
273    deallocate(cloudth_sigmath)
274    deallocate(cloudth_sigmaenv)
275
276! Marine
277! Variables de sortie simulateur AIRS
278
279 !    if (ok_airs) then
280      deallocate (map_prop_hc,map_prop_hist)
281      deallocate (alt_tropo)
282      deallocate (map_emis_hc,map_iwp_hc,map_deltaz_hc)
283      deallocate (map_pcld_hc,map_tcld_hc)
284      deallocate (map_emis_hist,map_iwp_hist,map_deltaz_hist)
285      deallocate (map_rad_hist)
286      deallocate (map_ntot,map_hc,map_hist)
287      deallocate (map_Cb,map_ThCi,map_Anv)
288      deallocate (map_emis_Cb,map_pcld_Cb,map_tcld_Cb)
289      deallocate (map_emis_ThCi,map_pcld_ThCi,map_tcld_ThCi)
290      deallocate (map_emis_Anv,map_pcld_Anv,map_tcld_Anv)
291  !   endif
292
293    DEALLOCATE(scdnc)
294    DEALLOCATE(cldncl)
295    DEALLOCATE(reffclwtop)
296    DEALLOCATE(lcc)
297    DEALLOCATE(reffclws)
298    DEALLOCATE(reffclwc)
299    DEALLOCATE(cldnvi)
300    DEALLOCATE(lcc3d)
301    DEALLOCATE(lcc3dcon)
302    DEALLOCATE(lcc3dstra)
303    DEALLOCATE(icc3dcon)
304    DEALLOCATE(icc3dstra)
305
306  END SUBROUTINE phys_output_var_end
307
308END MODULE phys_output_var_mod
Note: See TracBrowser for help on using the repository browser.