SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_nam_topd.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 ! ##############################################################
7  SUBROUTINE read_nam_topd(HPROGRAM,&
8  obudget_topd,knb_topd,&
9  ostock_topd,&
10  knb_stock,knb_restart,&
11  kfreq_maps_wg,kfreq_maps_asat,kfreq_maps_runoff,&
12  pspeedr,pspeedg,pspeedh,pqinit,prtop_d2)
13 ! ##############################################################
14 !
15 !!**** *READ_NAM TOPD* reads namelist NAM_TOPD
16 !!
17 !! PURPOSE
18 !! -------
19 !!
20 !! NAM_TOPD is a namelist used to define whether Topmodel coupling
21 !! is performed or not and the time step ratio between hydrological
22 !! model and ISBA.
23 !! This routine aims at reading and initialising those variables.
24 !!
25 !! METHOD
26 !! ------
27 !!
28 !
29 !! EXTERNAL
30 !! --------
31 !!
32 !! IMPLICIT ARGUMENTS
33 !! ------------------
34 !!
35 !! REFERENCE
36 !! ---------
37 !!
38 !! AUTHOR
39 !! ------
40 !!
41 !! B. Vincendon Meteo-France
42 !!
43 !! MODIFICATION
44 !! ------------
45 !!
46 !! Original 11/2006
47 !! B. Vincendon 02/2014 : adding possibility to choose the speed of water on hillslopes and
48 !! to write runoff maps on watersheds
49 !!
50 !----------------------------------------------------------------------------
51 !
52 !* 0. DECLARATION
53 ! -----------
54 !
55 USE modd_topd_par, ONLY : jpcat
56 USE modd_topodyn, ONLY : nncat
57 !
58 USE mode_pos_surf
59 !
60 USE modi_get_luout
61 USE modi_open_namelist
62 USE modi_close_namelist
63 !
64 USE yomhook ,ONLY : lhook, dr_hook
65 USE parkind1 ,ONLY : jprb
66 !
67 IMPLICIT NONE
68 !
69 !* 0.1 Declaration of arguments
70 ! ------------------------
71 !
72  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
73 LOGICAL, INTENT(OUT) :: obudget_topd ! budget computation
74 INTEGER, INTENT(OUT) :: knb_topd ! Ratio between Topmodel time step and ISBA time step
75 LOGICAL, INTENT(OUT) :: ostock_topd ! T if use of stock from previous simulation
76 INTEGER, INTENT(OUT) :: knb_stock ! number of time step to read in previous simulation
77 INTEGER, INTENT(OUT) :: knb_restart ! number of time step to write for next simulation
78 INTEGER, INTENT(OUT) :: kfreq_maps_wg!
79 INTEGER, INTENT(OUT) :: kfreq_maps_asat!
80 INTEGER, INTENT(OUT) :: kfreq_maps_runoff
81 REAL, DIMENSION(JPCAT),INTENT(OUT) :: pspeedr ! River speed
82 REAL, DIMENSION(JPCAT),INTENT(OUT) :: pspeedg ! Ground speed
83 REAL, DIMENSION(JPCAT),INTENT(OUT) :: pspeedh ! Hillslope speed
84 REAL, DIMENSION(JPCAT),INTENT(OUT) :: pqinit ! Initial discharge at catchments outlet
85 REAL, DIMENSION(JPCAT),INTENT(OUT) :: prtop_d2
86 !
87 !* 0.2 Declaration of local variables
88 ! ------------------------------
89 !
90 LOGICAL :: lbudget_topd
91 LOGICAL :: lstock_topd
92 INTEGER :: nnb_topd
93 INTEGER :: nfreq_maps_wg
94 INTEGER :: nfreq_maps_asat
95 INTEGER :: nfreq_maps_runoff
96 INTEGER :: nnb_stp_stock
97 INTEGER :: nnb_stp_restart
98 REAL, DIMENSION(JPCAT) :: xspeedr
99 REAL, DIMENSION(JPCAT) :: xspeedg
100 REAL, DIMENSION(JPCAT) :: xspeedh
101 REAL, DIMENSION(JPCAT) :: xqinit
102 REAL, DIMENSION(JPCAT) :: xrtop_d2
103 !
104 INTEGER :: iluout ! output listing logical unit
105 INTEGER :: ilunam ! namelist file logical unit
106 LOGICAL :: gfound ! flag when namelist is present
107 REAL(KIND=JPRB) :: zhook_handle
108 !
109 !* 0.3 Declaration of namelists
110 !
111 namelist/nam_topd/lbudget_topd, lstock_topd, nnb_topd, &
112  nfreq_maps_wg, nfreq_maps_asat, nfreq_maps_runoff,&
113  nnb_stp_stock, nnb_stp_restart, &
114  xspeedr, xspeedg, xspeedh, xqinit, xrtop_d2
115 !-------------------------------------------------------------------------------
116 IF (lhook) CALL dr_hook('READ_NAM_TOPD',0,zhook_handle)
117 !
118 !* 1. Initializations of defaults
119 ! ---------------------------
120 !
121 lbudget_topd = .false.
122 lstock_topd = .false.
123 nnb_topd = 1
124 nfreq_maps_wg = 0
125 nfreq_maps_asat = 0
126 nfreq_maps_runoff = 0
127 nnb_stp_stock = 1
128 nnb_stp_restart = 1
129 xspeedr(:) = 3.0 ! default value of river speed (adapted for Cevennes zone)
130 xspeedg(:) = 0.3 ! default value of speed in the ground
131 xspeedh(:) = 0.3 ! default value of hillspeed
132 xqinit(:) = 0.
133 xrtop_d2(:) = 1.
134 !
135  CALL get_luout(hprogram,iluout)
136 !
137 !-------------------------------------------------------------------------------
138 !
139 !* 2. Reading of namelist
140 ! -------------------
141 !
142  CALL open_namelist(hprogram,ilunam)
143 !
144  CALL posnam(ilunam,'NAM_TOPD',gfound,iluout)
145 IF (gfound) READ(unit=ilunam,nml=nam_topd)
146 !
147  CALL close_namelist(hprogram,ilunam)
148 !
149 !-------------------------------------------------------------------------------
150 !
151 !* 3. Fills output arguments
152 ! ----------------------
153 !
154 obudget_topd = lbudget_topd
155 ostock_topd = lstock_topd
156 knb_topd = nnb_topd
157 knb_stock = nnb_stp_stock
158 knb_restart = nnb_stp_restart
159 kfreq_maps_wg = nfreq_maps_wg
160 kfreq_maps_asat = nfreq_maps_asat
161 kfreq_maps_runoff = nfreq_maps_runoff
162 pspeedr(1:nncat) = xspeedr(1:nncat)
163 pspeedg(1:nncat) = xspeedg(1:nncat)
164 WHERE(xspeedh(1:nncat)/=0.3)
165  pspeedh(1:nncat) = xspeedh(1:nncat)
166 ELSEWHERE
167  pspeedh(1:nncat) = xspeedr(1:nncat)/10.
168 ENDWHERE
169 pqinit(1:nncat) = xqinit(1:nncat)
170 prtop_d2(1:nncat) = xrtop_d2(1:nncat)
171 !
172 WRITE(iluout,*) 'NAM_TOPD:'
173 WRITE(iluout,*) 'LBUDGET ',lbudget_topd
174 WRITE(iluout,*) 'NNB_TOP',nnb_topd
175 WRITE(iluout,*) 'LSTOCK',lstock_topd
176 WRITE(iluout,*) 'NNB_RESTART,NNB_STOCK',nnb_stp_restart,nnb_stp_stock
177 WRITE(iluout,*) 'NFREQ_MAPS_WG,NFREQ_MAPS_ASAT',nfreq_maps_wg,nfreq_maps_asat
178 WRITE(iluout,*) 'NFREQ_MAPS_RUNOFF',nfreq_maps_runoff
179 !
180 IF (lhook) CALL dr_hook('READ_NAM_TOPD',1,zhook_handle)
181 !-------------------------------------------------------------------------------
182 !
183 END SUBROUTINE read_nam_topd
subroutine read_nam_topd(HPROGRAM, OBUDGET_TOPD, KNB_TOPD, OSTOCK_TOPD, KNB_STOCK, KNB_RESTART, KFREQ_MAPS_WG, KFREQ_MAPS_ASAT, KFREQ_MAPS_RUNOFF, PSPEEDR, PSPEEDG, PSPEEDH, PQINIT, PRTOP_D2)
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)