SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
sfx_oasis_read_nam.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 sfx_oasis_read_nam(HPROGRAM,PTSTEP_SURF,HINIT)
7 !##################################################################
8 !
9 !!**** *SFX_OASIS_READ_NAM* - routine to read the configuration for SFX-OASIS coupling
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !!
28 !! AUTHOR
29 !! ------
30 !! B. Decharme *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 05/2008
35 !-------------------------------------------------------------------------------
36 !
37 !* 0. DECLARATIONS
38 ! ------------
39 !
41 !
42 USE modd_sfx_oasis, ONLY : loasis, xruntime, &
43  lcpl_land, lcpl_gw, lcpl_flood, &
44  lcpl_calving, lcpl_lake, &
45  lcpl_sea, lcpl_seaice
46 !
47 USE mode_pos_surf
48 !
49 USE modi_get_luout
50 USE modi_open_namelist
51 USE modi_close_namelist
52 !
53 USE modi_abor1_sfx
54 !
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 IMPLICIT NONE
59 !
60 !* 0.1 Declarations of arguments
61 ! -------------------------
62 !
63  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
64 REAL, INTENT(IN) :: ptstep_surf ! Surfex time step
65  CHARACTER(LEN=3), INTENT(IN), OPTIONAL :: hinit ! choice of fields to initialize
66 !
67 !* 0.2 Declarations of local parameter
68 ! -------------------------------
69 !
70 INTEGER, PARAMETER :: kin = 1
71 INTEGER, PARAMETER :: kout = 0
72  CHARACTER(LEN=5), PARAMETER :: yland = 'land'
73  CHARACTER(LEN=5), PARAMETER :: ylake = 'lake'
74  CHARACTER(LEN=5), PARAMETER :: ysea = 'ocean'
75 !
76 !* 0.3 Declarations of local variables
77 ! -------------------------------
78 !
79 LOGICAL :: gfound ! Return code when searching namelist
80 INTEGER :: iluout ! Listing id
81 INTEGER :: ilunam ! logical unit of namelist file
82  CHARACTER(LEN=20) :: ykey
83  CHARACTER(LEN=50) :: ycomment
84  CHARACTER(LEN=3) :: yinit
85 !
86 REAL(KIND=JPRB) :: zhook_handle
87 !
88 !-------------------------------------------------------------------------------
89 !
90 IF (lhook) CALL dr_hook('SFX_OASIS_READ_NAM',0,zhook_handle)
91 !
92 !
93 !* 0. Initialize :
94 ! ------------
95 !
96 lcpl_land = .false.
97 lcpl_gw = .false.
98 lcpl_flood = .false.
99 lcpl_calving = .false.
100 lcpl_lake = .false.
101 lcpl_sea = .false.
102 lcpl_seaice = .false.
103 !
104 IF(.NOT.loasis)THEN
105  IF (lhook) CALL dr_hook('SFX_OASIS_READ_NAM',1,zhook_handle)
106  RETURN
107 ENDIF
108 !
109 yinit = 'ALL'
110 IF(present(hinit))yinit=hinit
111 !
112  CALL get_luout(hprogram,iluout)
113 !
114 !* 1. Read namelists and check status :
115 ! --------------------------------
116 !
117  CALL open_namelist(hprogram,ilunam)
118 !
119  CALL posnam(ilunam,'NAM_SFX_LAND_CPL',gfound,iluout)
120 !
121 IF (gfound) THEN
122  READ(unit=ilunam,nml=nam_sfx_land_cpl)
123 ELSE
124  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
125  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
126  WRITE(iluout,*)'NAM_SFX_LAND_CPL not found : Surfex land not coupled with river routing'
127  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
128  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
129 ENDIF
130 !
131  CALL posnam(ilunam,'NAM_SFX_SEA_CPL',gfound,iluout)
132 !
133 IF (gfound) THEN
134  READ(unit=ilunam,nml=nam_sfx_sea_cpl)
135 ELSE
136  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
137  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
138  WRITE(iluout,*)'NAM_SFX_SEA_CPL not found : Surfex sea not coupled with ocean model'
139  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
140  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
141 ENDIF
142 !
143  CALL posnam(ilunam,'NAM_SFX_LAKE_CPL',gfound,iluout)
144 !
145 IF (gfound) THEN
146  READ(unit=ilunam,nml=nam_sfx_lake_cpl)
147 ELSE
148  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
149  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
150  WRITE(iluout,*)'NAM_SFX_LAKE_CPL not found : Surfex lake not coupled with ocean model'
151  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
152  WRITE(iluout,*)'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!'
153 ENDIF
154 !
155  CALL close_namelist(hprogram,ilunam)
156 !
157 IF(xtstep_cpl_land>0.0)lcpl_land=.true.
158 IF(xtstep_cpl_lake>0.0)lcpl_lake=.true.
159 IF(xtstep_cpl_sea >0.0)lcpl_sea =.true.
160 !
161 IF(.NOT.lcpl_land.AND..NOT.lcpl_sea)THEN
162  CALL abor1_sfx('SFX_OASIS_READ_NAM: OASIS USED BUT NAMELIST NOT FOUND')
163 ENDIF
164 !
165 !-------------------------------------------------------------------------------
166 !
167 !* 2. Check time step consistency
168 ! ---------------------------
169 !
170 IF(yinit/='PRE')THEN
171  IF(mod(xruntime,ptstep_surf)/=0.)THEN
172  WRITE(iluout,*)'! MOD(XRUNTIME,XTSTEP_SURF)/=0 !!!'
173  WRITE(iluout,*)'! XTSTEP_SURF (model timestep) must be a multiple of $RUNTIME in oasis namcouple !!!'
174  CALL abor1_sfx('SFX_OASIS_READ_NAM: XTSTEP_SURF must be a multiple of $RUNTIME in oasis namcouple !!!')
175  ENDIF
176 ENDIF
177 !
178 !-------------------------------------------------------------------------------
179 !
180 !* 3. Check status for Land surface fields
181 ! ------------------------------------
182 !
183 IF(lcpl_land)THEN
184 !
185  IF(yinit/='PRE')THEN
186  IF(mod(xtstep_cpl_land,ptstep_surf)/=0.)THEN
187  WRITE(iluout,*)'! MOD(XTSTEP_SURF,XTSTEP_CPL_LAND) /= 0 !'
188  WRITE(iluout,*)'XTSTEP_SURF =',ptstep_surf,'XTSTEP_CPL_LAND = ',xtstep_cpl_land
189  IF(ptstep_surf>xtstep_cpl_land) &
190  WRITE(iluout,*)'! XTSTEP_SURF (model timestep) is superiror to XTSTEP_CPL_LAND !'
191  CALL abor1_sfx('SFX_OASIS_READ_NAM: XTSTEP_SURF and XTSTEP_CPL_LAND not consistent !!!')
192  ENDIF
193  ENDIF
194 !
195 ! Land Output variable
196 !
197  ykey ='CRUNOFF'
198  ycomment='Surface runoff'
199  CALL check_field(crunoff,ykey,ycomment,yland,kout)
200 !
201  ykey ='CDRAIN'
202  ycomment='Deep drainage'
203  CALL check_field(cdrain,ykey,ycomment,yland,kout)
204 !
205 ! Particular case due to calving case
206 !
207  IF(len_trim(ccalving)>0)THEN
208  lcpl_calving = .true.
209  ENDIF
210 !
211  IF(lcpl_calving)THEN
212  ykey ='CCALVING'
213  ycomment='Calving flux'
214  CALL check_field(ccalving,ykey,ycomment,yland,kout)
215  ENDIF
216 !
217 ! Particular case due to water table depth / surface coupling
218 !
219  IF(len_trim(cwtd)>0.OR.len_trim(cfwtd)>0.OR.len_trim(crecharge)>0)THEN
220  lcpl_gw = .true.
221  ENDIF
222 !
223  IF(lcpl_gw)THEN
224 !
225 ! Output variable
226 !
227  ykey ='CRECHARGE'
228  ycomment='Groundwater recharge'
229  CALL check_field(crecharge,ykey,ycomment,yland,kout)
230 !
231 ! Input variable
232 !
233  ykey ='CWTD'
234  ycomment='Water table depth'
235  CALL check_field(cwtd,ykey,ycomment,yland,kin)
236 !
237  ykey ='CFWTD'
238  ycomment='Fraction of WTD to rise'
239  CALL check_field(cfwtd,ykey,ycomment,yland,kin)
240 !
241  ENDIF
242 !
243 ! Particular case due to floodplains coupling
244 !
245  IF(len_trim(csrcflood)>0.OR.len_trim(cfflood)>0.OR.len_trim(cpiflood)>0)THEN
246  lcpl_flood = .true.
247  ENDIF
248 !
249  IF(lcpl_flood)THEN
250 !
251 ! Output variable
252 !
253  ykey ='CSRCFLOOD'
254  ycomment='flood freshwater flux'
255  CALL check_field(csrcflood,ykey,ycomment,yland,kout)
256 !
257 ! Input variable
258 !
259  ykey ='CFFLOOD'
260  ycomment='Flood fraction'
261  CALL check_field(cfflood,ykey,ycomment,yland,kin)
262 !
263  ykey ='CPIFLOOD'
264  ycomment='Flood potential infiltration'
265  CALL check_field(cpiflood,ykey,ycomment,yland,kin)
266 !
267  ENDIF
268 !
269 ENDIF
270 !
271 !-------------------------------------------------------------------------------
272 !
273 !* 4. Check status for Land surface fields
274 ! ------------------------------------
275 !
276 IF(lcpl_lake)THEN
277 !
278  IF(yinit/='PRE')THEN
279  IF(mod(xtstep_cpl_lake,ptstep_surf)/=0.)THEN
280  WRITE(iluout,*)'! MOD(XTSTEP_SURF,XTSTEP_CPL_LAKE) /= 0 !'
281  WRITE(iluout,*)'XTSTEP_SURF =',ptstep_surf,'XTSTEP_CPL_LAKE = ',xtstep_cpl_lake
282  IF(ptstep_surf>xtstep_cpl_lake) &
283  WRITE(iluout,*)'! XTSTEP_SURF (model timestep) is superiror to XTSTEP_CPL_LAKE !'
284  CALL abor1_sfx('SFX_OASIS_READ_NAM: XTSTEP_SURF and XTSTEP_CPL_LAKE not consistent !!!')
285  ENDIF
286  ENDIF
287 !
288 ! Output variables
289 !
290  ykey ='CLAKE_EVAP'
291  ycomment='Evaporation rate'
292  CALL check_field(clake_evap,ykey,ycomment,ylake,kout)
293 !
294  ykey ='CLAKE_RAIN'
295  ycomment='Rainfall rate'
296  CALL check_field(clake_rain,ykey,ycomment,ylake,kout)
297 !
298  ykey ='CLAKE_SNOW'
299  ycomment='Snowfall rate'
300  CALL check_field(clake_snow,ykey,ycomment,ylake,kout)
301 !
302  ykey ='CLAKE_WATF'
303  ycomment='Freshwater flux'
304  CALL check_field(clake_watf,ykey,ycomment,ylake,kout)
305 !
306 ENDIF
307 !
308 !-------------------------------------------------------------------------------
309 !
310 !* 5. Check status for Sea fields
311 ! ---------------------------
312 !
313 IF(lcpl_sea)THEN
314 !
315  IF(yinit/='PRE')THEN
316  IF(mod(xtstep_cpl_sea,ptstep_surf)/=0.)THEN
317  WRITE(iluout,*)'! MOD(XTSTEP_SURF,XTSTEP_CPL_SEA) /= 0 !'
318  WRITE(iluout,*)'XTSTEP_SURF =',ptstep_surf,'XTSTEP_CPL_SEA = ',xtstep_cpl_sea
319  IF(ptstep_surf>xtstep_cpl_sea) &
320  WRITE(iluout,*)'! XTSTEP_SURF (model timestep) is superiror to XTSTEP_CPL_SEA !'
321  CALL abor1_sfx('SFX_OASIS_READ_NAM: XTSTEP_SURF and XTSTEP_CPL_SEA not consistent !!!')
322  ENDIF
323  ENDIF
324 !
325 ! Sea Output variables
326 !
327  ykey ='CSEA_FWSU'
328  ycomment='zonal wind stress'
329  CALL check_field(csea_fwsu,ykey,ycomment,ysea,kout)
330 !
331  ykey ='CSEA_FWSV'
332  ycomment='meridian wind stress'
333  CALL check_field(csea_fwsv,ykey,ycomment,ysea,kout)
334 !
335  ykey ='CSEA_HEAT'
336  ycomment='Non solar net heat flux'
337  CALL check_field(csea_heat,ykey,ycomment,ysea,kout)
338 !
339  ykey ='CSEA_SNET'
340  ycomment='Solar net heat flux'
341  CALL check_field(csea_snet,ykey,ycomment,ysea,kout)
342 !
343  ykey ='CSEA_WIND'
344  ycomment='module of 10m wind speed'
345  CALL check_field(csea_wind,ykey,ycomment,ysea,kout)
346 !
347  ykey ='CSEA_FWSM'
348  ycomment='module of wind stress'
349  CALL check_field(csea_fwsm,ykey,ycomment,ysea,kout)
350 !
351  ykey ='CSEA_EVAP'
352  ycomment='Evaporation rate'
353  CALL check_field(csea_evap,ykey,ycomment,ysea,kout)
354 !
355  ykey ='CSEA_RAIN'
356  ycomment='Rainfall rate'
357  CALL check_field(csea_rain,ykey,ycomment,ysea,kout)
358 !
359  ykey ='CSEA_SNOW'
360  ycomment='Snowfall rate'
361  CALL check_field(csea_snow,ykey,ycomment,ysea,kout)
362 !
363  ykey ='CSEA_WATF'
364  ycomment='Freshwater flux'
365  CALL check_field(csea_watf,ykey,ycomment,ysea,kout)
366 !
367 ! Sea Input variables
368 !
369  ykey ='CSEA_SST'
370  ycomment='Sea surface temperature'
371  CALL check_field(csea_sst,ykey,ycomment,ysea,kin)
372 !
373  ykey ='CSEA_UCU'
374  ycomment='Sea u-current stress'
375  CALL check_field(csea_ucu,ykey,ycomment,ysea,kin)
376 !
377  ykey ='CSEA_VCU'
378  ycomment='Sea v-current stress'
379  CALL check_field(csea_vcu,ykey,ycomment,ysea,kin)
380 !
381 ! Sea-ice fluxes
382 !
383  IF(len_trim(cseaice_heat)>0.OR.len_trim(cseaice_snet)>0.OR. &
384  len_trim(cseaice_evap)>0.OR.len_trim(cseaice_sit )>0.OR. &
385  len_trim(cseaice_cvr )>0.OR.len_trim(cseaice_alb )>0 )THEN
386  lcpl_seaice=.true.
387  ENDIF
388 !
389  IF(lcpl_seaice)THEN
390 !
391 ! Sea-ice Output variables
392 !
393  ykey ='CSEAICE_HEAT'
394  ycomment='Sea-ice non solar net heat flux'
395  CALL check_field(cseaice_heat,ykey,ycomment,ysea,kout)
396 !
397  ykey ='CSEAICE_SNET'
398  ycomment='Sea-ice solar net heat flux'
399  CALL check_field(cseaice_snet,ykey,ycomment,ysea,kout)
400 !
401  ykey ='CSEAICE_EVAP'
402  ycomment='Sea-ice sublimation'
403  CALL check_field(cseaice_evap,ykey,ycomment,ysea,kout)
404 !
405 ! Sea-ice Input variables
406 !
407  ykey ='CSEAICE_SIT'
408  ycomment='Sea-ice temperature'
409  CALL check_field(cseaice_sit,ykey,ycomment,ysea,kin)
410 !
411  ykey ='CSEAICE_CVR'
412  ycomment='Sea-ice cover'
413  CALL check_field(cseaice_cvr,ykey,ycomment,ysea,kin)
414 !
415  ykey ='CSEAICE_ALB'
416  ycomment='Sea-ice albedo'
417  CALL check_field(cseaice_alb,ykey,ycomment,ysea,kin)
418 !
419  ENDIF
420 !
421 ENDIF
422 !
423 IF (lhook) CALL dr_hook('SFX_OASIS_READ_NAM',1,zhook_handle)
424 !
425 !-------------------------------------------------------------------------------
426  CONTAINS
427 !-------------------------------------------------------------------------------
428 !
429 SUBROUTINE check_field(HFIELD,HKEY,HCOMMENT,HTYP,KID)
430 !
431 IMPLICIT NONE
432 !
433  CHARACTER(LEN=*), INTENT(IN) :: hfield
434  CHARACTER(LEN=*), INTENT(IN) :: hkey
435  CHARACTER(LEN=*), INTENT(IN) :: hcomment
436  CHARACTER(LEN=*), INTENT(IN) :: htyp
437 INTEGER, INTENT(IN) :: kid
438 !
439  CHARACTER(LEN=20) :: ywork
440  CHARACTER(LEN=20) :: ynamelist
441  CHARACTER(LEN=128) :: ycomment1
442  CHARACTER(LEN=128) :: ycomment2
443 LOGICAL :: lstop
444 !
445 REAL(KIND=JPRB) :: zhook_handle
446 !
447 IF (lhook) CALL dr_hook('SFX_OASIS_READ_NAM:CHECK_FIELD',0,zhook_handle)
448 !
449 IF(len_trim(hfield)==0)THEN
450 !
451  IF(kid==0)THEN
452  ywork=trim(htyp)//' - SFX'
453  ELSE
454  ywork='SFX - '//trim(htyp)
455  ENDIF
456 !
457  SELECT CASE (htyp)
458  CASE(yland)
459  ynamelist='NAM_SFX_LAND_CPL'
460  CASE(ysea)
461  ynamelist='NAM_SFX_SEA_CPL'
462  CASE(ylake)
463  ynamelist='NAM_SFX_LAKE_CPL'
464  CASE default
465  CALL abor1_sfx('SFX_OASIS_READ_NAM: TYPE NOT SUPPORTED OR IMPLEMENTD : '//trim(htyp))
466  END SELECT
467 !
468  ycomment1= 'SFX_OASIS_READ_NAM: '//trim(hcomment)//' is not done for '//trim(ywork)//' coupling'
469  ycomment2= 'SFX_OASIS_READ_NAM: Namelist key '//trim(hkey)//' is not in '//trim(ynamelist)
470 !
471  WRITE(iluout,*)trim(ycomment1)
472  WRITE(iluout,*)trim(ycomment2)
473 !
474 ! For oceanic coupling do not stop the model if a field from surfex to ocean is
475 ! not done because many particular case can be used
476 !
477  IF(kid==0.AND.htyp/=yland)THEN
478  lstop=.false.
479  ELSE
480  lstop=.true.
481  ENDIF
482 !
483  IF(lstop)THEN
484  CALL abor1_sfx(ycomment1)
485  ENDIF
486 !
487 ENDIF
488 !
489 IF (lhook) CALL dr_hook('SFX_OASIS_READ_NAM:CHECK_FIELD',1,zhook_handle)
490 !
491 END SUBROUTINE check_field
492 !
493 !-------------------------------------------------------------------------------
494 !
495 END SUBROUTINE sfx_oasis_read_nam
subroutine sfx_oasis_read_nam(HPROGRAM, PTSTEP_SURF, HINIT)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine check_field(HFIELD, HKEY, HCOMMENT, HTYP, KID)
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)