SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
default_seaice.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 ! #########
6 SUBROUTINE default_seaice(HPROGRAM, &
7  hinterpol_sic, hinterpol_sit, pfreezing_sst,&
8  pseaice_tstep, psic_efolding_time, &
9  psit_efolding_time, pcd_ice, psi_flx_drv )
10 ! ########################################################################
11 !
12 !!**** *DEFAULT_SEAICE* - routine to set default values for the configuration for SEAICE scheme
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !!** METHOD
18 !! ------
19 !! For now, only Gelato seaice scheme is handled
20 !!
21 !! We do use MODD_GLT_PARAM, for modifying its values, in order to
22 !! avoid duplicating code with Gelato sources
23 !!
24 !! We set all its parameters to values which are sensible in Surfex context
25 !! This is done by inserting a relevant 'gltpar' file as source code, and
26 !! changing a few values (we used a Glt 6.0.36 version, initially)
27 !!
28 !! EXTERNAL
29 !! --------
30 !!
31 !!
32 !! IMPLICIT ARGUMENTS
33 !! ------------------
34 !!
35 !! REFERENCE
36 !! ---------
37 !!
38 !!
39 !! AUTHOR
40 !! ------
41 !! S.Senesi *Meteo France*
42 !!
43 !! MODIFICATIONS
44 !! -------------
45 !! Original 01/2014
46 !-------------------------------------------------------------------------------
47 !
48 !* 0. DECLARATIONS
49 ! ------------
50 !
51 USE modd_surf_par, ONLY : xundef
52 USE modi_get_luout
53 !
54 USE modd_glt_param, ONLY : nmkinit, nrstout, nrstgl4, nthermo, ndynami, nadvect, ntimers, &
55  ndyncor, ncdlssh, niceage, nicesal, nmponds, nsnwrad, nleviti, nsalflx, nextqoc, &
56  nicesub, cnflxin, cfsidmp, xfsidmpeft, chsidmp, xhsidmpeft, &
57  cdiafmt, cdialev, dttave , navedia, ninsdia, ndiamax, nsavinp, &
58  nsavout, nupdbud, nprinto, nprlast, cn_grdname, rn_htopoc, nidate , niter, &
59  dtt, nt, thick, nilay, nslay, xh0 , xh1 , xh2 , xh3 , xh4 , ntstp , ndte , xfsimax, &
60  xicethcr, xhsimin, alblc , xlmelt , xswhdfr, albyngi, albimlt, albsmlt, albsdry,ngrdlu,&
61  nsavlu, nrstlu , n0vilu , n0valu , n2vilu , n2valu , nxvilu , nxvalu , nibglu , &
62  nspalu , noutlu , ntimlu , ciopath, &
63  gelato_leadproc, gelato_myrank, lwg, nnflxin, ntd
64 !
65 USE modd_surfex_mpi, ONLY : nrank, npio
66 !
67 !
68 USE yomhook ,ONLY : lhook, dr_hook
69 USE parkind1 ,ONLY : jprb
70 !
71 IMPLICIT NONE
72 !
73 !* 0.1 Declarations of arguments
74 ! -------------------------
75 !
76 !
77  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling ISBA
78  CHARACTER(LEN=6), INTENT(OUT) :: hinterpol_sic ! Quadratic interpolation of monthly SIC
79  CHARACTER(LEN=6), INTENT(OUT) :: hinterpol_sit ! Quadratic interpolation of monthly SIT
80 REAL, INTENT(OUT) :: pfreezing_sst ! Value marking frozen sea in SST data
81 REAL, INTENT(OUT) :: pseaice_tstep ! For damping of SIC (days)
82 REAL, INTENT(OUT) :: psic_efolding_time ! E-folding time on SIC relaxation
83 REAL, INTENT(OUT) :: psit_efolding_time ! E-folding time on SIT relaxation
84 REAL, INTENT(OUT) :: pcd_ice ! turbulent exchanges transfer coefficient on seaice
85 REAL, INTENT(OUT) :: psi_flx_drv ! turbulent exchanges transfer coefficient on seaice
86 
87 !
88 REAL(KIND=JPRB) :: zhook_handle
89 !
90 !* 0.2 Declarations of local variables
91 ! -------------------------------
92 INTEGER :: iluout ! logical unit of output file
93 integer jl
94 real zjl
95 !
96 !-------------------------------------------------------------------------------
97 !
98 IF (lhook) CALL dr_hook('DEFAULT_SEAICE',0,zhook_handle)
99 !
100  CALL get_luout(hprogram,iluout)
101 !
102 hinterpol_sic = "NONE"
103 hinterpol_sit = "NONE"
104 pfreezing_sst = -1.8 ! Celsius degree
105 pseaice_tstep = xundef
106 psic_efolding_time = 0 ! in days; 0 means no relaxation
107 psit_efolding_time = 0 ! in days; 0 means no relaxation
108 pcd_ice = 0.0
109 psi_flx_drv = -20.
110 !
111 ! Even if default case is to avoid using a seaice scheme, we set
112 ! default Gelato seaice model parameters
113 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
114 !
115 ! Setting those Gelato parameters which are not usually set by an
116 ! external file but by the gelato library caller program
117 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
118 !
119 ! .. Number of categories considered in observations towards which damping is
120 ! applied
121 ntd=1
122 ! .. One input non-solar forcing flux per ice category (nt) or one input
123 ! non-solar flux to be shared between all the categories (1)
124 nnflxin=1
125 ! .. Which is the leading process number (useless now ?)
126 gelato_leadproc=0
127 ! Adapt proc number and print flags to the Surfex proc numbering scheme
128 gelato_myrank=nrank
129 lwg=(nrank == npio)
130 
131 
132 ! Setting those Gelato parameters which are usually set by an
133 ! external file (gltpar)
134 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
135 !
136 ! Gelato model parameters
137 ! =========================
138 !
139 ! .. These parameters can be (theoretically) freely changed by the user
140 !
141 !
142 ! 1. Options to run GELATO
143 ! -------------------------
144 !
145 ! - nmkinit : create initial conditions file
146 ! nmkinit=0 --> use a restart file instead
147 ! nmkinit=1 --> use sea ice analytical initialization
148 ! nmkinit=2 --> use a sea ice fraction climatology
149 ! - nrstout : create an output restart file
150 ! nrstout=0 --> no output restart
151 ! nrstout=1 --> output restart will be created
152 ! - nrstgl4 : about restart format
153 ! nrstgl4=0 --> use an old format restart (before Gelato 4)
154 ! nrstgl4=1 --> use a new format restart (Gelato 4 and newer)
155 ! - nthermo : disable/enable sea ice thermodynamics
156 ! nthermo=0 --> no thermodynamics
157 ! nthermo=1 --> thermodynamics enabled
158 ! - ndynami : disable/enable sea ice dynamics
159 ! ndynami=0 --> no dynamics
160 ! ndynami=1 --> dynamics enabled
161 ! - nadvect : disable/enable ice transport
162 ! nadvect=0 --> no ice transport
163 ! nadvect=1 --> ice transport enabled
164 ! - ntimers : disable/enable timers
165 ! ntimers=0 --> no timers
166 ! ntimers=1 --> timers enabled
167 ! - ndyncor : correct water and salt non-conservation due to advection
168 ! ndyncor=0 --> no correction
169 ! ndyncor=1 --> correction
170 ! - ncdlssh : take ssh into account when computing concentration/dilution
171 ! ncdlssh=0 --> ssh not taken into account
172 ! ncdlssh=1 --> ssh taken into account
173 ! - niceage : disable/enable ice age computation
174 ! niceage=0 --> no ice age computation
175 ! niceage=1 --> ice age computation enabled
176 ! - nicesal : disable/enable ice salinity computation
177 ! nicesal=0 --> no ice salinity computation
178 ! nicesal=1 --> ice salinity computation enabled
179 ! - nmponds : disable/enable melt pond computation (for ice surface albedo)
180 ! nmponds=0 --> no melt ponds computation
181 ! nmponds=1 --> melt ponds computation enabled
182 ! - nsnwrad : snowfall radiative effect
183 ! nsnwrad=0 --> no radiative effect of snow melting into sea water
184 ! (recommended in case of coupling, if snow fall in
185 ! your atm. model does not cause any heat gain for the
186 ! atmosphere)
187 ! nsnwrad=1 --> generates a negative heat flux sent to the ocean by
188 ! Gelato, due to the melting of snow into the ocean
189 ! - nleviti : sea ice is levitating over the ocean or not
190 ! nleviti=0 --> sea ice is not levitating (a freshwater flux due to the
191 ! melting/freezing of ice is sent to the ocean model)
192 ! --> sea ice is levitating
193 ! - nsalflx : ice-ocean salt flux parameterisation
194 ! (if 2 or 3, check ocean topmost level dz parameter xhtopoc !)
195 ! nsalflx=1 --> approximated calculation
196 ! nsalflx=2 --> exact calculation
197 ! nsalflx=3 --> exact calculation, but SSS replaced with standard sal.
198 ! nsalflx=4 --> simplified calculation as in LIM2 (fixed ocean and ice reference salinity)
199 ! - nextqoc : ocean-ice heat flux
200 ! nextqoc=1 --> the %qoc given as an input is taken into account
201 ! nextqoc=0 --> the %qoc is computed by Gelato
202 ! - nicesub : ice sublimation
203 ! nicesub=1 --> take ice sublimation into account (non heat conservative)
204 ! nicesub=0 --> no ice sublimation
205 ! - cnflxin : input fluxes
206 ! cnflxin --> 'mixed' : only one flux, to share between water/ice
207 ! cnflxin --> 'double': one flux for water, one flux for ice
208 ! cnflxin --> 'multi' : one flux for water, one flux for each ice cat
209 !
210 nmkinit = 0
211 nrstout = 0
212 nrstgl4 = 1
213 nthermo = 1
214 ndynami = 0
215 nadvect = 0
216 ntimers = 0
217 ndyncor = 0
218 ncdlssh = 1
219 niceage = 1
220 nicesal = 1
221 nmponds = 1
222 nsnwrad = 1
223 nleviti = 1
224 nsalflx = 2
225 nextqoc = 0
226 nicesub = 1
227 cnflxin = 'double'
228 !
229 !
230 ! 2. Damping and restoring
231 ! -------------------------
232 !
233 ! - cfsidmp : sea ice fraction constraint
234 ! cfsidmp='NONE' --> no sea ice fraction constraint
235 ! cfsidmp='DAMP' --> damp
236 ! cfsidmp='PRESCRIBE' --> prescribe
237 ! - xfsidmpeft : sea ice fraction damping e-folding time (in days)
238 ! - chsidmp : sea ice thickness constraint
239 ! chsidmp='NONE' --> no sea ice thickness constraint
240 ! chsidmp='DAMP_ADD' --> damp (thickness of all ice categories is
241 ! modified by the same value: h_i => h_i + add)
242 ! chsidmp='DAMP_FAC' --> damp (thickness of all ice categories is
243 ! modified by the same factor: h_i => h_i * fac)
244 ! chsidmp='PRESCRIBE' --> prescribe
245 ! - xhsidmpeft : sea ice thickness damping e-folding time (in days)
246 !
247 cfsidmp='NONE'
248 xfsidmpeft=0.
249 chsidmp='NONE'
250 xhsidmpeft=0.
251 !
252 !
253 ! 3. Diagnostics output
254 ! ----------------------
255 !
256 ! - cdiafmt : diagnostics format
257 ! cdiafmt='GELATO' --> Gelato Vairmer format
258 ! cdiafmt='VMAR5' --> IPCC AR5 vairmer format
259 ! cdiafmt='NCAR5' --> IPCC AR5 NetCDF format (not active yet)
260 ! - cdialev : diagnostics level
261 ! . cdialev can include one, two or all of the letters b, d and t
262 ! . If cdiafmt='GELATO'
263 ! - 1: makes the 2D diag. file (2D fields), called
264 ! '2d.[ave|ins].vairmer'. Contains: ice concentration, thickness,
265 ! velocity components, thin ice+thick ice, snow thickness).
266 ! . - 2: add more detailed 2D diagnostics to the 2D diag file,
267 ! like: solar short wave flux, non solar flux, water flux crossing
268 ! the leads+sea ice ensemble...
269 ! . - 3: makes the 0d.ins.vairmer diag. file (0D fields).
270 ! Contains: sea ice area, extent, volume, for both hemispheres +
271 ! transports at most Arctic Straits
272 ! - Example: cdialev=13 or 31 means that you want only the 2d basic
273 ! diagnostics + 0d diagnostic.
274 ! . If cdiafmt='VMAR5' or 'NCAR5'
275 ! - 1: save only the priority 1 fields
276 ! - 2: save only the priority 2 fields
277 ! - 3: save only the priority 3 fields
278 ! - x: save only my personal fields (additional)
279 ! - note fields e.g. in priority 2 fields can have a space dimension
280 ! equal to grid size nxglo*nyglo or equal to 1
281 ! - VMAR5: output in Vairmer; NCAR5: output in NetCDF.
282 ! - Example: cdialev=123x means you want all AR5 fields + yours
283 ! - dttave : period for averaged fields (days, optional, default=365)
284 ! - navedia : average the output over dttave and over the whole run
285 ! - ninsdia : output delivered once per time step
286 ! - ndiamax : maximum number of diagnostic files
287 ! - nsavinp : allows to save gelato routine input in a file (used in
288 ! coupled mode)
289 ! nsavinp=0 --> gelato routine input is not saved
290 ! nsavinp=1 --> gelato routine input is saved in a file
291 ! - nsavout : allows to save gelato routine output in a file (used in
292 ! coupled mode)
293 ! nsavout=0 --> gelato routine input is not saved
294 ! nsavout=1 --> gelato routine input is saved in a file
295 ! - nupdbud : compute budgets (for model energy conservation tests)
296 ! nupdbud=0 --> no budgets computations (for operational runs)
297 ! nupdbud=1 --> budgets computations (for model validation)
298 ! - nprinto : GELATO prints output as follows
299 ! nprinto=0 --> minimum output print
300 ! nprinto=1 --> print fields statistics : mini, maxi, av.
301 ! nprinto=2 --> print fields + field statistics
302 ! - nprlast : GELATO prints output as nprinto levels (last time step only)
303 ! - cinsfld : list of fields to be delivered at every time step
304 ! (all -> deliver all fields)
305 ! Note that one line per requested field should be given, e.g.:
306 ! cinsfld = sit
307 ! cinsfld = sic
308 ! ...
309 !
310 cdiafmt = 'VMAR5'
311 cdialev = ''
312 dttave = 30.
313 navedia = 0
314 ninsdia = 0
315 ndiamax = 90
316 nsavinp = 0
317 nsavout = 0
318 nupdbud = 0
319 nprinto = 0
320 nprlast = 0
321 !
322 !
323 ! 4. Grid definition
324 ! -------------------
325 !
326 ! - cn_grdname : grid name radical. Defined the grid you are running on.
327 ! . Available (pre-coded) options are :
328 ! 'OPAG8', 'NEMO1', 'ORCA2' or 'MICOM'.
329 ! For these precoded grids, any nbndco, nxglo and nyglo values you
330 ! will specify in gltpar will be ignored by the code.
331 ! . You may specify another cgrdname, but then the nbndco, nxglo
332 ! and nyglo values you provide in gltpar MUST MAKE SENSE and will
333 ! be taken into account.
334 ! - rn_htopoc : reference thickness (in m) of the topmost ocean level
335 ! . This is important if Gelato is coupled to an ocean model, to
336 ! send the right concentration / dilution flux to the ocean.
337 !
338 cn_grdname = 'SURFEX'
339 rn_htopoc = 10.
340 !
341 !
342 ! 5. Run date position and time step
343 ! -----------------------------------
344 !
345 ! - nidate : initial date for running GELATO, YYYYMMDD (-)
346 ! - niter : number of iterations from reference date (-)
347 ! - dtt : time step for dynamics and thermodynamics (s)
348 !
349 nidate = 20010101
350 niter = 100000
351 dtt = xundef ! means : same time step as seaflux
352 !
353 !
354 ! 6. Number of ice categories
355 ! ----------------------------
356 !
357 ! - nt : number of ice thicknesses (-)
358 ! - thick : boundaries for thickness categories (-)
359 !
360 nt = 1
361 IF (ALLOCATED(thick)) DEALLOCATE( thick )
362 ALLOCATE( thick(nt+1) )
363 thick(1)= -.01
364 thick(2) = 1000.
365 !
366 !
367 ! 7. Number of layers in the ice-snow slab
368 ! -----------------------------------------
369 !
370 ! .. Number of layers when solving the problem of vertical heat
371 ! diffusion through the ice and snow slab. Note that if the
372 ! scheme is explicit, nslay=1 is compulsory.
373 !
374 ! - nilay : number of ice layers in vertical discretisation (-)
375 ! - nslay : number of snow layers in vertical discretisation (-)
376 ! - xh* : vertical coordinate parameters
377 ! If you need to run the model with constant vertical levels
378 ! (not recommended), specify xh1=1. and xh2=0.
379 !
380 nilay = 9
381 nslay = 1
382 xh0 = 4.392339514718992e-01
383 xh1 = 1.049607477174487e-01
384 xh2 = 9.507487632412231e-02
385 xh3 = 1.
386 xh4 = 5.208820443636069
387 !
388 !
389 ! 8. Elastic Viscous-Plastic sea ice rheology parameters
390 ! -------------------------------------------------------
391 !
392 ! - ntstp : number of dynamics time steps during one
393 ! thermodynamics time step.
394 ! - ndte : number of subcycles for velocity computations
395 ! during sea ice EVP dynamics.
396 !
397 ntstp = 1
398 ndte = 100
399 !
400 !
401 ! 9. Limit Values for sea ice
402 ! ----------------------------
403 !
404 ! - xfsimax : maximum allowable fractional area for sea ice
405 ! - xicethcr : ice thickness that represents the limit between thin
406 ! and thick ice (m)
407 ! - xhsimin : minimum allowable ice thickness
408 !
409 xfsimax = .995
410 xicethcr = .8
411 xhsimin = .2
412 !
413 !
414 ! 10. Parameterizations
415 ! -----------------------
416 !
417 ! .. If you need a standard parameterization of low clouds (not simulated
418 ! by your atmosphere model), a reasonable value for this parameter should
419 ! be 0.25. If you don't need this parameterization, use alblc=0.
420 ! (it is not recommended to use values other than 0...)
421 ! - alblc : albedo of low clouds
422 ! - xlmelt : lateral melting parameterization factor
423 ! - xswhdfr : fraction of the solar radiation absorbed by snow that
424 ! is involved in the vertical heat diffusion (the rest contributes to direct
425 ! warming/melting)
426 ! - albyngi : parameterisation of young ice albedo (exponential formulation)
427 ! albyngi=0. --> albedo of young ice does not depend on thickness
428 ! albyngi=1. --> albedo of young ice depends on thickness
429 ! - albimlt : albedo of melting ice
430 ! - albsmlt : albedo of melting snow
431 ! - albsdry : albedo of dry snow
432 !
433 alblc = 0.
434 xlmelt = 3.e-3
435 xswhdfr = 0.95
436 albyngi = 1.
437 albimlt = 0.56
438 albsmlt = 0.77
439 albsdry = 0.84
440 !
441 !
442 ! 11. Logical units
443 ! -------------------
444 !
445 ! - ngrdlu : unit for reading the grid
446 ! - nsavlu : unit for writing input/output fields for Gelato
447 ! - nrstlu : unit for reading/writing Gelato restart
448 ! - n0vilu : unit for writing 0D Glt Instantaneous diags
449 ! - n0valu : unit for writing 0D Glt Averaged diags
450 ! - n2vilu : unit for writing 2D Glt or IPCC-AR5 Instantaneous diags
451 ! - n2valu : unit for writing 2D Glt or IPCC-AR5 Averaged diags
452 ! - nxvilu : unit for writing Instantaneous additional diags (AR5 case)
453 ! - nxvalu : unit for writing Averaged additional diags (AR5 case)
454 ! - nibglu : unit for iceberg physics input/output
455 ! - nspalu : spare unit for personal use !
456 ! - noutlu : unit for GELATO output
457 ! - ntimlu : unit for GELATO timers
458 !
459 ngrdlu = 153
460 nsavlu = 111
461 nrstlu = 151
462 n0vilu = 123
463 n0valu = 125
464 n2vilu = 121
465 n2valu = 122
466 nxvilu = 133
467 nxvalu = 131
468 nibglu = 120
469 nspalu = 130
470 noutlu = iluout
471 ntimlu = 201
472 !
473 !
474 ! 12. Path to keep Gelato I/O fields
475 ! -----------------------------------
476 !
477 ! .. You must define this path (complete), but without "/" at the end if
478 ! you want to keep Gelato daily input/output variables (for example to
479 ! "replay" a simulation with input/output data obtained in coupled mode).
480 ! This variable is used only if nsavinp=1 or nsavout=1.
481 !
482 ! - ciopath : path for input/output fields to gelato routine
483 !
484 ciopath = '.'
485 
486 IF (lhook) CALL dr_hook('DEFAULT_SEAICE',1,zhook_handle)
487 !
488 !-------------------------------------------------------------------------------
489 !
490 END SUBROUTINE default_seaice
subroutine default_seaice(HPROGRAM, HINTERPOL_SIC, HINTERPOL_SIT, PFREEZING_SST, PSEAICE_TSTEP, PSIC_EFOLDING_TIME, PSIT_EFOLDING_TIME, PCD_ICE, PSI_FLX_DRV)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6