SURFEX v8.1
General documentation of Surfex
modd_seafluxn.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #################
7 ! #################
8 !
9 !!**** *MODD_SEAFLUX_n - declaration of surface parameters for an inland water surface
10 !!
11 !! PURPOSE
12 !! -------
13 ! Declaration of surface parameters
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! None
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !! AUTHOR
24 !! ------
25 !! V. Masson *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 01/2004
30 !! S. Senesi 01/2014 adapt to fractional seaice, and to seaice scheme
31 !! S. Belamari 03/2014 Include NZ0
32 !
33 !* 0. DECLARATIONS
34 ! ------------
35 !
36 USE modd_surf_par, ONLY : xundef
38 !
39 USE modd_types_glt, ONLY : t_glt
40 !
41 !
42 USE yomhook ,ONLY : lhook, dr_hook
43 USE parkind1 ,ONLY : jprb
44 !
45 IMPLICIT NONE
46 
48 !
49 ! General surface:
50 !
51  REAL, POINTER, DIMENSION(:) :: xzs ! orography
52  REAL, POINTER, DIMENSION(:,:) :: xcover ! fraction of each ecosystem (-)
53  LOGICAL, POINTER, DIMENSION(:):: lcover ! GCOVER(i)=T --> ith cover field is not 0.
54  LOGICAL :: lsbl ! T: SBL scheme between sea and atm. forcing level
55 ! ! F: no atmospheric layers below forcing level
56  LOGICAL :: lhandle_sic ! T: we do weight seaice and open sea fluxes
57  CHARACTER(LEN=6) :: cseaice_scheme! Name of the seaice scheme
58  REAL, POINTER, DIMENSION(:) :: xseabathy ! bathymetry
59 !
60  LOGICAL :: linterpol_sst ! Interpolation of monthly SST
61  CHARACTER(LEN=6) :: cinterpol_sst ! Interpolation method of monthly SST
62  LOGICAL :: linterpol_sss ! Interpolation of monthly SSS
63  CHARACTER(LEN=6) :: cinterpol_sss ! Interpolation method of monthly SSS
64  LOGICAL :: linterpol_sic ! Interpolation of monthly SIC
65  CHARACTER(LEN=6) :: cinterpol_sic ! Interpolation method of monthly SIC
66  LOGICAL :: linterpol_sit ! Interpolation of monthly SIT
67  CHARACTER(LEN=6) :: cinterpol_sit ! Interpolation method of monthly SIT
68  REAL :: xfreezing_sst ! Value marking frozen sea in SST data
69  REAL :: xsic_efolding_time ! For damping of SIC (days)
70  REAL :: xsit_efolding_time ! For damping of SIT (days)
71  REAL :: xseaice_tstep ! Sea ice model time step
72  REAL :: xcd_ice_cst ! Turbulent exchange coefficient for seaice
73  REAL :: xsi_flx_drv ! Derivative of fluxes on seaice w.r.t to the temperature (W m-2 K-1)
74 
75 !
76 ! Type of formulation for the fluxes
77 !
78  CHARACTER(LEN=6) :: csea_flux ! type of flux computation
79  CHARACTER(LEN=4) :: csea_alb ! type of albedo
80  LOGICAL :: lpwg ! flag for gust
81  LOGICAL :: lprecip ! flag for precip correction
82  LOGICAL :: lpwebb ! flag for Webb correction
83  INTEGER :: nz0 ! set to 0,1 or 2 according to Z0 formulation
84  ! 0= ARPEGE / 1= Smith (1988) / 2= Direct
85  INTEGER :: ngrvwaves ! set to 0,1 or 2 according to the
86  ! gravity waves model used in coare30_flux
87  REAL :: xichce ! CE coef calculation for ECUME
88  LOGICAL :: lpertflux ! flag for stochastic flux perturbation
89 !
90 ! Sea/Ocean:
91 !
92  REAL, POINTER, DIMENSION(:) :: xsst ! sea surface temperature
93  REAL, POINTER, DIMENSION(:) :: xsss ! sea surface salinity
94  REAL, POINTER, DIMENSION(:) :: xtice ! sea ice temperature
95  REAL, POINTER, DIMENSION(:) :: xsic ! sea ice concentration ( constraint for seaice scheme )
96  REAL, POINTER, DIMENSION(:) :: xsst_ini! initial sea surface temperature
97  REAL, POINTER, DIMENSION(:) :: xz0 ! roughness length
98  REAL, POINTER, DIMENSION(:) :: xz0h ! roughness length for heat
99  REAL, POINTER, DIMENSION(:) :: xemis ! emissivity
100  REAL, POINTER, DIMENSION(:) :: xdir_alb! direct albedo
101  REAL, POINTER, DIMENSION(:) :: xsca_alb! diffuse albedo
102  REAL, POINTER, DIMENSION(:) :: xice_alb! sea-ice albedo from seaice model (ESM or embedded)
103  REAL, POINTER, DIMENSION(:) :: xumer ! U component of sea current (for ESM coupling)
104  REAL, POINTER, DIMENSION(:) :: xvmer ! V component of sea current (for ESM coupling)
105 !
106  REAL, POINTER, DIMENSION(:,:) :: xsst_mth! monthly sea surface temperature (precedent, current and next)
107  REAL, POINTER, DIMENSION(:,:) :: xsss_mth! monthly sea surface salinity (precedent, current and next)
108  REAL, POINTER, DIMENSION(:,:) :: xsic_mth! monthly sea ice cover (precedent, current and next)
109  REAL, POINTER, DIMENSION(:,:) :: xsit_mth! monthly sea ice thickness (precedent, current and next)
110  REAL, POINTER, DIMENSION(:) :: xfsic ! nudging (or forcing) sea ice cover
111  REAL, POINTER, DIMENSION(:) :: xfsit ! nudging sea ice thickness
112 !
113  REAL, POINTER, DIMENSION(:) :: xcpl_sea_wind ! 10m wind speed for ESM coupling
114  REAL, POINTER, DIMENSION(:) :: xcpl_sea_fwsu ! zonal wind stress for ESM coupling
115  REAL, POINTER, DIMENSION(:) :: xcpl_sea_fwsv ! meridian wind stress for ESM coupling
116  REAL, POINTER, DIMENSION(:) :: xcpl_sea_snet ! Solar net heat flux
117  REAL, POINTER, DIMENSION(:) :: xcpl_sea_heat ! Non solar net heat flux
118  REAL, POINTER, DIMENSION(:) :: xcpl_sea_evap ! Evaporation for ESM coupling
119  REAL, POINTER, DIMENSION(:) :: xcpl_sea_rain ! Rainfall for ESM coupling
120  REAL, POINTER, DIMENSION(:) :: xcpl_sea_snow ! Snowfall for ESM coupling
121  REAL, POINTER, DIMENSION(:) :: xcpl_sea_fwsm ! wind stress for ESM coupling
122 !
123  REAL, POINTER, DIMENSION(:) :: xcpl_seaice_snet ! Solar net heat flux for ESM coupling
124  REAL, POINTER, DIMENSION(:) :: xcpl_seaice_heat ! Non solar net heat flux
125  REAL, POINTER, DIMENSION(:) :: xcpl_seaice_evap ! Ice sublimation for ESM coupling
126 !
127  REAL, POINTER, DIMENSION(:) :: xpertflux ! Stochastic flux perturbation pattern
128 !
129 ! Sea-ice :
130 !
131  TYPE(t_glt) :: tglt ! Sea-ice state , diagnostics and auxilliaries
132  ! for the case of embedded Gelato Seaice model
133 !
134 ! Date:
135 !
136  type(date_time) :: ttime ! current date and time
137  type(date_time) :: tztime
138  LOGICAL :: ltztime_done
139  INTEGER :: jsx
140 !
141 ! Time-step:
142 !
143  REAL :: xtstep ! time step
144 !
145  REAL :: xout_tstep ! output writing time step
146 !
147 !
148 !
149 END TYPE seaflux_t
150 
151 
152 
153 CONTAINS
154 
155 !
156 
157 
158 
159 
160 SUBROUTINE seaflux_init(YSEAFLUX)
161 TYPE(seaflux_t), INTENT(INOUT) :: YSEAFLUX
162 REAL(KIND=JPRB) :: ZHOOK_HANDLE
163 IF (lhook) CALL dr_hook("MODD_SEAFLUX_N:SEAFLUX_INIT",0,zhook_handle)
164  NULLIFY(yseaflux%XZS)
165  NULLIFY(yseaflux%XCOVER)
166  NULLIFY(yseaflux%LCOVER)
167  NULLIFY(yseaflux%XSEABATHY)
168  NULLIFY(yseaflux%XSST)
169  NULLIFY(yseaflux%XSSS)
170  NULLIFY(yseaflux%XSIC)
171  NULLIFY(yseaflux%XTICE)
172  NULLIFY(yseaflux%XSST_INI)
173  NULLIFY(yseaflux%XZ0)
174  NULLIFY(yseaflux%XZ0H)
175  NULLIFY(yseaflux%XEMIS)
176  NULLIFY(yseaflux%XDIR_ALB)
177  NULLIFY(yseaflux%XSCA_ALB)
178  NULLIFY(yseaflux%XICE_ALB)
179  NULLIFY(yseaflux%XUMER)
180  NULLIFY(yseaflux%XVMER)
181  NULLIFY(yseaflux%XSST_MTH)
182  NULLIFY(yseaflux%XSSS_MTH)
183  NULLIFY(yseaflux%XSIC_MTH)
184  NULLIFY(yseaflux%XSIT_MTH)
185  NULLIFY(yseaflux%XFSIC)
186  NULLIFY(yseaflux%XFSIT)
187  NULLIFY(yseaflux%XCPL_SEA_WIND)
188  NULLIFY(yseaflux%XCPL_SEA_FWSU)
189  NULLIFY(yseaflux%XCPL_SEA_FWSV)
190  NULLIFY(yseaflux%XCPL_SEA_SNET)
191  NULLIFY(yseaflux%XCPL_SEA_HEAT)
192  NULLIFY(yseaflux%XCPL_SEA_EVAP)
193  NULLIFY(yseaflux%XCPL_SEA_RAIN)
194  NULLIFY(yseaflux%XCPL_SEA_SNOW)
195  NULLIFY(yseaflux%XCPL_SEA_FWSM)
196  NULLIFY(yseaflux%XCPL_SEAICE_SNET)
197  NULLIFY(yseaflux%XCPL_SEAICE_HEAT)
198  NULLIFY(yseaflux%XCPL_SEAICE_EVAP)
199  NULLIFY(yseaflux%XPERTFLUX)
200 yseaflux%LSBL=.false.
201 yseaflux%LHANDLE_SIC=.false.
202 yseaflux%CSEAICE_SCHEME='NONE '
203 yseaflux%LINTERPOL_SST=.false.
204 yseaflux%CINTERPOL_SST=' '
205 yseaflux%LINTERPOL_SSS=.false.
206 yseaflux%CINTERPOL_SSS=' '
207 yseaflux%LINTERPOL_SIC=.false.
208 yseaflux%CINTERPOL_SIC=' '
209 yseaflux%LINTERPOL_SIT=.false.
210 yseaflux%CINTERPOL_SIT=' '
211 yseaflux%XFREEZING_SST=-1.8
212 yseaflux%XSIC_EFOLDING_TIME=0. ! means : no damping
213 yseaflux%XSIT_EFOLDING_TIME=0. ! means : no damping
214 yseaflux%XSEAICE_TSTEP=xundef
215 yseaflux%XCD_ICE_CST=0.
216 yseaflux%XSI_FLX_DRV=-20.
217 yseaflux%CSEA_FLUX=' '
218 yseaflux%CSEA_ALB=' '
219 yseaflux%LPWG=.false.
220 yseaflux%LPRECIP=.false.
221 yseaflux%LPWEBB=.false.
222 yseaflux%NZ0=0
223 yseaflux%NGRVWAVES=0
224 yseaflux%XICHCE=0.
225 yseaflux%LPERTFLUX=.false.
226 yseaflux%JSX=0
227 yseaflux%LTZTIME_DONE = .false.
228 yseaflux%XTSTEP=0.
229 yseaflux%XOUT_TSTEP=0.
230 IF (lhook) CALL dr_hook("MODD_SEAFLUX_N:SEAFLUX_INIT",1,zhook_handle)
231 END SUBROUTINE seaflux_init
232 
233 
234 END MODULE modd_seaflux_n
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine seaflux_init(YSEAFLUX)