source: trunk/LMDZ.GENERIC/libf/phystd/phys_state_var_mod.F90 @ 3194

Last change on this file since 3194 was 3100, checked in by bhatnags, 2 years ago

Generic-PCM

This commit updates the slab ocean module to a parallelisable dynamic slab ocean module. This is particularly relevant if you want to be able to use oceanic heat transport in parallel mode.

It has the following features:

(a) Computes sea ice creation and evolution.
(b) Snow has thermodynamic properties.
(c) Computes oceanic horizontal transport (diffusion & surface-wind driven Ekman transport).
(d) Can be used in parallel mode.

Required callphys.def flags:
The slab ocean and its dependencies can be activated with the following flags (already added to deftank):
## Ocean options
## ~
# Model slab-ocean (Main flag for slab ocean)
ok_slab_ocean = .true.
# The following flags can only be set to true if ok_slab_ocean is true
# Ekman transport
slab_ekman = .true.
# Ekman zonal advection
slab_ekman_zonadv = .true.
# Horizontal diffusion (default coef_hdiff=25000., can be changed)
slab_hdiff = .true.
# Slab-ocean timestep (in physics timesteps)
cpl_pas = 1
# Gent-McWilliams? Scheme (can only be true if slab_ekman is true)
slab_gm = .true.

Notes:
In the current state, the model crashes if moistadjustment = .true. Unsure whether this is due to the slab or is an inherent issue with moistadj (under investigation).

SB and EM

