Newer
Older

WAUTELET Philippe
committed
!MNH_LIC Copyright 1995-2021 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence

WAUTELET Philippe
committed
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.

WAUTELET Philippe
committed
!-----------------------------------------------------------------
! ########################

WAUTELET Philippe
committed
MODULE MODI_PHYS_PARAM_n
! ########################
!
!
INTERFACE
!

WAUTELET Philippe
committed
SUBROUTINE PHYS_PARAM_n( KTCOUNT, TPFILE, &
PRAD, PSHADOWS, PKAFR, PGROUND, PMAFL, PDRAG,PEOL, PTURB, &
PTRACER, PTIME_BU, PWETDEPAER, OMASKkids, OCLOUD_ONLY )

WAUTELET Philippe
committed
!
USE MODD_IO, ONLY: TFILEDATA

WAUTELET Philippe
committed
use modd_precision, only: MNHTIME
!
INTEGER, INTENT(IN) :: KTCOUNT ! temporal iteration count

WAUTELET Philippe
committed
TYPE(TFILEDATA), INTENT(IN) :: TPFILE ! Synchronous output file

WAUTELET Philippe
committed
! advection schemes
REAL(kind=MNHTIME), DIMENSION(2), INTENT(INOUT) :: PRAD,PSHADOWS,PKAFR,PGROUND,PTURB,PMAFL,PDRAG,PTRACER,PEOL ! to store CPU

WAUTELET Philippe
committed
! time for computing time
REAL(kind=MNHTIME), DIMENSION(2), INTENT(INOUT) :: PTIME_BU ! time used in budget&LES budgets statistics
REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PWETDEPAER
LOGICAL, DIMENSION(:,:), INTENT(IN) :: OMASKkids ! kids domains mask
LOGICAL, INTENT(OUT) :: OCLOUD_ONLY ! conditionnal radiation computations for
! the only cloudy columns
!
END SUBROUTINE PHYS_PARAM_n
!
END INTERFACE
!
END MODULE MODI_PHYS_PARAM_n
!

WAUTELET Philippe
committed
! ########################################################################################
SUBROUTINE PHYS_PARAM_n( KTCOUNT, TPFILE, &
PRAD, PSHADOWS, PKAFR, PGROUND, PMAFL, PEOL, PDRAG, PTURB, &
PTRACER, PTIME_BU, PWETDEPAER, OMASKkids, OCLOUD_ONLY )

