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

Last change on this file since 4441 was 4374, checked in by lguez, 19 months ago

Report modifications from phylmd into phylmdiso

Report modifications of revision 4370 from phylmd into phylmdiso.

File size: 11.6 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(:)      ! solid watter mass budget for each column (kg/m2/s)
32  REAL, SAVE, ALLOCATABLE :: d_qt_col(:)      ! total watter mass budget for each column (kg/m2/s)
33  REAL, SAVE, ALLOCATABLE :: d_ek_col(:)      ! kinetic energy budget for each column (W/m2)
34  REAL, SAVE, ALLOCATABLE :: d_h_dair_col(:)  ! enthalpy budget of dry air for each column (W/m2)
35  REAL, SAVE, ALLOCATABLE :: d_h_qw_col(:)    ! enthalpy budget of watter vapour for each column (W/m2)
36  REAL, SAVE, ALLOCATABLE :: d_h_ql_col(:)    ! enthalpy budget of liquid watter for each column (W/m2)
37  REAL, SAVE, ALLOCATABLE :: d_h_qs_col(:)    ! enthalpy budget of solid watter  for each column (W/m2)
38  REAL, SAVE, ALLOCATABLE :: d_h_col(:)       ! total enthalpy budget for each column (W/m2)
39  !$OMP THREADPRIVATE(d_qw_col, d_ql_col, d_qs_col, d_qt_col, d_ek_col, d_h_dair_col)
40  !$OMP THREADPRIVATE(d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_col)
41
42  ! Outputs used in cloudth_vert to extract the moments of the horizontal and
43  ! vertical PDFs
44  REAL, SAVE, ALLOCATABLE :: cloudth_sth(:,:),cloudth_senv(:,:)
45  !$OMP THREADPRIVATE(cloudth_sth,cloudth_senv)
46  REAL, SAVE, ALLOCATABLE :: cloudth_sigmath(:,:),cloudth_sigmaenv(:,:)
47  !$OMP THREADPRIVATE(cloudth_sigmath,cloudth_sigmaenv)
48
49! Marine
50! Variables de sortie du simulateur AIRS
51
52  REAL, SAVE, ALLOCATABLE :: map_prop_hc(:),map_prop_hist(:),alt_tropo(:)
53  !$OMP THREADPRIVATE(map_prop_hc,map_prop_hist,alt_tropo)
54  REAL, SAVE, ALLOCATABLE :: map_emis_hc(:),map_iwp_hc(:),map_deltaz_hc(:), &
55                       map_pcld_hc(:),map_tcld_hc(:)
56  !$OMP THREADPRIVATE(map_emis_hc,map_iwp_hc,map_deltaz_hc,map_pcld_hc,map_tcld_hc)
57  REAL, SAVE, ALLOCATABLE :: map_emis_hist(:),map_iwp_hist(:),map_deltaz_hist(:),map_rad_hist(:)         
58  !$OMP THREADPRIVATE(map_emis_hist,map_iwp_hist,map_deltaz_hist,map_rad_hist)
59  REAL, SAVE, ALLOCATABLE :: map_ntot(:),map_hc(:),map_hist(:)
60  REAL, SAVE, ALLOCATABLE :: map_Cb(:),map_ThCi(:),map_Anv(:)
61  !$OMP THREADPRIVATE(map_ntot,map_hc,map_hist,map_Cb,map_ThCi,map_Anv)
62  REAL, SAVE, ALLOCATABLE :: map_emis_Cb(:),map_pcld_Cb(:),map_tcld_Cb(:)
63  REAL, SAVE, ALLOCATABLE :: map_emis_ThCi(:),map_pcld_ThCi(:),map_tcld_ThCi(:)
64  !$OMP THREADPRIVATE(map_emis_Cb,map_pcld_Cb,map_tcld_Cb,map_emis_ThCi)
65  REAL, SAVE, ALLOCATABLE :: map_emis_Anv(:),map_pcld_Anv(:),map_tcld_Anv(:)
66  !$OMP THREADPRIVATE(map_pcld_ThCi,map_tcld_ThCi,map_emis_Anv,map_pcld_Anv,map_tcld_Anv)             
67   
68
69  ! ug Plein de variables venues de phys_output_mod
70  INTEGER, PARAMETER                           :: nfiles = 10
71  LOGICAL, DIMENSION(nfiles), SAVE             :: clef_files
72  LOGICAL, DIMENSION(nfiles), SAVE             :: clef_stations
73  INTEGER, DIMENSION(nfiles), SAVE             :: lev_files
74  INTEGER, DIMENSION(nfiles), SAVE             :: nid_files
75  INTEGER, DIMENSION(nfiles), SAVE  :: nnid_files
76  !$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files)
77  INTEGER, DIMENSION(nfiles), SAVE :: nnhorim
78
79  INTEGER, DIMENSION(nfiles), SAVE :: nhorim, nvertm
80  INTEGER, DIMENSION(nfiles), SAVE :: nvertap, nvertbp, nvertAlt
81  REAL, DIMENSION(nfiles), SAVE                :: zoutm
82  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE   :: type_ecri
83  !$OMP THREADPRIVATE(nnhorim, nhorim, nvertm, zoutm,type_ecri)
84  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: type_ecri_files, phys_out_filetypes
85  !$OMP THREADPRIVATE(type_ecri_files, phys_out_filetypes)
86  CHARACTER(LEN=20), DIMENSION(nfiles), SAVE  :: phys_out_filenames
87  !$OMP THREADPRIVATE(phys_out_filenames)
88
89  ! swaero_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
90  ! swaerofree_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
91  ! dryaod_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
92  !--OB: this needs to be set to TRUE by default and changed back to FALSE after first radiation call
93  !--    and corrected back to TRUE based on output requests
94  LOGICAL, SAVE                                :: swaerofree_diag=.TRUE.
95  LOGICAL, SAVE                                :: swaero_diag=.TRUE.
96  LOGICAL, SAVE                                :: dryaod_diag=.TRUE.
97  !$OMP THREADPRIVATE(swaerofree_diag, swaero_diag, dryaod_diag)
98  ! ok_4xCO2atm : flag indicates if it is necessary to do a second call of
99  ! radiation code with a 4xCO2 or another different GES to assess SW/LW
100  ! in this case
101  !--IM: as for swaero_diag or dryaod_diag this needs to be set to TRUE by default and
102  !--    changed back to FALSE after first radiation call and corrected back to TRUE
103  !--    based on output requests
104  LOGICAL, SAVE                                :: ok_4xCO2atm=.TRUE.
105  !$OMP THREADPRIVATE(ok_4xCO2atm)
106
107  INTEGER, SAVE:: levmin(nfiles) = 1
108  INTEGER, SAVE:: levmax(nfiles)
109  !$OMP THREADPRIVATE(levmin, levmax)
110
111  REAL, SAVE                :: zdtime_moy
112  !$OMP THREADPRIVATE(zdtime_moy)
113
114  LOGICAL, SAVE :: vars_defined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL
115
116  REAL, allocatable:: zustr_gwd_hines(:), zvstr_gwd_hines(:) ! (klon)
117  REAL, allocatable:: zustr_gwd_front(:), zvstr_gwd_front(:) ! (klon)
118  REAL, allocatable:: zustr_gwd_rando(:), zvstr_gwd_rando(:) ! (klon)
119  !$OMP THREADPRIVATE(zustr_gwd_hines, zvstr_gwd_hines)
120  !$OMP THREADPRIVATE(zustr_gwd_front, zvstr_gwd_front)
121  !$OMP THREADPRIVATE(zustr_gwd_rando, zvstr_gwd_rando)
122
123  TYPE ctrl_out
124     INTEGER,DIMENSION(nfiles)            :: flag
125     CHARACTER(len=20)                    :: name
126     CHARACTER(len=150)                   :: description
127     CHARACTER(len=20)                    :: unit
128     CHARACTER(len=20),DIMENSION(nfiles)  :: type_ecrit
129  END TYPE ctrl_out
130
131  REAL, SAVE, ALLOCATABLE :: sens_prec_liq_o(:,:), sens_prec_sol_o(:,:)
132  REAL, SAVE, ALLOCATABLE :: lat_prec_liq_o(:,:), lat_prec_sol_o(:,:)
133 !$OMP THREADPRIVATE(sens_prec_liq_o, sens_prec_sol_o,lat_prec_liq_o,lat_prec_sol_o)
134
135  ! Ocean-atmosphere interface, subskin ocean and near-surface ocean:
136 
137  REAL, SAVE, ALLOCATABLE:: tkt(:) ! (klon)
138  ! épaisseur (m) de la couche de diffusion thermique (microlayer)
139  ! cool skin thickness
140
141  REAL, SAVE, ALLOCATABLE:: tks(:) ! (klon)
142  ! épaisseur (m) de la couche de diffusion de masse (microlayer)
143 
144  REAL, SAVE, ALLOCATABLE:: taur(:) ! (klon) momentum flux due to rain, in Pa
145
146  REAL, SAVE, ALLOCATABLE:: sss(:) ! (klon)
147  ! bulk salinity of the surface layer of the ocean, in ppt
148 
149  !$OMP THREADPRIVATE(tkt, tks, taur, sss)
150
151CONTAINS
152
153  !======================================================================
154  SUBROUTINE phys_output_var_init
155    use dimphy
156    use config_ocean_skin_m, only: activate_ocean_skin
157
158    IMPLICIT NONE
159
160    include "clesphys.h"
161
162    !------------------------------------------------
163
164    allocate(snow_o(klon), zfra_o(klon))
165    allocate(sza_o(klon) )
166    allocate(itau_con(klon))
167    allocate(sens_prec_liq_o(klon,2))
168    allocate(sens_prec_sol_o(klon,2))
169    allocate(lat_prec_liq_o(klon,2))
170    allocate(lat_prec_sol_o(klon,2))
171    sens_prec_liq_o = 0.0 ; sens_prec_sol_o = 0.0
172    lat_prec_liq_o = 0.0 ; lat_prec_sol_o = 0.0
173
174    allocate (bils_ec(klon),bils_ech(klon),bils_tke(klon),bils_diss(klon),bils_kinetic(klon),bils_enthalp(klon),bils_latent(klon))
175    allocate (d_qw_col(klon), d_ql_col(klon), d_qs_col(klon), d_qt_col(klon), d_ek_col(klon), d_h_dair_col(klon) &
176  &         , d_h_qw_col(klon), d_h_ql_col(klon), d_h_qs_col(klon), d_h_col(klon))
177    d_qw_col=0. ; d_ql_col=0. ; d_qs_col=0. ; d_qt_col=0. ; d_ek_col=0. ; d_h_dair_col =0.
178    d_h_qw_col=0. ; d_h_ql_col=0. ; d_h_qs_col=0. ; d_h_col=0.
179
180    ! Outputs used in cloudth_vert
181    allocate(cloudth_sth(klon,klev))
182    allocate(cloudth_senv(klon,klev))
183    cloudth_sth = 0. ; cloudth_senv = 0.
184    allocate(cloudth_sigmath(klon,klev))
185    allocate(cloudth_sigmaenv(klon,klev))
186    cloudth_sigmath = 0. ; cloudth_sigmaenv = 0.
187
188! Marine
189! Variables de sortie simulateur AIRS
190
191!     if (ok_airs) then
192      allocate (map_prop_hc(klon),map_prop_hist(klon))
193      allocate (alt_tropo(klon))
194      allocate (map_emis_hc(klon),map_iwp_hc(klon),map_deltaz_hc(klon))
195      allocate (map_pcld_hc(klon),map_tcld_hc(klon))
196      allocate (map_emis_hist(klon),map_iwp_hist(klon),map_deltaz_hist(klon))
197      allocate (map_rad_hist(klon))
198      allocate (map_ntot(klon),map_hc(klon),map_hist(klon))
199      allocate (map_Cb(klon),map_ThCi(klon),map_Anv(klon))
200      allocate (map_emis_Cb(klon),map_pcld_Cb(klon),map_tcld_Cb(klon))
201      allocate (map_emis_ThCi(klon),map_pcld_ThCi(klon),map_tcld_ThCi(klon))
202      allocate (map_emis_Anv(klon),map_pcld_Anv(klon),map_tcld_Anv(klon))
203!     endif
204
205    IF (ok_hines) allocate(zustr_gwd_hines(klon), zvstr_gwd_hines(klon))
206    IF (.not.ok_hines.and.ok_gwd_rando) &
207                  allocate(zustr_gwd_front(klon), zvstr_gwd_front(klon))
208    IF (ok_gwd_rando) allocate(zustr_gwd_rando(klon), zvstr_gwd_rando(klon))
209
210    if (activate_ocean_skin >= 1) allocate(tkt(klon), tks(klon), taur(klon), &
211         sss(klon))
212
213  END SUBROUTINE phys_output_var_init
214
215  !======================================================================
216  SUBROUTINE phys_output_var_end
217    USE dimphy
218    IMPLICIT NONE
219
220    include "clesphys.h"
221
222    deallocate(snow_o,zfra_o,itau_con)
223    deallocate(sza_o)
224    deallocate (bils_ec,bils_ech,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
225    deallocate (d_qw_col, d_ql_col, d_qs_col, d_qt_col, d_ek_col, d_h_dair_col &
226  &           , d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_col)
227
228    ! Outputs used in cloudth_vert
229    deallocate(cloudth_sth)
230    deallocate(cloudth_senv)
231    deallocate(cloudth_sigmath)
232    deallocate(cloudth_sigmaenv)
233
234! Marine
235! Variables de sortie simulateur AIRS
236
237 !    if (ok_airs) then
238      deallocate (map_prop_hc,map_prop_hist)
239      deallocate (alt_tropo)
240      deallocate (map_emis_hc,map_iwp_hc,map_deltaz_hc)
241      deallocate (map_pcld_hc,map_tcld_hc)
242      deallocate (map_emis_hist,map_iwp_hist,map_deltaz_hist)
243      deallocate (map_rad_hist)
244      deallocate (map_ntot,map_hc,map_hist)
245      deallocate (map_Cb,map_ThCi,map_Anv)
246      deallocate (map_emis_Cb,map_pcld_Cb,map_tcld_Cb)
247      deallocate (map_emis_ThCi,map_pcld_ThCi,map_tcld_ThCi)
248      deallocate (map_emis_Anv,map_pcld_Anv,map_tcld_Anv)
249  !   endif
250
251  END SUBROUTINE phys_output_var_end
252
253END MODULE phys_output_var_mod
Note: See TracBrowser for help on using the repository browser.