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

Last change on this file since 4775 was 4775, checked in by idelkadi, 6 months ago

Correction: update of phylmdiso following modifications linked to the implementation of the double call of Ecrad

File size: 13.9 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
179  !AI. cloud_cover_sw, cloud_cover_sw_s2 from Ecrad (1rt and 2 call)
180  REAL, SAVE, ALLOCATABLE:: cloud_cover_sw(:), cloud_cover_sw_s2(:)
181  !$OMP THREADPRIVATE(cloud_cover_sw, cloud_cover_sw_s2)
182
183CONTAINS
184
185  !======================================================================
186  SUBROUTINE phys_output_var_init
187    use dimphy
188    use config_ocean_skin_m, only: activate_ocean_skin
189
190    IMPLICIT NONE
191
192    include "clesphys.h"
193
194    !------------------------------------------------
195
196    allocate(snow_o(klon), zfra_o(klon))
197    allocate(sza_o(klon) )
198    allocate(itau_con(klon))
199    allocate(sens_prec_liq_o(klon,2))
200    allocate(sens_prec_sol_o(klon,2))
201    allocate(lat_prec_liq_o(klon,2))
202    allocate(lat_prec_sol_o(klon,2))
203    sens_prec_liq_o = 0.0 ; sens_prec_sol_o = 0.0
204    lat_prec_liq_o = 0.0 ; lat_prec_sol_o = 0.0
205
206    allocate (bils_ec(klon),bils_ech(klon),bils_tke(klon),bils_diss(klon),bils_kinetic(klon),bils_enthalp(klon),bils_latent(klon))
207    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) &
208  &         , d_h_qw_col(klon), d_h_ql_col(klon), d_h_qs_col(klon), d_h_qbs_col(klon), d_h_col(klon))
209    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.
210    d_h_qw_col=0. ; d_h_ql_col=0. ; d_h_qs_col=0. ; d_h_qbs_col=0. ; d_h_col=0.
211
212    ! Outputs used in cloudth_vert
213    allocate(cloudth_sth(klon,klev))
214    allocate(cloudth_senv(klon,klev))
215    cloudth_sth = 0. ; cloudth_senv = 0.
216    allocate(cloudth_sigmath(klon,klev))
217    allocate(cloudth_sigmaenv(klon,klev))
218    cloudth_sigmath = 0. ; cloudth_sigmaenv = 0.
219
220! Marine
221! Variables de sortie simulateur AIRS
222
223!     if (ok_airs) then
224      allocate (map_prop_hc(klon),map_prop_hist(klon))
225      allocate (alt_tropo(klon))
226      allocate (map_emis_hc(klon),map_iwp_hc(klon),map_deltaz_hc(klon))
227      allocate (map_pcld_hc(klon),map_tcld_hc(klon))
228      allocate (map_emis_hist(klon),map_iwp_hist(klon),map_deltaz_hist(klon))
229      allocate (map_rad_hist(klon))
230      allocate (map_ntot(klon),map_hc(klon),map_hist(klon))
231      allocate (map_Cb(klon),map_ThCi(klon),map_Anv(klon))
232      allocate (map_emis_Cb(klon),map_pcld_Cb(klon),map_tcld_Cb(klon))
233      allocate (map_emis_ThCi(klon),map_pcld_ThCi(klon),map_tcld_ThCi(klon))
234      allocate (map_emis_Anv(klon),map_pcld_Anv(klon),map_tcld_Anv(klon))
235!     endif
236
237    IF (ok_hines) allocate(zustr_gwd_hines(klon), zvstr_gwd_hines(klon))
238    IF (.not.ok_hines.and.ok_gwd_rando) &
239                  allocate(zustr_gwd_front(klon), zvstr_gwd_front(klon))
240    IF (ok_gwd_rando) allocate(zustr_gwd_rando(klon), zvstr_gwd_rando(klon))
241
242    if (activate_ocean_skin >= 1) allocate(tkt(klon), tks(klon), taur(klon), &
243         sss(klon))
244
245! Sorties de lmdz_cloud_optics_pro
246    ALLOCATE(scdnc(klon, klev))
247    ALLOCATE(cldncl(klon))
248    ALLOCATE(reffclwtop(klon))
249    ALLOCATE(lcc(klon))
250    ALLOCATE(reffclws(klon, klev))
251    ALLOCATE(reffclwc(klon, klev))
252    ALLOCATE(cldnvi(klon))
253    ALLOCATE(lcc3d(klon, klev))
254    ALLOCATE(lcc3dcon(klon, klev))
255    ALLOCATE(lcc3dstra(klon, klev))
256    ALLOCATE(icc3dcon(klon, klev))
257    ALLOCATE(icc3dstra(klon, klev))
258
259    ! cloud_cover_sw, cloud_cover_sw_s2 from Ecrad
260    ALLOCATE(cloud_cover_sw(klon))
261    ALLOCATE(cloud_cover_sw_s2(klon))
262
263  END SUBROUTINE phys_output_var_init
264
265  !======================================================================
266  SUBROUTINE phys_output_var_end
267    USE dimphy
268    IMPLICIT NONE
269
270    include "clesphys.h"
271
272    deallocate(snow_o,zfra_o,itau_con)
273    deallocate(sza_o)
274    deallocate (bils_ec,bils_ech,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
275    deallocate (d_qw_col, d_ql_col, d_qs_col, d_qbs_col, d_qt_col, d_ek_col, d_h_dair_col &
276  &           , d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_qbs_col, d_h_col)
277
278    ! Outputs used in cloudth_vert
279    deallocate(cloudth_sth)
280    deallocate(cloudth_senv)
281    deallocate(cloudth_sigmath)
282    deallocate(cloudth_sigmaenv)
283
284! Marine
285! Variables de sortie simulateur AIRS
286
287 !    if (ok_airs) then
288      deallocate (map_prop_hc,map_prop_hist)
289      deallocate (alt_tropo)
290      deallocate (map_emis_hc,map_iwp_hc,map_deltaz_hc)
291      deallocate (map_pcld_hc,map_tcld_hc)
292      deallocate (map_emis_hist,map_iwp_hist,map_deltaz_hist)
293      deallocate (map_rad_hist)
294      deallocate (map_ntot,map_hc,map_hist)
295      deallocate (map_Cb,map_ThCi,map_Anv)
296      deallocate (map_emis_Cb,map_pcld_Cb,map_tcld_Cb)
297      deallocate (map_emis_ThCi,map_pcld_ThCi,map_tcld_ThCi)
298      deallocate (map_emis_Anv,map_pcld_Anv,map_tcld_Anv)
299  !   endif
300
301    DEALLOCATE(scdnc)
302    DEALLOCATE(cldncl)
303    DEALLOCATE(reffclwtop)
304    DEALLOCATE(lcc)
305    DEALLOCATE(reffclws)
306    DEALLOCATE(reffclwc)
307    DEALLOCATE(cldnvi)
308    DEALLOCATE(lcc3d)
309    DEALLOCATE(lcc3dcon)
310    DEALLOCATE(lcc3dstra)
311    DEALLOCATE(icc3dcon)
312    DEALLOCATE(icc3dstra)
313
314    !AI cloud_cover_sw, cloud_cover_sw_s2 from Ecrad
315    DEALLOCATE(cloud_cover_sw, cloud_cover_sw_s2)
316
317  END SUBROUTINE phys_output_var_end
318
319END MODULE phys_output_var_mod
Note: See TracBrowser for help on using the repository browser.