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

Last change on this file since 4622 was 4523, checked in by evignon, 14 months ago

merge de la branche blowing snow vers la trunk
premiere tentative
Etienne

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