SURFEX v8.1
General documentation of Surfex
read_seaicen.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 read_seaice_n (G, S, HPROGRAM,KLU,KLUOUT)
7 ! #########################################
8 !
9 !!**** *READ_SEAICE_n* - read seaice scheme variables
10 !!
11 !!
12 !! PURPOSE : feed seaice scheme state variable and 'domain' structure
13 !! -------
14 !!
15 !!** METHOD :
16 !! -------
17 !! For now, only Gelato model is handled
18 !!
19 !! for state variable : quite standard in Surfex : use READ_SURF with
20 !! relevant field names (same names as in genuine gelato restarts)
21 !! for domain information : copy from MODD_SEAFLUX_GRID
22 !! for bathymetry : copy from MODD_SEAFLUX
23 !!
24 !! EXTERNALS : READ_SURF, GLTOOLS_ALLOC, GET_TYPE_DIM, ABOR1_SFX
25 !! --------
26 !!
27 !! IMPLICIT ARGUMENTS : Gelato state variable, and a few namelist parameters
28 !! ------------------
29 !!
30 !! REFERENCE : routine restartr in original Gelato sources (V6.0.20)
31 !! ---------
32 !!
33 !! AUTHOR : S. Sénési *Meteo France*
34 !! ------
35 !!
36 !! MODIFICATIONS
37 !! -------------
38 !! Original 01/2014
39 !-------------------------------------------------------------------------------
40 !
41 !* 0. DECLARATIONS
42 ! ------------
43 !
44 !
45 !
46 !
47 !
48 USE modd_sfx_grid_n, ONLY : grid_t
49 USE modd_seaflux_n, ONLY : seaflux_t
50 !
51 USE modd_csts, ONLY : xpi, xttsi, xtt
52 USE modd_surf_par, ONLY : xundef
53 USE modd_sfx_oasis, ONLY : lcpl_seaice
54 USE modd_water_par, ONLY : xalbseaice
55 !
56 USE modd_types_glt, ONLY : t_glt
57 USE modd_glt_param, ONLY : nl, nt, nx, ny, nxglo, nyglo, xdomsrf, &
58  xdomsrf_g, nprinto, cfsidmp, chsidmp, &
59  xfsidmpeft, xhsidmpeft, ntd
60 USE modd_glt_const_thm, ONLY : epsil1
61 USE lib_mpp, ONLY : mpp_sum
62 USE modi_glt_sndatmf
63 USE modi_gltools_alloc
64 USE modi_gltools_readnam
65 !
67 USE modi_interpol_sst_mth
68 !
69 USE modi_get_luout
70 USE modi_abor1_sfx
71 !
72 USE yomhook ,ONLY : lhook, dr_hook
73 USE parkind1 ,ONLY : jprb
74 !
75 IMPLICIT NONE
76 !
77 !* 0.1 Declarations of arguments
78 ! -------------------------
79 !
80 !
81 !
82 !
83 TYPE(grid_t), INTENT(INOUT) :: G
84 TYPE(seaflux_t), INTENT(INOUT) :: S
85 !
86  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
87 INTEGER, INTENT(IN) :: KLU ! number of sea patch point
88 INTEGER, INTENT(IN) :: KLUOUT
89 !
90 !* 0.2 Declarations of local variables
91 ! -------------------------------
92 !
93 INTEGER :: IRESP ! Error code after reading
94 !
95 INTEGER :: JMTH, INMTH
96  CHARACTER(LEN=2 ) :: YMTH
97  CHARACTER(LEN=5) :: YLVL
98 !
99  CHARACTER(LEN=12) :: YCATEG ! category to read
100  CHARACTER(LEN=12) :: YLEVEL ! Level to read
101  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
102  CHARACTER(LEN=200) :: YMESS ! Error Message
103 !
104 INTEGER :: JX,JK,JL ! loop counter on ice categories and layers and grid points
105 INTEGER :: inl_in_file,int_in_file ! file values for ice catgories and layers numbers
106 REAL :: ZFSIT
107 !
108 REAL(KIND=JPRB) :: ZHOOK_HANDLE
109 !
110 !-------------------------------------------------------------------------------
111 IF (lhook) CALL dr_hook('READ_SEAICE_n',0,zhook_handle)
112 !
113 IF (.NOT.s%LHANDLE_SIC) THEN
114  ALLOCATE(s%XSIC(0))
115  IF (lhook) CALL dr_hook('READ_SEAICE_n',1,zhook_handle)
116  RETURN
117 ENDIF
118 !
119 nx=klu
120 !
121 ALLOCATE(s%XSIC(klu))
122 s%XSIC(:)=xundef
123 !
124 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
125 !
126 ! Dealing with external sea-ice cover data (either for nudging or forcing)
127 !
128 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
129 !
130 IF(s%LINTERPOL_SIC)THEN
131  !
132  ALLOCATE(s%XFSIC(klu))
133  !
134  !Precedent, Current, Next, and Second-next Monthly SIC
135  inmth=4
136  !
137  ALLOCATE(s%XSIC_MTH(klu,inmth))
138  DO jmth=1,inmth
139  WRITE(ymth,'(I2)') (jmth-1)
140  yrecfm='SIC_MTH'//adjustl(ymth(:len_trim(ymth)))
141  CALL read_surf(hprogram,yrecfm,s%XSIC_MTH(:,jmth),iresp)
142  CALL check_seaice(yrecfm,s%XSIC_MTH(:,jmth))
143  ENDDO
144  !
145  CALL interpol_sst_mth(s,'C')
146  !
147  IF (any(s%XFSIC(:)>1.0).OR.any(s%XFSIC(:)<0.0)) THEN
148  CALL abor1_sfx('READ_SEAICE_n: FSIC should be >=0 and <=1')
149  ENDIF
150  !
151 ELSE
152  !
153  ALLOCATE(s%XFSIC(0))
154  ALLOCATE(s%XSIC_MTH(0,0))
155  !
156 ENDIF
157 !
158 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
159 !
160 ! Worrying about a seaice scheme
161 !
162 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
163 !
164  CALL read_surf(hprogram,'SEAICE_SCHEM',s%CSEAICE_SCHEME,iresp)
165 !
166 IF (trim(s%CSEAICE_SCHEME) == 'NONE' ) THEN
167  IF (s%LINTERPOL_SIC ) THEN
168  s%XTICE=s%XSST
169  s%XSIC=s%XFSIC
170  s%XICE_ALB=xalbseaice
171  IF (lhook) CALL dr_hook('READ_SEAICE_n',1,zhook_handle)
172  RETURN
173  ELSE
174  CALL abor1_sfx("READ_SEAICE_n: MUST HAVE CINTERPOL_SIC /= NONE WITH CSEAICE_SCHEME == NONE ")
175  ENDIF
176 ELSE
177  IF (trim(s%CSEAICE_SCHEME) /= 'GELATO') THEN
178  WRITE(kluout,*)'READ_SEAICE_n:CSEAICE_SCHEME read in PREP, ',s%CSEAICE_SCHEME,', is not yet handled'
179  CALL abor1_sfx("READ_SEAICE_n:CAN ONLY HANDLE GELATO SEAICE MODEL YET (and not the one quoted in PREP)")
180  ENDIF
181 ENDIF
182 !
183 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
184 !
185 ! Start of Gelato specifics
186 !
187 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
188 !
189 IF(lcpl_seaice)THEN
190  CALL abor1_sfx('READ_SEAICEN: CANNOT YET MANAGE BOTH TRUE LCPL_SEAICE AND CSEAICE_SCHEME = GELATO')
191 ENDIF
192 nxglo=nx
193 #if ! defined in_arpege
194  CALL mpp_sum(nxglo) ! Should also sum up over NPROMA blocks, in Arpege; but not that easy....
195 #else
196 IF (nprinto > 0) THEN
197  WRITE(kluout,*)'Gelato cannot yet compute global averages when running in Arpege (because of collective comm vs. NPROMA blocks)'
198 ENDIF
199 nxglo=max(nxglo,1)
200 #endif
201 !
202 ! Use convention XSIC_EFOLDING_TIME=0 for avoiding any relaxation
203 ! toward SIC observation and impose it.
204 !
205 IF(s%LINTERPOL_SIC)THEN
206  IF (s%XSIC_EFOLDING_TIME==0.0) THEN
207  cfsidmp='PRESCRIBE'
208  ELSE
209  cfsidmp='DAMP'
210  xfsidmpeft=s%XSIC_EFOLDING_TIME
211  ENDIF
212 ENDIF
213 !
214 IF(s%LINTERPOL_SIT)THEN
215  IF (s%XSIT_EFOLDING_TIME==0.0) THEN
216  chsidmp='PRESCRIBE'
217  ELSE
218  chsidmp='DAMP_FAC'
219  xhsidmpeft= s%XSIT_EFOLDING_TIME
220  ENDIF
221 ENDIF
222 !
223 !* Physical dimensions are set for Gelato , as a 1D field (second dimension is degenerated)
224 !
225 ! Supersedes Gelato hard defaults with a Gelato genuine namelist
226 ! if available (for Gelato wizzards !)
227  CALL gltools_readnam(.false.,kluout)
228 !
229 ny=1
230 nyglo=1
231  CALL gltools_alloc(s%TGLT)
232 !
233 !* 0. Check dimensions : number of layers and ice categories
234 !
235  CALL read_surf(hprogram,'ICENL',inl_in_file,iresp)
236 IF (inl_in_file /= nl) THEN
237  WRITE(ymess,'("Mismatch in # of seaice layers : prep=",I2," nml=",I2)') inl_in_file, nl
238  CALL abor1_sfx(ymess)
239 END IF
240  CALL read_surf(hprogram,'ICENT',int_in_file,iresp)
241 IF (int_in_file /= nt) THEN
242  WRITE(ymess,'("Mismatch in # of seaice categories : prep=",I2," nml=",I2)') int_in_file, nt
243  CALL abor1_sfx(ymess)
244 END IF
245 !
246 !* 1. (Semi-)prognostic fields with only space dimension(s) :
247 !
248  CALL read_surf(hprogram,'ICEUSTAR',s%TGLT%ust(:,1),iresp)
249 !
250 !* 2. Prognostic fields with space and ice-category dimension(s) :
251 !
252 DO jk=1,nt
253  WRITE(ylvl,'(I2)') jk
254  ycateg='_'//adjustl(ylvl)
255  ! .. Read sea ice age for type JK
256  CALL read_surf(hprogram,'ICEAGE'//ycateg,s%TGLT%sit(jk,:,1)%age,iresp)
257  ! .. Read melt pond volume for type JK
258  CALL read_surf(hprogram,'ICEVMP'//ycateg,s%TGLT%sit(jk,:,1)%vmp,iresp)
259  ! .. Read sea ice surface albedo for type JK
260  CALL read_surf(hprogram,'ICEASN'//ycateg,s%TGLT%sit(jk,:,1)%asn,iresp)
261  ! .. Read sea ice fraction for type JK
262  CALL read_surf(hprogram,'ICEFSI'//ycateg, s%TGLT%sit(jk,:,1)%fsi,iresp)
263  ! .. Read sea ice thickness for type JK
264  CALL read_surf(hprogram,'ICEHSI'//ycateg, s%TGLT%sit(jk,:,1)%hsi,iresp)
265  ! .. Read sea ice salinity for type JK
266  CALL read_surf(hprogram,'ICESSI'//ycateg, s%TGLT%sit(jk,:,1)%ssi,iresp)
267  ! .. Read sea ice surface temperature for type JK
268  CALL read_surf(hprogram,'ICETSF'//ycateg, s%TGLT%sit(jk,:,1)%tsf,iresp)
269  ! .. Read snow thickness for type JK
270  CALL read_surf(hprogram,'ICEHSN'//ycateg, s%TGLT%sit(jk,:,1)%hsn,iresp)
271  ! .. Read snow density for type JK
272  CALL read_surf(hprogram,'ICERSN'//ycateg, s%TGLT%sit(jk,:,1)%rsn,iresp)
273  !
274  !* 3. Prognostic fields with space, ice-category and layer dimensions :
275  !
276  DO jl=1,nl
277  WRITE(ylvl,'(I2)') jl
278  ylevel=ycateg(1:len_trim(ycateg))//'_'//adjustl(ylvl)
279  ! .. Read sea ice vertical gltools_enthalpy profile for type JK and level JL
280  CALL read_surf(hprogram,'ICEH'//ylevel, s%TGLT%sil(jl,jk,:,1)%ent,iresp)
281  END DO
282 END DO
283 !
284 ! 4. Compute ice class existence boolean from ice fractions:
285 !
286 WHERE ( s%TGLT%sit(:,:,1)%fsi<epsil1 )
287  s%TGLT%sit(:,:,1)%esi = .false.
288 ELSEWHERE
289  s%TGLT%sit(:,:,1)%esi = .true.
290 ENDWHERE
291 !
292 ! 4.1 Run original Gelato checks on values read in restart
293 !
294 ! .. Detect negative ice concentrations
295 !
296 DO jx=1,nx
297  DO jl=1,nt
298  IF ( s%TGLT%sit(jl,jx,1)%fsi<0. ) THEN
299  WRITE(kluout,*) &
300  '**** WARNING **** Correcting problem in ice conc. < 0 at i=', &
301  1,' j=',jx,' k=',jl
302  s%TGLT%sit(jl,jx,1)%fsi = 0.
303  ENDIF
304  END DO
305  !
306  zfsit = sum( s%TGLT%sit(:,jx,1)%fsi )
307  !
308  ! .. Detect total concentrations that exceed unity
309  !
310  IF ( zfsit>1. ) THEN
311  WRITE(kluout,*) &
312  '**** WARNING **** Correcting problem in total ice conc. >1 at i=', &
313  1,' j=',jx,' fsi=',zfsit
314  s%TGLT%sit(:,jx,1)%fsi = s%TGLT%sit(:,jx,1)%fsi / zfsit
315  ENDIF
316  !
317  ! .. Detect non zero concentrations but zero thickness (no consequence)
318  !
319  WHERE( s%TGLT%sit(:,jx,1)%fsi>epsil1 .AND. s%TGLT%sit(:,jx,1)%hsi<epsil1)
320  s%TGLT%sit(:,jx,1)%fsi=0.
321  s%TGLT%sit(:,jx,1)%hsi=0.
322  s%TGLT%sit(:,jx,1)%hsn=0.
323  ENDWHERE
324  !
325 END DO
326 
327 ! 5. Initalize Gelato domain parameters
328 !
329 ! All points of Surfex 1D grid in seaflux are sea points
330 !
331 s%TGLT%dom(:,1)%tmk=1
332 s%TGLT%dom(:,1)%imk=1
333 !
334 ! Masks for U- and V- grid point are not used
335 !
336 s%TGLT%dom(:,1)%umk=1
337 s%TGLT%dom(:,1)%vmk=1
338 !
339 ! lat,lon,srf are inherited from seaflux grid
340 !
341 s%TGLT%dom(:,1)%lon=g%XLON(:)*xpi/180.
342 s%TGLT%dom(:,1)%lat=g%XLAT(:)*xpi/180.
343 !
344 ! Except in Gelato dynamics, mesh lengths are used only to compute mesh area
345 ! Hence, a simple setting can be used
346 !
347 s%TGLT%dom(:,1)%dxc=g%XMESH_SIZE(:)**0.5
348 s%TGLT%dom(:,1)%dyc=s%TGLT%dom(:,1)%dxc
349 s%TGLT%dom(:,1)%srf=g%XMESH_SIZE(:)
350 !
351 ! Surface of local and global ocean domain (ghost points are masked out)
352 !
353 xdomsrf = sum( s%TGLT%dom(:,1)%srf, mask=(s%TGLT%dom(:,1)%tmk==1) )
354 xdomsrf_g = xdomsrf
355 #if ! defined in_arpege
356  CALL mpp_sum(xdomsrf_g)
357 #else
358 ! Avoid zero divide in Gelato computation of global area averages
359 xdomsrf_g = max(xdomsrf_g, 1.e-9)
360 #endif
361 !
362 ! 7. Initalize Gelato time parameters
363 !
364 s%TGLT%ind%beg=1
365 !
366 ! Dummy high value for end time. Implies only that Gelato won't output
367 ! its own format of run-long averaged diagnostics (which are useless
368 ! in Surfex diags logic)
369 !
370 s%TGLT%ind%end=50000000
371 !
372 ! 8. Initalize Gelato bathymetry - change sign w.r.t Surfex
373 !
374 s%TGLT%bat(:,1)=-s%XSEABATHY
375 !
376 !
377 !* Sea ice thickness nudging data
378 !
379 IF(s%LINTERPOL_SIT)THEN
380  !
381  ALLOCATE(s%XFSIT(klu))
382  !
383  !Precedent, Current, Next, and Second-next Monthly SIT
384  inmth=4
385  !
386  ALLOCATE(s%XSIT_MTH(klu,inmth))
387  DO jmth=1,inmth
388  WRITE(ymth,'(I2)') (jmth-1)
389  yrecfm='SIT_MTH'//adjustl(ymth(:len_trim(ymth)))
390  CALL read_surf(hprogram,yrecfm,s%XSIT_MTH(:,jmth),iresp)
391  CALL check_seaice(yrecfm,s%XSIT_MTH(:,jmth))
392  ENDDO
393  !
394  CALL interpol_sst_mth(s,'H')
395  !
396 ELSE
397  !
398  ALLOCATE(s%XFSIT(0))
399  ALLOCATE(s%XSIT_MTH(0,0))
400  !
401 ENDIF
402 !
403 !! Initialize the coupling variables with 'snapshot' prognostic variables
404 ! (for now, averaged over ice categories)
405 !
406  CALL glt_sndatmf( s%TGLT, xttsi - xtt )
407 s%XSIC(:) = s%TGLT%ice_atm(1,:,1)%fsi
408 s%XTICE(:) = s%TGLT%ice_atm(1,:,1)%tsf
409 s%XICE_ALB(:) = s%TGLT%ice_atm(1,:,1)%alb
410 !
411 ! Must init ocean mixed layer temp with sensible value for getting correct diag for time step=0
412 s%TGLT%oce_all(:,1)%tml=s%XSST(:)
413 !
414 IF (lhook) CALL dr_hook('READ_SEAICE_n',1,zhook_handle)
415 !
416 !-------------------------------------------------------------------------------
417 CONTAINS
418 !-------------------------------------------------------------------------------
419 !
420 SUBROUTINE check_seaice(HFIELD,PFIELD)
421 !
422 !
423 IMPLICIT NONE
424 !
425  CHARACTER(LEN=12), INTENT(IN) :: HFIELD
426 REAL, DIMENSION(:), INTENT(IN) :: PFIELD
427 !
428 REAL :: ZMAX,ZMIN
429 INTEGER :: JI, IERRC
430 !
431 REAL(KIND=JPRB) :: ZHOOK_HANDLE
432 !
433 IF (lhook) CALL dr_hook('READ_SEAICE_n:CHECK_SEAICE',0,zhook_handle)
434 !
435 zmin=-1.0e10
436 zmax=1.0e10
437 !
438 ierrc=0
439 !
440 DO ji=1,klu
441  IF(pfield(ji)>zmax.OR.pfield(ji)<zmin)THEN
442  ierrc=ierrc+1
443  WRITE(kluout,*)'PROBLEM FIELD '//trim(hfield)//' =',pfield(ji),&
444  'NOT REALISTIC AT LOCATION (LAT/LON)',g%XLAT(ji),g%XLON(ji)
445  ENDIF
446 ENDDO
447 !
448 IF(ierrc>0) CALL abor1_sfx('READ_SEAICE_n: FIELD '//trim(hfield)//' NOT REALISTIC')
449 !
450 IF (lhook) CALL dr_hook('READ_SEAICE_n:CHECK_SEAICE',1,zhook_handle)
451 
452 END SUBROUTINE check_seaice
453 !
454 !------------------------------------------------------------------------------
455 !
456 END SUBROUTINE read_seaice_n
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
real, save xttsi
Definition: modd_csts.F90:67
real, save xalbseaice
real, save xpi
Definition: modd_csts.F90:43
subroutine check_seaice(HFIELD, PFIELD)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
subroutine read_seaice_n(G, S, HPROGRAM, KLU, KLUOUT)
Definition: read_seaicen.F90:7
subroutine interpol_sst_mth(S, HFLAG)
integer, parameter jprb
Definition: parkind1.F90:32
intent(out) overrides sub arrays one Sort by the least significant key first sum(iindex(1:n))
logical lhook
Definition: yomhook.F90:15
static int mask
Definition: ifssig.c:38
real, save xtt
Definition: modd_csts.F90:66