SURFEX v8.1
General documentation of Surfex
read_teb_veg_confn.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_teb_veg_conf_n (CHT, IO, HPROGRAM)
7 ! #######################################################
8 !
9 !!**** *READ_TEB_VEG_CONF* - routine to read the configuration for VEG
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 !! V. Masson *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 01/2003
35 !! P Le Moigne 09/2005 AGS modifs of L. Jarlan
36 !! P Le Moigne 09/2005 CSNOWRES option
37 !! Modified by P. Le Moigne (06/2006): seeding and irrigation
38 !! Modified by P. Le Moigne (05/2008): deep soil characteristics
39 !! B. Decharme 06/2013 delete CTOPREG
40 !-------------------------------------------------------------------------------
41 !
42 !* 0. DECLARATIONS
43 ! ------------
44 !
45 !
46 !
47 !
48 USE modd_ch_teb_n, ONLY : ch_teb_t
50 !
52 !
53 USE mode_pos_surf
54 !
56 USE modi_get_luout
57 USE modi_open_namelist
58 USE modi_close_namelist
59 !
61 !
62 USE modd_read_namelist, ONLY : lnam_read
63 USE modd_surf_par, ONLY : xundef
64 !
65 !
66 USE yomhook ,ONLY : lhook, dr_hook
67 USE parkind1 ,ONLY : jprb
68 !
69 IMPLICIT NONE
70 !
71 !* 0.1 Declarations of arguments
72 ! -------------------------
73 !
74 !
75 TYPE(ch_teb_t), INTENT(INOUT) :: CHT
76 TYPE(isba_options_t), INTENT(INOUT) :: IO
77 !
78  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling ISBA
79 
80 !
81 !* 0.2 Declarations of local variables
82 ! -------------------------------
83 !
84 !
85 LOGICAL :: GFOUND ! Return code when searching namelist
86 INTEGER :: ILUOUT ! logical unit of output file
87 INTEGER :: INAM ! logical unit of namelist file
88 INTEGER :: IMI
89 REAL(KIND=JPRB) :: ZHOOK_HANDLE
90 !-------------------------------------------------------------------------------
91 !
92 !* get output listing file logical unit
93 !
94 IF (lhook) CALL dr_hook('READ_TEB_VEG_CONF_N',0,zhook_handle)
95  CALL get_luout(hprogram,iluout)
96 !
98 !
99 IF (imi.NE.-1 .AND. lnam_read) THEN
100  CALL init_nam_teb_vegn(io)
101  CALL init_nam_teb_veg_agsn(io)
102  CALL init_nam_ch_controln(cht)
103  CALL init_nam_ch_teb_vegn(cht)
104  CALL init_nam_sgh_teb_vegn(io)
105 ENDIF
106 
107 IF (lnam_read) THEN
108  !
109  !* open namelist file
110  !
111  CALL open_namelist(hprogram,inam)
112  !
113  !* reading of namelist
114  ! -------------------
115  !
116  CALL posnam(inam,'NAM_ISBAN',gfound,iluout)
117  IF (gfound) READ(unit=inam,nml=nam_isban)
118  CALL posnam(inam,'NAM_ISBA_AGSN',gfound,iluout)
119  IF (gfound) READ(unit=inam,nml=nam_isba_agsn)
120 ! for the time being, chemistry is not implemented on gardens
121 ! CALL POSNAM(INAM,'NAM_CH_ISBAN',GFOUND,ILUOUT)
122 ! IF (GFOUND) READ(UNIT=INAM,NML=NAM_CH_ISBAn)
123  CALL posnam(inam,'NAM_CH_CONTROLN',gfound,iluout)
124  IF (gfound) READ(unit=inam,nml=nam_ch_controln)
125  CALL posnam(inam,'NAM_SGH_ISBAN',gfound,iluout)
126  IF (gfound) READ(unit=inam,nml=nam_sgh_isban)
127  !
128  CALL test_nam_var_surf(iluout,'CSCOND',cscond,'NP89','PL98')
129  CALL test_nam_var_surf(iluout,'CC1DRY',cc1dry,'DEF ','GB93')
130  CALL test_nam_var_surf(iluout,'CSOILFRZ',csoilfrz,'DEF','LWT')
131  CALL test_nam_var_surf(iluout,'CDIFSFCOND',cdifsfcond,'DEF ','MLCH')
132  CALL test_nam_var_surf(iluout,'CSNOWRES',csnowres,'DEF','RIL')
133  CALL test_nam_var_surf(iluout,'CCPSURF',ccpsurf,'DRY','HUM')
134  !
135  CALL test_nam_var_surf(iluout,'CRUNOFF',crunoff,'WSAT','DT92','SGH ','TOPD')
136  CALL test_nam_var_surf(iluout,'CKSAT',cksat,'DEF','SGH','EXP')
137  CALL test_nam_var_surf(iluout,'CHORT',chort,'DEF','SGH')
138  !
139  !* close namelist file
140  !
141  CALL close_namelist(hprogram,inam)
142  !
143 ENDIF
144 !
145 IF (imi.NE.-1) THEN
146  CALL update_nam_teb_vegn(io)
147  CALL update_nam_teb_veg_agsn(io)
148  CALL update_nam_ch_teb_vegn(cht)
149  CALL update_nam_ch_controln(cht)
150  CALL update_nam_sgh_teb_vegn(io)
151 ENDIF
152 IF (lhook) CALL dr_hook('READ_TEB_VEG_CONF_N',1,zhook_handle)
153 !
154 !-------------------------------------------------------------------------------
155 !
156 !* surface time-step forced by the atmosphere
157 !
158 !XTSTEP = XUNDEF
159 !
160 !-------------------------------------------------------------------------------
161 !
162 END SUBROUTINE read_teb_veg_conf_n
integer function get_current_model_index_surfex()
subroutine init_nam_sgh_teb_vegn(TGDO)
character(len=4) crunoff
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
character(len=3) cksat
real, parameter xundef
character(len=4) cc1dry
subroutine read_teb_veg_conf_n(CHT, IO, HPROGRAM)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine init_nam_teb_veg_agsn(TGDO)
subroutine close_namelist(HPROGRAM, KLUNAM)
character(len=3) csnowres
subroutine update_nam_teb_veg_agsn(TGDO)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
character(len=3) ccpsurf
subroutine init_nam_teb_vegn(TGDO)
logical lhook
Definition: yomhook.F90:15
subroutine init_nam_ch_controln(CHT)
character(len=4) cscond
subroutine update_nam_sgh_teb_vegn(TGDO)
character(len=3) csoilfrz
subroutine update_nam_teb_vegn(TGDO)
character(len=3) chort
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
subroutine update_nam_ch_teb_vegn(CHT)
subroutine update_nam_ch_controln(CHT)
subroutine init_nam_ch_teb_vegn(CHT)
character(len=4) cdifsfcond