source: LMDZ6/branches/Ocean_skin/libf/phylmd/phys_output_var_mod.F90 @ 4009

Last change on this file since 4009 was 3740, checked in by lguez, 4 years ago

Send delta temperature to the ocean

The grid of Nemo is finer than the grid of LMDZ. So LMDZ receives from
Oasis a spatial average of bulk SST. If we send to Nemo the interface
temperature computed by LMDZ, it is regridded as a step function
by Oasis and, in Nemo, the difference between bulk SST and interface
temperature has spatial oscillations. To avoid this, we send to Nemo
the difference between bulk SST and interface temperature computed by
LMDZ, instead of the interface temperature.

So, in module cpl_mod, rename cpl_t_int to cpl_delta_temp,
cpl_t_int_2D to cpl_delta_temp_2D. In module oasis, rename
ids_t_int to ids_delta_temp. Change
infosend(ids_delta_temp)%name to "CODTEMP".

In procedure cpl_send_ocean_fields, rename dummy argument
t_int to tsurf_in just for clarity, because this argument is
passed also when activate_ocean_skin /= 2. Add dummy argument
sst_nff. We cannot just replace dummy argument t_int by a dummy
argument that would receive tsurf_in - sst_nff because sst_nff is
not defined when activate_ocean_skin == 0.

In procedure ocean_cpl_noice, add dummy argument sst_nff.

