SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_nam_pgd_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_pgd_topd(HPROGRAM,OCOUPL_TOPD,HCAT,PF_PARAM_BV,PC_DEPTH_RATIO_BV)
8 ! ##############################################################
9 !
10 !!**** *READ_NAM_TOPD_n* reads namelist NAM_TOPD
11 !!
12 !! PURPOSE
13 !! -------
14 !! NAM_TOPD is a namelist used only for Topmodel coupling
15 !! It permits to define the different catchments studied.
16 !! This routine aims at reading and initialising those names.
17 !!
18 !! METHOD
19 !! ------
20 !!
21 !
22 !! EXTERNAL
23 !! --------
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !! AUTHOR
32 !! ------
33 !!
34 !! B. Vincendon Meteo-France
35 !!
36 !! MODIFICATION
37 !! ------------
38 !!
39 !! Original 11/2006
40 !!
41 !----------------------------------------------------------------------------
42 !
43 !* 0. DECLARATION
44 ! -----------
45 !
46 USE modi_get_luout
47 USE modi_open_namelist
48 USE modi_close_namelist
49 !
50 USE modd_topd_par, ONLY : jpcat
51 USE modd_topodyn, ONLY : nncat
52 !
53 USE mode_pos_surf
54 !
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 IMPLICIT NONE
59 !
60 !* 0.1 Declaration of arguments
61 ! ------------------------
62 !
63  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
64 LOGICAL, INTENT(OUT) :: ocoupl_topd
65  CHARACTER(LEN=15), DIMENSION(JPCAT),INTENT(OUT) :: hcat ! Names of catchments
66 REAL, DIMENSION(JPCAT),INTENT(OUT) :: pf_param_bv
67 REAL, DIMENSION(JPCAT),INTENT(OUT) :: pc_depth_ratio_bv
68 !
69 !* 0.2 Declaration of local variables
70 ! ------------------------------
71 !
72  CHARACTER(LEN=15), DIMENSION(JPCAT) :: ccat
73 LOGICAL :: lcoupl_topd
74 REAL, DIMENSION(JPCAT) :: xf_param_bv
75 REAL, DIMENSION(JPCAT) :: xc_depth_ratio_bv
76 !
77 INTEGER :: iluout ! output listing logical unit
78 INTEGER :: ilunam ! namelist file logical unit
79 LOGICAL :: gfound ! flag when namelist is present
80 REAL(KIND=JPRB) :: zhook_handle
81 !
82 !* 0.3 Declaration of namelists
83 !
84 !
85 namelist/nam_pgd_topd/ccat, lcoupl_topd, xf_param_bv, xc_depth_ratio_bv
86 !-------------------------------------------------------------------------------
87 IF (lhook) CALL dr_hook('READ_NAM_PGD_TOPD',0,zhook_handle)
88 !
89 !* 1. Initializations of defaults
90 ! ---------------------------
91 !
92 lcoupl_topd = .false.
93  ccat(:) = ' '
94 xf_param_bv(:) = 2.5
95 xc_depth_ratio_bv(:) = 1.
96 !
97  CALL get_luout(hprogram,iluout)
98 !
99 !-------------------------------------------------------------------------------
100 !
101 !* 2. Reading of namelist
102 ! -------------------
103 !
104  CALL open_namelist(hprogram,ilunam)
105 !CALL OPEN_NAMELIST(HPROGRAM,'SURF ',ILUNAM)
106 !
107  CALL posnam(ilunam,'NAM_PGD_TOPD',gfound,iluout)
108 IF (gfound) READ(unit=ilunam,nml=nam_pgd_topd)
109 !
110  CALL close_namelist(hprogram,ilunam)
111 !
112 ! 2. Initialises number of catchments and time step variables
113 ! -------------------------------------------------------
114 !
115 nncat=count(ccat(:)/=' ')
116 !
117 !-------------------------------------------------------------------------------
118 !
119 !* 3. Fills output arguments
120 ! ----------------------
121 !
122 ocoupl_topd = lcoupl_topd
123 hcat(1:nncat) = ccat(1:nncat)
124 pf_param_bv(1:nncat) = xf_param_bv(1:nncat)
125 pc_depth_ratio_bv(1:nncat) = xc_depth_ratio_bv(1:nncat)
126 !
127 IF (lhook) CALL dr_hook('READ_NAM_PGD_TOPD',1,zhook_handle)
128 !-------------------------------------------------------------------------------
129 !
130 END SUBROUTINE read_nam_pgd_topd
subroutine read_nam_pgd_topd(HPROGRAM, OCOUPL_TOPD, HCAT, PF_PARAM_BV, PC_DEPTH_RATIO_BV)
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)