File size: 14.1 KB
Line 
1!
2! $Id: phys_state_var_mod.F90 1670 2012-10-17 08:42:04Z idelkadi $
3!
4      MODULE phys_state_var_mod
5! Variables sauvegardees pour le startphy.nc
6!======================================================================
7!
8!
9!======================================================================
10! Declaration des variables
11      USE dimphy, only : klon,klev
12      USE comsoil_h, only : nsoilmx
13      use comsaison_h, only: mu0, fract
14      use radcommon_h, only: glat
15!      use slab_ice_h, only : noceanmx
16      USE ocean_slab_mod, ONLY: nslay
17      USE radinc_h, only : L_NSPECTI, L_NSPECTV,naerkind
18      use surfdat_h, only: phisfi, albedodat,  &
19                        zmea, zstd, zsig, zgam, zthe
20      use turb_mod, only: q2,sensibFlux,wstar,ustar,tstar,hfmax_th,zmax_th
21      use nonoro_gwd_ran_mod, only: ini_nonoro_gwd_ran, end_nonoro_gwd_ran
22
23      real,allocatable,dimension(:,:),save :: ztprevious ! Previous loop Atmospheric Temperature (K)
24! Useful for Dynamical Heating calculation.
25      real,allocatable,dimension(:,:),save :: zuprevious
26!$OMP THREADPRIVATE(ztprevious,zuprevious)
27
28      real, dimension(:),allocatable,save ::  tsurf                ! Surface temperature (K).
29      real, dimension(:,:),allocatable,save ::  tsoil              ! Sub-surface temperatures (K).
30      real, dimension(:,:),allocatable,save :: albedo              ! Surface Spectral albedo. By MT2015.
31      real, dimension(:),allocatable,save :: albedo_equivalent     ! Spectral Mean albedo.
32      real, dimension(:),allocatable,save :: albedo_equivalent1     ! Spectral Mean albedo clear sky.
33      real, dimension(:),allocatable,save :: albedo_snow_SPECTV    ! Snow Spectral albedo.
34      real, dimension(:),allocatable,save :: albedo_co2_ice_SPECTV ! CO2 ice Spectral albedo.
35!$OMP THREADPRIVATE(tsurf,tsoil,albedo,albedo_equivalent,albedo_equivalent1,albedo_snow_SPECTV,albedo_co2_ice_SPECTV)
36
37      real,dimension(:),allocatable,save :: albedo_bareground ! Bare Ground Albedo. By MT 2015.
38      real,dimension(:),allocatable,save :: rnat              ! Defines the type of the grid (ocean,continent,...). By BC.
39!$OMP THREADPRIVATE(albedo_bareground,rnat)
40
41      real,dimension(:),allocatable,save :: emis        ! Thermal IR surface emissivity.
42      real,dimension(:,:),allocatable,save :: dtrad     ! Net atmospheric radiative heating rate (K.s-1).
43      real,dimension(:),allocatable,save :: fluxrad_sky ! Radiative flux from sky absorbed by surface (W.m-2).
44      real,dimension(:),allocatable,save :: fluxrad     ! Net radiative surface flux (W.m-2).
45      real,dimension(:),allocatable,save :: capcal      ! Surface heat capacity (J m-2 K-1).
46      real,dimension(:),allocatable,save :: fluxgrd     ! Surface conduction flux (W.m-2).
47      real,dimension(:,:),allocatable,save :: qsurf     ! Tracer on surface (e.g. kg.m-2).
48!$OMP THREADPRIVATE(emis,dtrad,fluxrad_sky,fluxrad,capcal,fluxgrd,qsurf)
49
50      ! FOR DIAGNOSTIC :
51
52      real,dimension(:),allocatable,save :: fluxsurf_lw     ! Incident Long Wave (IR) surface flux (W.m-2).
53      real,dimension(:),allocatable,save :: fluxsurf_lw1     ! Incident Long Wave (IR) surface flux (W.m-2) clear sky.
54      real,dimension(:),allocatable,save :: fluxsurf_sw     ! Incident Short Wave (stellar) surface flux (W.m-2).
55      real,dimension(:),allocatable,save :: fluxsurf_sw1     ! Incident Short Wave (stellar) surface flux (W.m-2) clear sky.
56      real,dimension(:),allocatable,save :: fluxsurfabs_sw  ! Absorbed Short Wave (stellar) flux by the surface (W.m-2).
57!$OMP THREADPRIVATE(fluxsurf_lw,fluxsurf_lw1,fluxsurf_sw,fluxsurf_sw1,fluxsurfabs_sw)
58
59      real,dimension(:),allocatable,save :: fluxtop_lw      ! Outgoing LW (IR) flux to space (W.m-2).
60      real,dimension(:),allocatable,save :: fluxtop_lw1      ! Outgoing LW (IR) flux to space (W.m-2) clear sky.
61      real,dimension(:),allocatable,save :: fluxabs_sw      ! Absorbed SW (stellar) flux (W.m-2).
62      real,dimension(:),allocatable,save :: fluxabs_sw1      ! Absorbed SW (stellar) flux (W.m-2) clear sky.
63      real,dimension(:),allocatable,save :: fluxtop_dn      ! Incoming SW (stellar) radiation at the top of the atmosphere (W.m-2).
64      real,dimension(:),allocatable,save :: fluxdyn         ! Horizontal heat transport by dynamics (W.m-2).
65!$OMP THREADPRIVATE(fluxtop_lw,fluxtop_lw1,fluxabs_sw,fluxabs_sw1,fluxtop_dn,fluxdyn)
66
67      real,dimension(:,:),allocatable,save :: OLR_nu        ! Outgoing LW radiation in each band (Normalized to the band width (W/m2/cm-1)).
68      real,dimension(:,:),allocatable,save :: OSR_nu        ! Outgoing SW radiation in each band (Normalized to the band width (W/m2/cm-1)).
69      real,dimension(:,:),allocatable,save :: GSR_nu        ! Surface SW (or 'Ground' SW) radiation in each band (Normalized to the band width (W/m2/cm-1)).
70      real,dimension(:,:),allocatable,save :: zdtlw         ! LW heating tendencies (K/s).
71      real,dimension(:,:),allocatable,save :: zdtsw         ! SW heating tendencies (K/s).
72      !real,dimension(:),allocatable,save :: sensibFlux      ! Turbulent flux given by the atmosphere to the surface (W.m-2).
73!$OMP THREADPRIVATE(OLR_nu,OSR_nu,GSR_nu,zdtlw,zdtsw)
74
75      real,dimension(:,:,:),allocatable,save :: int_dtauv   ! VI optical thickness of layers within narrowbands for diags ().
76      real,dimension(:,:,:),allocatable,save :: int_dtaui   ! IR optical thickness of layers within narrowbands for diags ().
77!$OMP THREADPRIVATE(int_dtaui,int_dtauv)
78
79      real,allocatable,dimension(:),save :: tau_col ! Total Aerosol Optical Depth.
80      real,allocatable,save :: hice(:) ! Oceanic Ice height. by BC
81!$OMP THREADPRIVATE(tau_col,hice)
82
83      real,allocatable,dimension(:,:),save :: cloudfrac  ! Fraction of clouds (%).
84      real,allocatable,dimension(:),save :: totcloudfrac ! Column fraction of clouds (%).
85!$OMP THREADPRIVATE(cloudfrac,totcloudfrac)
86
87      real,allocatable,dimension(:,:),save :: qsurf_hist
88      real,allocatable,dimension(:,:,:),save :: nueffrad ! Aerosol effective radius variance. By RW
89!$OMP THREADPRIVATE(qsurf_hist,nueffrad)
90
91      real,allocatable,dimension(:),save :: ice_initial
92      real,allocatable,dimension(:),save :: ice_min
93!$OMP THREADPRIVATE(ice_initial,ice_min)
94
95      real,dimension(:),allocatable,save ::  pctsrf_sic
96      real,dimension(:,:),allocatable,save :: tslab        ! Slab_ocean temperature (K)
97      real,dimension(:),allocatable,save ::  tsea_ice      ! Temperature of the top layer (K), either snow or ice
98!      real,dimension(:),allocatable,save :: tice           ! Sea ice temperature (K) if there is snow on top of it
99      real,dimension(:),allocatable,save :: sea_ice
100      real,dimension(:),allocatable,save :: zmasq
101      integer,dimension(:),allocatable,save ::knindex
102      real,allocatable,dimension(:,:,:),save :: reffrad
103      real,dimension(:), allocatable,save :: fluxgrdocean  ! Surface conduction flux (W.m-2) with slab_ocean.
104!$OMP THREADPRIVATE(pctsrf_sic,tslab,tsea_ice,sea_ice,zmasq,knindex,reffrad,fluxgrdocean)
105
106      real,dimension(:,:),allocatable,save :: dEzdiff   ! Turbulent diffusion heating (W.m-2)
107      real,dimension(:),allocatable,save :: dEdiff      ! Integrated turbulent diffusion heating (W.m-2)
108      real,dimension(:),allocatable,save :: dEdiffs
109      real,dimension(:,:),allocatable,save :: dEzRadsw  ! Radiative heating (W.m-2)
110      real,dimension(:,:),allocatable,save :: dEzRadlw  ! Radiative heating (W.m-2)
111!$OMP THREADPRIVATE(dEzdiff,dEdiff,dEdiffs,dEzRadsw,dEzRadlw)
112
113      real,dimension(:),allocatable,save :: madjdE      ! Heat from moistadj (W.m-2)
114      real,dimension(:,:),allocatable,save :: madjdEz   ! Heat from moistadj (W.m-2)
115      real,dimension(:),allocatable,save :: lscaledE    ! Heat from largescale (W.m-2)
116      real,dimension(:,:),allocatable,save :: lscaledEz ! Heat from largescale (W.m-2)
117!$OMP THREADPRIVATE(madjdE,madjdEz,lscaledE,lscaledEz)
118     
119      real,dimension(:),allocatable,save :: genericconddE ! Heat from generic condensation (W.m-2)
120!$OMP THREADPRIVATE(genericconddE)
121
122      real,dimension(:),allocatable,save :: H2Omaxcol ! Maximum possible H2O column amount (at 100% saturation) (kg.m-2).
123!$OMP THREADPRIVATE(H2Omaxcol)
124     
125CONTAINS
126
127!======================================================================
128SUBROUTINE phys_state_var_init(nqtot)
129
130IMPLICIT NONE
131
132        integer,intent(in) :: nqtot
133
134!  Parametres de l'Orographie a l'Echelle Sous-Maille (OESM):
135!
136!zmea(:)   ! orographie moyenne
137!zstd(:)   ! deviation standard de l'OESM
138!zsig(:)   ! pente de l'OESM
139!zgam(:)   ! anisotropie de l'OESM
140!zthe(:)   ! orientation de l'OESM
141!zpic(:)   ! Maximum de l'OESM
142!zval(:)   ! Minimum de l'OESM
143!rugoro(:) ! longueur de rugosite de l'OESM
144
145        ALLOCATE(phisfi(klon))
146        ALLOCATE(tsurf(klon))
147        ALLOCATE(tsoil(klon,nsoilmx))
148        ALLOCATE(albedo(klon,L_NSPECTV))
149        ALLOCATE(albedo_equivalent(klon))
150        ALLOCATE(albedo_equivalent1(klon))
151        ALLOCATE(albedo_snow_SPECTV(L_NSPECTV))
152        ALLOCATE(albedo_co2_ice_SPECTV(L_NSPECTV))
153        ALLOCATE(albedo_bareground(klon))
154        ALLOCATE(rnat(klon))
155        ALLOCATE(emis(klon))
156        ALLOCATE(dtrad(klon,klev))
157        ALLOCATE(fluxrad_sky(klon))
158        ALLOCATE(fluxrad(klon))
159        ALLOCATE(capcal(klon))
160        ALLOCATE(fluxgrd(klon))
161        ALLOCATE(fluxgrdocean(klon))
162        ALLOCATE(qsurf(klon,nqtot))
163        ALLOCATE(q2(klon,klev+1))
164        ALLOCATE(ztprevious(klon,klev))
165        ALLOCATE(zuprevious(klon,klev))
166        ALLOCATE(cloudfrac(klon,klev))
167        ALLOCATE(totcloudfrac(klon))
168        ALLOCATE(hice(klon))
169        ALLOCATE(qsurf_hist(klon,nqtot))
170        ALLOCATE(reffrad(klon,klev,naerkind))
171        ALLOCATE(nueffrad(klon,klev,naerkind))
172        ALLOCATE(ice_initial(klon))
173        ALLOCATE(ice_min(klon))
174        ALLOCATE(fluxsurf_lw(klon))
175        ALLOCATE(fluxsurf_lw1(klon))
176        ALLOCATE(fluxsurf_sw(klon))
177        ALLOCATE(fluxsurf_sw1(klon))
178        ALLOCATE(fluxsurfabs_sw(klon))
179        ALLOCATE(fluxtop_lw(klon))
180        ALLOCATE(fluxtop_lw1(klon))
181        ALLOCATE(fluxabs_sw(klon))
182        ALLOCATE(fluxabs_sw1(klon))
183        ALLOCATE(fluxtop_dn(klon))
184        ALLOCATE(fluxdyn(klon))
185        ALLOCATE(OLR_nu(klon,L_NSPECTI))
186        ALLOCATE(OSR_nu(klon,L_NSPECTV))
187        ALLOCATE(GSR_nu(klon,L_NSPECTV))
188        ALLOCATE(int_dtaui(klon,klev,L_NSPECTI))
189        ALLOCATE(int_dtauv(klon,klev,L_NSPECTV))
190        ALLOCATE(sensibFlux(klon))
191        ALLOCATE(zdtlw(klon,klev))
192        ALLOCATE(zdtsw(klon,klev))
193        ALLOCATE(tau_col(klon))
194        ALLOCATE(pctsrf_sic(klon))
195        ALLOCATE(tslab(klon,nslay))
196        ALLOCATE(tsea_ice(klon))
197!        ALLOCATE(tice(klon))
198        ALLOCATE(sea_ice(klon))
199        ALLOCATE(zmasq(klon))
200        ALLOCATE(knindex(klon))
201        ALLOCATE(dEzdiff(klon,klev))
202        ALLOCATE(dEdiff(klon))
203        ALLOCATE(dEdiffs(klon))
204        ALLOCATE(dEzRadsw(klon,klev))
205        ALLOCATE(dEzRadlw(klon,klev))
206        ALLOCATE(madjdE(klon))
207        ALLOCATE(madjdEz(klon,klev))
208        ALLOCATE(lscaledE(klon))
209        ALLOCATE(lscaledEz(klon,klev))
210        ALLOCATE(genericconddE(klon))
211        ALLOCATE(H2Omaxcol(klon))
212        ! This is defined in comsaison_h
213        ALLOCATE(mu0(klon))
214        ALLOCATE(fract(klon))
215         ! This is defined in radcommon_h
216        ALLOCATE(glat(klon))
217        ALLOCATE(albedodat(klon))
218        ALLOCATE(zmea(klon))
219        ALLOCATE(zstd(klon))
220        ALLOCATE(zsig(klon))
221        ALLOCATE(zgam(klon))
222        ALLOCATE(zthe(klon))
223        !allocate(l0(klon))
224        allocate(wstar(klon))
225        allocate(ustar(klon))
226        allocate(tstar(klon))
227        allocate(hfmax_th(klon))
228        allocate(zmax_th(klon))
229        ! allocate arrays in "nonoro_gwd_ran_mod"
230        call ini_nonoro_gwd_ran(klon,klev)
231END SUBROUTINE phys_state_var_init
232
233!======================================================================
234SUBROUTINE phys_state_var_end
235
236IMPLICIT NONE
237
238        DEALLOCATE(tsurf)
239        DEALLOCATE(tsoil)
240        DEALLOCATE(albedo)
241        DEALLOCATE(albedo_equivalent)
242        DEALLOCATE(albedo_equivalent1)
243        DEALLOCATE(albedo_snow_SPECTV)
244        DEALLOCATE(albedo_co2_ice_SPECTV)
245        DEALLOCATE(albedo_bareground)
246        DEALLOCATE(rnat)
247        DEALLOCATE(emis)
248        DEALLOCATE(dtrad)
249        DEALLOCATE(fluxrad_sky)
250        DEALLOCATE(fluxrad)
251        DEALLOCATE(capcal)
252
253        DEALLOCATE(fluxgrd)
254        DEALLOCATE(fluxgrdocean)
255        DEALLOCATE(qsurf)
256        DEALLOCATE(q2)
257        DEALLOCATE(ztprevious)
258        DEALLOCATE(zuprevious)
259        DEALLOCATE(cloudfrac)
260        DEALLOCATE(totcloudfrac)
261        DEALLOCATE(hice)
262        DEALLOCATE(qsurf_hist)
263        DEALLOCATE(reffrad)
264        DEALLOCATE(nueffrad)
265        DEALLOCATE(ice_initial)
266        DEALLOCATE(ice_min)
267        DEALLOCATE(fluxsurf_lw)
268        DEALLOCATE(fluxsurf_lw1)
269        DEALLOCATE(fluxsurf_sw)
270        DEALLOCATE(fluxsurf_sw1)
271        DEALLOCATE(fluxsurfabs_sw)
272        DEALLOCATE(fluxtop_lw)
273        DEALLOCATE(fluxtop_lw1)
274        DEALLOCATE(fluxabs_sw)
275        DEALLOCATE(fluxabs_sw1)
276        DEALLOCATE(fluxtop_dn)
277        DEALLOCATE(fluxdyn)
278        DEALLOCATE(OLR_nu)
279        DEALLOCATE(OSR_nu)
280        DEALLOCATE(GSR_nu)
281        DEALLOCATE(int_dtaui)
282        DEALLOCATE(int_dtauv)
283        DEALLOCATE(sensibFlux)
284        DEALLOCATE(zdtlw)
285        DEALLOCATE(zdtsw)
286        DEALLOCATE(tau_col)
287        DEALLOCATE(pctsrf_sic)
288        DEALLOCATE(tslab)
289        DEALLOCATE(tsea_ice)
290 !       DEALLOCATE(tice)
291        DEALLOCATE(sea_ice)
292        DEALLOCATE(zmasq)
293        DEALLOCATE(knindex)
294        DEALLOCATE(dEzdiff)
295        DEALLOCATE(dEdiff)
296        DEALLOCATE(dEdiffs)
297        DEALLOCATE(dEzRadsw)
298        DEALLOCATE(dEzRadlw)
299        DEALLOCATE(madjdE)
300        DEALLOCATE(madjdEz)
301        DEALLOCATE(lscaledE)
302        DEALLOCATE(lscaledEz)
303        DEALLOCATE(genericconddE)
304        DEALLOCATE(H2Omaxcol)       
305        DEALLOCATE(mu0)
306        DEALLOCATE(fract)
307        DEALLOCATE(glat)
308        DEALLOCATE(phisfi)
309        DEALLOCATE(albedodat)
310        DEALLOCATE(zmea)
311        DEALLOCATE(zstd)
312        DEALLOCATE(zsig)
313        DEALLOCATE(zgam)
314        DEALLOCATE(zthe)
315        !deallocate(l0)
316        deallocate(wstar)
317        deallocate(ustar)
318        deallocate(tstar)
319        deallocate(hfmax_th)
320        deallocate(zmax_th)
321        ! deallocate arrays in "nonoro_gwd_ran_mod"
322        call end_nonoro_gwd_ran
323
324END SUBROUTINE phys_state_var_end
325
326      END MODULE phys_state_var_mod
Note: See TracBrowser for help on using the repository browser.