As for interface salinity, we have to send delta temperature from the
previous time step. So we have to transform sst_nff into a state
variable. So move sst_nff from module phys_output_var_mod to
module phys_state_var_mod. Define ysst_nff in procedure
pbl_surface before the call to surf_ocean. Choose a value of
sst_nff for an appearing ocean fraction. Read sst_nff in procedure
phyetat0, write it in procedure phyredem. Change the intent of dummy argument
sst_nff in procedure surf_ocean to inout.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
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(:)      ! 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, ALLOCATABLE, SAVE:: dter(:)
138  ! Temperature variation in the diffusive microlayer, that is
139  ! ocean-air interface temperature minus subskin temperature. In K.
140     
141  REAL, SAVE, ALLOCATABLE:: dser(:)
142  ! Temperature variation in the diffusive microlayer, that is
143  ! subskin temperature minus ocean-air interface temperature. In K.
144
145  REAL, SAVE, ALLOCATABLE:: tkt(:)
146  ! épaisseur (m) de la couche de diffusion thermique (microlayer)
147  ! cool skin thickness
148
149  REAL, SAVE, ALLOCATABLE:: tks(:)
150  ! épaisseur (m) de la couche de diffusion de masse (microlayer)
151 
152  REAL, SAVE, ALLOCATABLE:: taur(:) ! momentum flux due to rain, in Pa
153
154  REAL, SAVE, ALLOCATABLE:: sss(:)
155  ! bulk salinity of the surface layer of the ocean, in ppt
156 
157  !$OMP THREADPRIVATE(dter, dser, tkt, tks, taur, sss)
158
159CONTAINS
160
161  !======================================================================
162  SUBROUTINE phys_output_var_init
163    use dimphy
164    use config_ocean_skin_m, only: activate_ocean_skin
165
166    IMPLICIT NONE
167
168    include "clesphys.h"
169
170    !------------------------------------------------
171
172    allocate(snow_o(klon), zfra_o(klon))
173    allocate(sza_o(klon) )
174    allocate(itau_con(klon))
175    allocate(sens_prec_liq_o(klon,2))
176    allocate(sens_prec_sol_o(klon,2))
177    allocate(lat_prec_liq_o(klon,2))
178    allocate(lat_prec_sol_o(klon,2))
179    sens_prec_liq_o = 0.0 ; sens_prec_sol_o = 0.0
180    lat_prec_liq_o = 0.0 ; lat_prec_sol_o = 0.0
181
182    allocate (bils_ec(klon),bils_ech(klon),bils_tke(klon),bils_diss(klon),bils_kinetic(klon),bils_enthalp(klon),bils_latent(klon))
183    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) &
184  &         , d_h_qw_col(klon), d_h_ql_col(klon), d_h_qs_col(klon), d_h_col(klon))
185    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.
186    d_h_qw_col=0. ; d_h_ql_col=0. ; d_h_qs_col=0. ; d_h_col=0.
187
188    ! Outputs used in cloudth_vert
189    allocate(cloudth_sth(klon,klev))
190    allocate(cloudth_senv(klon,klev))
191    cloudth_sth = 0. ; cloudth_senv = 0.
192    allocate(cloudth_sigmath(klon,klev))
193    allocate(cloudth_sigmaenv(klon,klev))
194    cloudth_sigmath = 0. ; cloudth_sigmaenv = 0.
195
196! Marine
197! Variables de sortie simulateur AIRS
198
199!     if (ok_airs) then
200      allocate (map_prop_hc(klon),map_prop_hist(klon))
201      allocate (alt_tropo(klon))
202      allocate (map_emis_hc(klon),map_iwp_hc(klon),map_deltaz_hc(klon))
203      allocate (map_pcld_hc(klon),map_tcld_hc(klon))
204      allocate (map_emis_hist(klon),map_iwp_hist(klon),map_deltaz_hist(klon))
205      allocate (map_rad_hist(klon))
206      allocate (map_ntot(klon),map_hc(klon),map_hist(klon))
207      allocate (map_Cb(klon),map_ThCi(klon),map_Anv(klon))
208      allocate (map_emis_Cb(klon),map_pcld_Cb(klon),map_tcld_Cb(klon))
209      allocate (map_emis_ThCi(klon),map_pcld_ThCi(klon),map_tcld_ThCi(klon))
210      allocate (map_emis_Anv(klon),map_pcld_Anv(klon),map_tcld_Anv(klon))
211!     endif
212
213    IF (ok_hines) allocate(zustr_gwd_hines(klon), zvstr_gwd_hines(klon))
214    IF (.not.ok_hines.and.ok_gwd_rando) &
215                  allocate(zustr_gwd_front(klon), zvstr_gwd_front(klon))
216    IF (ok_gwd_rando) allocate(zustr_gwd_rando(klon), zvstr_gwd_rando(klon))
217
218    if (activate_ocean_skin >= 1) allocate(dter(klon), dser(klon), tkt(klon), &
219         tks(klon), taur(klon), sss(klon))
220
221  END SUBROUTINE phys_output_var_init
222
223  !======================================================================
224  SUBROUTINE phys_output_var_end
225    USE dimphy
226    IMPLICIT NONE
227
228    include "clesphys.h"
229
230    deallocate(snow_o,zfra_o,itau_con)
231    deallocate(sza_o)
232    deallocate (bils_ec,bils_ech,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent)
233    deallocate (d_qw_col, d_ql_col, d_qs_col, d_qt_col, d_ek_col, d_h_dair_col &
234  &           , d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_col)
235
236    ! Outputs used in cloudth_vert
237    deallocate(cloudth_sth)
238    deallocate(cloudth_senv)
239    deallocate(cloudth_sigmath)
240    deallocate(cloudth_sigmaenv)
241
242! Marine
243! Variables de sortie simulateur AIRS
244
245 !    if (ok_airs) then
246      deallocate (map_prop_hc,map_prop_hist)
247      deallocate (alt_tropo)
248      deallocate (map_emis_hc,map_iwp_hc,map_deltaz_hc)
249      deallocate (map_pcld_hc,map_tcld_hc)
250      deallocate (map_emis_hist,map_iwp_hist,map_deltaz_hist)
251      deallocate (map_rad_hist)
252      deallocate (map_ntot,map_hc,map_hist)
253      deallocate (map_Cb,map_ThCi,map_Anv)
254      deallocate (map_emis_Cb,map_pcld_Cb,map_tcld_Cb)
255      deallocate (map_emis_ThCi,map_pcld_ThCi,map_tcld_ThCi)
256      deallocate (map_emis_Anv,map_pcld_Anv,map_tcld_Anv)
257  !   endif
258
259  END SUBROUTINE phys_output_var_end
260
261END MODULE phys_output_var_mod
Note: See TracBrowser for help on using the repository browser.