WAUTELET Philippe
committed
! ########################################################################################
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
!
!!**** *PHYS_PARAM_n * -monitor of the parameterizations used by model _n
!!
!! PURPOSE
!! -------
! The purpose of this routine is to update the sources by adding the
! parameterized terms. This is realized by sequentially calling the
! specialized routines.
!
!!** METHOD
!! ------
!! The first parametrization is the radiation scheme:
!! ----------------
!! * CRAD = 'FIXE'
!! In this case, a temporal interpolation is performed for the downward
!! surface fluxes XFLALWD and XFLASWD.
!! * CRAD = 'ECMWF'
!! Several tests are performed before calling the radiation computations
!! interface with the ECMWF radiation scheme code. A control is made to
!! ensure that:
!! - the full radiation code is called at the first model timestep
!! - there is a priority for calling the full radiation instead of the
!! cloud-only approximation if both must be called at the current
!! timestep
!! - the cloud-only option (approximation) is coherent with the
!! occurence of one cloudy vertical column at least
!! If all the above conditions are fulfilled (GRAD is .TRUE.) then the
!! position of the sun is computed in routine SUNPOS_n and the interfacing
!! routine RADIATIONS is called to update the radiative tendency XDTHRAD
!! and the downward surface fluxes XFLALWD and XFLASWD. Finally, the
!! radiative tendency is integrated as a source term in the THETA prognostic
!! equation.
!!
!! The second parameterization is the soil scheme:
!! -----------
!!
!! externalized surface
!!
!! The third parameterization is the turbulence scheme:
!! -----------------
!! * CTURB='NONE'
!! no turbulent mixing is taken into account
!! * CTURB='TKEL'
!! The turbulent fluxes are computed according to a one and half order
!! closure of the hydrodynamical equations. This scheme is based on a
!! prognostic for the turbulent kinetic energy and a mixing length
!! computation ( the mesh size or a physically based length). Other
!! turbulent moments are diagnosed according to a stationarization of the
!! second order turbulent moments. This turbulent scheme forecasts
!! either a purely vertical turbulent mixing or 3-dimensional mixing
!! according to its internal degrees of freedom.
!!
!!
!! The LAST parameterization is the chemistry scheme:
!! -----------------
!! The chemistry part of MesoNH has two namelists, NAM_SOLVER for the
!! parameters concerning the stiff solver, and NAM_MNHCn concerning the
!! configuration and options of the chemistry module itself.
!! The switch LUSECHEM in NAM_CONF acitvates or deactivates the chemistry.
!! The only variables of MesoNH that are modified by chemistry are the
!! scalar variables. If calculation of chemical surface fluxes is
!! requested, those fluxes are calculated before
!! entering the turbulence scheme, since those fluxes are taken into
!! account by TURB as surface boundary conditions.
!! CAUTION: chemistry has allways to be called AFTER ALL OTHER TERMS
!! that affect the scalar variables (dynamical terms, forcing,
!! parameterizations (like TURB, CONVECTION), since it uses the variables
!! XRSVS as input in case of the time-split option.
!!
!! EXTERNAL
!! --------
!! Subroutine SUNPOS_n : computes the position of the sun
!! Subroutine RADIATIONS : computes the radiative tendency and fluxes
!! Subroutine TSZ0 : computes the surface from temporally
!! interpolated Ts and given z0
!! Subroutine ISBA : computes the surface fluxes from a soil scheme
!! Subroutine TURB : computes the turbulence source terms
!! Subroutine CONVECTION : computes the convection source term
!! Subroutine CH_SURFACE_FLUX_n: computes the surface flux for chemical
!! species
!! Subroutine CH_MONITOR_n : computes the chemistry source terms
!! that are applied to the scalar variables
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!! USE MODD_DYN
!! USE MODD_CONF
!! USE MODD_CONF_n
!! USE MODD_CURVCOR_n
!! USE MODD_DYN_n
!! USE MODD_FIELD_n
!! USE MODD_GR_FIELD_n
!! USE MODD_LSFIELD_n
!! USE MODD_GRID_n
!! USE MODD_LBC_n
!! USE MODD_PARAM_RAD_n
!! USE MODD_RADIATIONS_n
!! USE MODD_REF_n
!! USE MODD_LUNIT_n
!! USE MODD_TIME_n
!! USE MODD_CH_MNHC_n
!!
!! REFERENCE
!! ---------
!! None
!!
!! AUTHOR
!! ------
!! J. Stein * Meteo-France *
!!
!! MODIFICATIONS
!! -------------
!! Original 05/01/95
!! Modifications Feb 14, 1995 (J.Cuxart) add the I/O arguments,
!! the director cosinus and change the names of the surface fluxes
!! Modifications March 21, 1995 (J.M.Carriere) take into account liquid
!! water
!! June 30,1995 (J.Stein) initialize at 0 the surf. fluxes
!! Modifications Sept. 1, 1995 (S.Belair) ISBA scheme
!! Modifications Sept.25, 1995 (J.Stein) switch on the radiation scheme
!! Modifications Sept. 11, 1995 (J.-P. Pinty) radiation scheme
!! Nov. 15, 1995 (J.Stein) cleaning + change the temporal
!! algorithm for the soil scheme-turbulence
!! Jan. 23, 1996 (J.Stein) add a new option for the surface
!! fluxes where Ts and z0 are given
!! March 18, 1996 (J.Stein) add the cloud fraction
!! March 28, 1996 (J.Stein) the soil scheme gives energy
!! fluxes + cleaning
!! June 17, 1996 (Lafore) statistics of computing time
!! August 4, 1996 (K. Suhre) add chemistry
!! Oct. 12, 1996 (J.Stein) use XSRCM in the turbulence
!! scheme
!! Nov. 18, 1996 (J.-P. Pinty) add domain translation
!! change arg. in radiations
!! Fev. 4, 1997 (J.Viviand) change isba's calling for ice
!! Jun. 22, 1997 (J.Stein) change the equation system and use
!! the absolute pressure
!! Jul. 09, 1997 (V.Masson) add directional z0
!! Jan. 24, 1998 (P.Bechtold) add convective transport for tracers
!! Jan. 24, 1998 (J.-P. Pinty) split SW and LW part for radiation
!! Mai. 10, 1999 (P.Bechtold) shallow convection
!! Oct. 20, 1999 (P.Jabouille) domain translation for turbulence
!! Jan. 04, 2000 (V.Masson) removes TSZ0 case
!! Jan. 04, 2000 (V.Masson) modifies albedo computation
! Jul 02, 2000 (F.Solmon/V.Masson) adaptation for patch approach
!! Nov. 15, 2000 (V.Masson) LES routines
!! Nov. 15, 2000 (V.Masson) effect of slopes on surface fluxes
!! Feb. 02, 2001 (P.Tulet) add friction velocities and aerodynamical
!! resistance (patch approach)
!! Jan. 04, 2000 (V.Masson) modify surf_rad_modif computation
!! Mar. 04, 2002 (F.Solmon) new interface for radiation call
!! Nov. 06, 2002 (V.Masson) LES budgets & budget time counters
!! Jan. 2004 (V.Masson) surface externalization
!! Jan. 13, 2004 (J.Escobar) bug correction : compute "GRAD" in parallel
!! Jan. 20, 2005 (P. Tulet) add dust sedimentation
!! Jan. 20, 2005 (P. Tulet) climatologic SSA
!! Jan. 20, 2005 (P. Tulet) add aerosol / dust scavenging
!! Jul. 2005 (N. Asencio) use the two-way result-fields
!! before ground_param call
!! May 2006 Remove EPS
!! Oct. 2007 (J.Pergaud) Add shallow_MF
!! Oct. 2009 (C.Lac) Introduction of different PTSTEP according to the
!! advection schemes
!! Oct. 2009 (V. MAsson) optimization of Pergaud et al massflux scheme
!! Aug. 2010 (V.Masson, C.Lac) Exchange of SBL_DEPTH for
!! reproducibility
!! Oct. 2010 (J.Escobar) init ZTIME_LES_MF ( pb detected with g95 )
!! Feb. 2011 (V.Masson, C.Lac) SBL_DEPTH values on outer pts
!! for RMC01
!! Sept.2011 (J.Escobar) init YINST_SFU ='M'
!!
!! Specific for 2D modeling :
!!
!! 06/2010 (P.Peyrille) add Call to aerozon.f90 if LAERO_FT=T
!! to update
!! aerosols and ozone climatology at each call to
!! phys_param otherwise it is constant to monthly average

Gaelle Tanguy
committed
!! 01/2014 (C.Lac) correction for the nesting of 2D surface
!! fields if the number of the son model does not
!! follow the number of the dad model

ESCOBAR MUNOZ Juan
committed
!! J.Escobar 21/03/2013: for HALOK comment all NHALO=1 test
!! M. Leriche 02/2017 Avoid negative fluxes if sv=0 outside the physics domain
!! C.Lac 10/2017 : ch_monitor and aer_monitor extracted from phys_param
!! to be called directly by modeln as the last process
!! 02/2018 Q.Libois ECRAD

WAUTELET Philippe
committed
! P. Wautelet 28/03/2018: replace TEMPORAL_DIST by DATETIME_DISTANCE
! P. Wautelet 05/2016-04/2018: new data structures and calls for I/O
! P. Wautelet 28/03/2019: use MNHTIME for time measurement variables

WAUTELET Philippe
committed
! P. Wautelet 26/04/2019: replace non-standard FLOAT function by REAL function

WAUTELET Philippe
committed
! P. Wautelet 20/05/2019: add name argument to ADDnFIELD_ll + new ADD4DFIELD_ll subroutine
! P. Wautelet 21/11/2019: ZRG_HOUR and ZRAT_HOUR are now parameter arrays

WAUTELET Philippe
committed
! C. Lac 11/2019: correction in the drag formula and application to building in addition to tree
! F. Auguste 02/2021: add IBM
! JL Redelsperger 03/2021: add the SW flux penetration for Ocean model case
!!-------------------------------------------------------------------------------
!
!* 0. DECLARATIONS
! ------------

WAUTELET Philippe
committed
USE MODD_ADV_n, ONLY : XRTKEMS
USE MODD_ARGSLIST_ll, ONLY : LIST_ll
use modd_budget, only: lbudget_th, lbudget_rv, lbudget_rc, lbudget_ri, lbudget_sv, &
NBUDGET_TH, NBUDGET_RV, NBUDGET_RC, NBUDGET_RI, NBUDGET_SV1, &
tbudgets, xtime_bu_process
USE MODD_CH_AEROSOL
USE MODD_CH_MNHC_n, ONLY : LUSECHEM, &! indicates if chemistry is used
LCH_CONV_SCAV, &
LCH_CONV_LINOX
USE MODD_CLOUD_MF_n
USE MODD_CONDSAMP

WAUTELET Philippe
committed
USE MODD_CST

WAUTELET Philippe
committed
USE MODD_DEEP_CONVECTION_n
USE MODD_DEF_EDDY_FLUX_n ! Ajout PP
USE MODD_DEF_EDDYUV_FLUX_n ! Ajout PP
USE MODD_DRAGBLDG_n
USE MODD_DRAGTREE_n

WAUTELET Philippe
committed
USE MODD_DUST
USE MODD_DYN
USE MODD_EOL_MAIN, ONLY: LMAIN_EOL, CMETH_EOL, NMODEL_EOL

WAUTELET Philippe
committed
USE MODD_FRC

WAUTELET Philippe
committed
USE MODD_GRID

WAUTELET Philippe
committed
USE MODD_IBM_PARAM_n, ONLY: LIBM, XIBM_EPSI, XIBM_LS

WAUTELET Philippe
committed
USE MODD_ICE_C1R3_DESCR, ONLY : XRTMIN_C1R3=>XRTMIN
USE MODD_IO, ONLY: TFILEDATA
USE MODD_LATZ_EDFLX

WAUTELET Philippe
committed
USE MODD_LES
USE MODD_LES_BUDGET
USE MODD_LSFIELD_n

WAUTELET Philippe
committed
USE MODD_METRICS_n
USE MODD_MNH_SURFEX_n
USE MODD_NESTING, ONLY : XWAY,NDAD, NDXRATIO_ALL, NDYRATIO_ALL
USE MODD_NSV

RODIER Quentin
committed
USE MODD_OCEANH

WAUTELET Philippe
committed
USE MODD_PARAM_C2R2, ONLY : LSEDC
USE MODD_PARAMETERS
USE MODD_PARAM_ICE, ONLY : LSEDIC
USE MODD_PARAM_KAFR_n
USE MODD_PARAM_LIMA, ONLY : MSEDC => LSEDC, XRTMIN_LIMA=>XRTMIN
USE MODD_PARAM_MFSHALL_n
USE MODD_PARAM_n
USE MODD_PARAM_RAD_n

WAUTELET Philippe
committed
USE MODD_PASPOL
USE MODD_PASPOL_n
USE MODD_PRECIP_n
use modd_precision, only: MNHTIME

WAUTELET Philippe
committed
USE MODD_RAIN_ICE_DESCR, ONLY: XRTMIN
USE MODD_REF, ONLY: LCOUPLES

WAUTELET Philippe
committed
USE MODD_REF_n
USE MODD_SALT

WAUTELET Philippe
committed
USE MODD_SUB_PHYS_PARAM_n

WAUTELET Philippe
committed
USE MODD_TIME_n
USE MODD_TIME, ONLY : TDTEXP ! Ajout PP
USE MODD_TURB_CLOUD, ONLY : CTURBLEN_CLOUD,NMODEL_CLOUD, &
XCEI,XCEI_MIN,XCEI_MAX,XCOEF_AMPL_SAT

WAUTELET Philippe
committed
USE MODD_TURB_FLUX_AIRCRAFT_BALLOON, ONLY : XTHW_FLUX, XRCW_FLUX, XSVW_FLUX
USE MODD_TURB_n

WAUTELET Philippe
committed
use mode_budget, only: Budget_store_end, Budget_store_init
USE MODE_DATETIME
USE MODE_DUST_PSD
USE MODE_ll

WAUTELET Philippe
committed
USE MODE_MODELN_HANDLER
USE MODE_MPPDB
USE MODE_SALT_PSD

WAUTELET Philippe
committed
USE MODI_CONDSAMP
USE MODI_CONVECTION

WAUTELET Philippe
committed
USE MODI_DRAG_VEG
USE MODI_DUST_FILTER
USE MODI_EDDY_FLUX_n ! Ajout PP
USE MODI_EDDY_FLUX_ONE_WAY_n ! Ajout PP

WAUTELET Philippe
committed
USE MODI_EDDYUV_FLUX_n ! Ajout PP
USE MODI_EDDYUV_FLUX_ONE_WAY_n ! Ajout PP
USE MODI_EOL_MAIN

WAUTELET Philippe
committed
USE MODI_GROUND_PARAM_n
USE MODI_PASPOL
USE MODI_RADIATIONS
USE MODI_SALT_FILTER
USE MODI_SEDIM_DUST
USE MODI_SEDIM_SALT
USE MODI_SHALLOW_MF_PACK
USE MODI_SUNPOS_n
USE MODI_SURF_RAD_MODIF

WAUTELET Philippe
committed
USE MODI_TURB
IMPLICIT NONE
!
!* 0.1 declarations of arguments
!
INTEGER, INTENT(IN) :: KTCOUNT ! temporal iteration count

WAUTELET Philippe
committed
TYPE(TFILEDATA), INTENT(IN) :: TPFILE ! Synchronous output file

WAUTELET Philippe
committed
! advection schemes
REAL(kind=MNHTIME), DIMENSION(2), INTENT(INOUT) :: PRAD,PSHADOWS,PKAFR,PGROUND,PTURB,PMAFL,PDRAG,PTRACER,PEOL ! to store CPU

WAUTELET Philippe
committed
! time for computing time
REAL(kind=MNHTIME), DIMENSION(2), INTENT(INOUT) :: PTIME_BU ! time used in budget&LES budgets statistics
REAL, DIMENSION(:,:,:,:), INTENT(INOUT) :: PWETDEPAER
LOGICAL, DIMENSION(:,:), INTENT(IN) :: OMASKkids ! kids domains mask
LOGICAL, INTENT(OUT) :: OCLOUD_ONLY ! conditionnal radiation computations for
! the only cloudy columns
!
!
!* 0.2 declarations of local variables
!
REAL, DIMENSION(:,:), ALLOCATABLE :: ZSFU ! surface flux of x and
REAL, DIMENSION(:,:), ALLOCATABLE :: ZSFV ! y component of wind
REAL, DIMENSION(:,:), ALLOCATABLE :: ZSFTH ! surface flux of theta
REAL, DIMENSION(:,:), ALLOCATABLE :: ZSFRV ! surface flux of vapor
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZSFSV ! surface flux of scalars
REAL, DIMENSION(:,:), ALLOCATABLE :: ZSFCO2! surface flux of CO2
!
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZDIR_ALB ! direct albedo
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZSCA_ALB ! diffuse albedo
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZEMIS ! emissivity
REAL, DIMENSION(:,:), ALLOCATABLE :: ZTSRAD ! surface temperature
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: ZRGDST,ZSIGDST,ZNDST,ZSVDST
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: ZRGSLT,ZSIGSLT,ZNSLT,ZSVSLT
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: ZRGAER,ZSIGAER,ZNAER,ZSVAER
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: ZSVT
!
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZEXN ! Atmospheric density and Exner
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZSIGMF ! MF contribution to XSIGS
!
REAL, DIMENSION(0:24), parameter :: ZRG_HOUR = (/ 0., 0., 0., 0., 0., 32.04, 114.19, &
228.01, 351.25, 465.49, 557.24, &
616.82, 638.33, 619.43, 566.56, &
474.71, 359.20, 230.87, 115.72, &
32.48, 0., 0., 0., 0., 0. /)
REAL, DIMENSION(0:24), parameter :: ZRAT_HOUR = (/ 326.00, 325.93, 325.12, 324.41, &
323.16, 321.95, 322.51, 325.16, &
328.01, 331.46, 335.58, 340.00, &
345.20, 350.32, 354.20, 356.58, &
356.56, 355.33, 352.79, 351.34, &
347.00, 342.00, 337.00, 332.00, &
326.00 /)

WAUTELET Philippe
committed
!
character(len=6) :: ynum
INTEGER :: IHOUR ! parameters necessary for the temporal
REAL :: ZTIME, ZDT ! interpolation
REAL :: ZTEMP_DIST ! time between 2 instants (in seconds)
!
LOGICAL :: GRAD ! conditionnal call for the full radiation
! computations
REAL :: ZRAD_GLOB_ll ! 'real' global parallel mask of 'GRAD'
INTEGER :: INFO_ll ! error report of parallel routines
! the only cloudy columns
!

WAUTELET Philippe
committed
REAL(kind=MNHTIME), DIMENSION(2) :: ZTIME1, ZTIME2, ZTIME3, ZTIME4 ! for computing time analysis
REAL(kind=MNHTIME), DIMENSION(2) :: ZTIME_LES_MF ! time spent in LES computation in shallow conv.
LOGICAL :: GDCONV ! conditionnal call for the deep convection
! computations
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZRC, ZRI, ZWT ! additional dummies
REAL, DIMENSION(:,:), ALLOCATABLE :: ZDXDY ! grid area
! for rc, ri, w required if main variables not allocated
!
INTEGER :: IIU, IJU, IKU ! dimensional indexes
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
!
INTEGER :: JSV ! Loop index for Scalar Variables
INTEGER :: JSWB ! loop on SW spectral bands
INTEGER :: IIB,IIE,IJB,IJE, IKB, IKE
INTEGER :: IMODEIDX
! index values for the Beginning or the End of the physical
! domain in x and y directions
TYPE(LIST_ll), POINTER :: TZFIELDS_ll ! list of fields to exchange
INTEGER :: IINFO_ll ! return code of parallel routine
!
!* variables for writing in a fm file
!
INTEGER :: IRESP ! IRESP : return-code if a problem appears
!in LFI subroutines at the open of the file
INTEGER :: ILUOUT ! logical unit numbers of output-listing
INTEGER :: IMI ! model index
INTEGER :: JKID ! loop index to look for the KID models
REAL :: ZINIRADIUSI, ZINIRADIUSJ ! ORILAM initial radius
REAL, DIMENSION(NMODE_DST) :: ZINIRADIUS ! DUST initial radius
REAL, DIMENSION(NMODE_SLT) :: ZINIRADIUS_SLT ! Sea Salt initial radius
REAL, DIMENSION(SIZE(XRSVS,1), SIZE(XRSVS,2), SIZE(XRSVS,3), SIZE(XRSVS,4)) :: ZRSVS
LOGICAL :: GCLD ! conditionnal call for dust wet deposition
! * arrays to store the surface fields before radiation and convection scheme
! calls
INTEGER :: IMODSON ! Number of son models of IMI with XWAY=2
INTEGER :: IKIDM ! index loop
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZSAVE_INPRR,ZSAVE_INPRS,ZSAVE_INPRG,ZSAVE_INPRH
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZSAVE_INPRC,ZSAVE_PRCONV,ZSAVE_PRSCONV
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: ZSAVE_DIRFLASWD, ZSAVE_SCAFLASWD,ZSAVE_DIRSRFSWD

RODIER Quentin
committed
! for ocean model
INTEGER :: JKM , JSW ! vertical index loop
REAL :: ZSWA,TINTSW ! index for SW interpolation and int time betwenn forcings (ocean model)
REAL, DIMENSION(:), ALLOCATABLE :: ZIZOCE(:) ! Solar flux penetrating in ocean
REAL, DIMENSION(:), ALLOCATABLE ::
Loading
Loading full blame...