SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_nam_pgd_orography.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_nam_pgd_orography(HPROGRAM, HZS, HFILETYPE, PUNIF_ZS, &
7  horogtype, penv, oimp_zs,&
8  hslope, hslopefiletype, oexplicit_slope )
9 ! ##############################################################
10 !
11 !!**** *READ_NAM_PGD_OROGRAPHY* reads namelist for Orography
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !! METHOD
17 !! ------
18 !!
19 !
20 !! EXTERNAL
21 !! --------
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! B. Decharme Meteo-France
33 !!
34 !! MODIFICATION
35 !! ------------
36 !!
37 !! Original 02/2010
38 !! M Lafaysse 07/2013 : explicit slope
39 !----------------------------------------------------------------------------
40 !
41 !* 0. DECLARATION
42 ! -----------
43 !
44 USE modd_surf_par, ONLY : xundef
45 !
46 USE modi_get_luout
47 USE modi_open_namelist
48 USE modi_close_namelist
49 !
50 USE mode_pos_surf
51 !
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 IMPLICIT NONE
57 !
58 !* 0.1 Declaration of arguments
59 ! ------------------------
60 !
61  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
62  CHARACTER(LEN=28), INTENT(OUT) :: hzs ! file name for orography
63  CHARACTER(LEN=6), INTENT(OUT) :: hfiletype ! data file type
64 REAL, INTENT(OUT) :: punif_zs ! uniform orography
65  CHARACTER(LEN=3), INTENT(OUT) :: horogtype ! orogpraphy type
66 REAL, INTENT(OUT) :: penv ! parameter for enveloppe orography:
67 LOGICAL, INTENT(OUT) :: oimp_zs ! Imposed orography from another PGD file
68  CHARACTER(LEN=28), INTENT(OUT),OPTIONAL :: hslope ! file name for slope
69  CHARACTER(LEN=6), INTENT(OUT),OPTIONAL :: hslopefiletype ! data file type
70 LOGICAL, INTENT(OUT),OPTIONAL :: oexplicit_slope ! Slope is computed from explicit ZS field and not subgrid orography
71 !
72 !
73 !* 0.2 Declaration of local variables
74 ! ------------------------------
75 !
76 INTEGER :: iluout ! output listing logical unit
77 INTEGER :: ilunam ! namelist file logical unit
78 LOGICAL :: gfound ! flag when namelist is present
79 !
80 !* 0.3 Declaration of namelists
81 ! ------------------------
82 !
83  CHARACTER(LEN=28) :: yzs ! file name for orography
84  CHARACTER(LEN=6) :: yzsfiletype ! data file type
85  CHARACTER(LEN=28) :: yslope ! file name for slope
86  CHARACTER(LEN=6) :: yslopefiletype ! data file type
87 REAL :: xunif_zs ! uniform orography
88  CHARACTER(LEN=3) :: corogtype ! orogpraphy type
89 ! ! 'AVG' : average orography
90 ! ! 'SIL' : silhouette orography
91 ! ! 'ENV' : enveloppe orography
92 REAL :: xenv ! parameter for enveloppe orography:
93 ! ! zs = avg_zs + XENV * SSO_STEDV
94 LOGICAL :: limp_zs ! Imposed orography from another PGD file
95 LOGICAL :: lexplicit_slope ! Slope is computed from explicit ZS field and not subgrid orography
96 REAL(KIND=JPRB) :: zhook_handle
97 !
98 namelist/nam_zs/yzs, yzsfiletype, xunif_zs, corogtype, xenv, limp_zs , &
99  yslope, yslopefiletype, lexplicit_slope
100 !
101 !-------------------------------------------------------------------------------
102 !
103 !* 1. Initializations of defaults
104 ! ---------------------------
105 !
106 IF (lhook) CALL dr_hook('READ_NAM_PGD_OROGRAPHY',0,zhook_handle)
107 xunif_zs = xundef
108 yzs = ' '
109 yzsfiletype = ' '
110 yslope = ' '
111 yslopefiletype = ' '
112 !
113  corogtype = 'ENV'
114 xenv = 0.
115 limp_zs = .false.
116 lexplicit_slope=.false.
117 !
118  CALL get_luout(hprogram,iluout)
119 !
120 !-------------------------------------------------------------------------------
121 !
122 !* 2. Reading of namelist
123 ! -------------------
124 !
125  CALL open_namelist(hprogram,ilunam)
126 !
127  CALL posnam(ilunam,'NAM_ZS',gfound,iluout)
128 IF (gfound) READ(unit=ilunam,nml=nam_zs)
129 !
130  CALL close_namelist(hprogram,ilunam)
131 !
132 !-------------------------------------------------------------------------------
133 !
134 hzs = yzs ! file name for orography
135 hfiletype = yzsfiletype ! data file type
136 IF (present(hslope)) THEN
137  hslope = yslope ! file name for slope
138  hslopefiletype = yslopefiletype ! data file type
139 END IF
140 punif_zs = xunif_zs ! uniform orography
141 horogtype = corogtype ! orogpraphy type
142 penv = xenv ! parameter for enveloppe orography:
143 oimp_zs = limp_zs ! Imposed orography from another PGD file
144 IF (present(oexplicit_slope)) THEN
145  oexplicit_slope=lexplicit_slope ! Slope is computed from explicit ZS field and not subgrid orography
146 END IF
147 IF (lhook) CALL dr_hook('READ_NAM_PGD_OROGRAPHY',1,zhook_handle)
148 !
149 !-------------------------------------------------------------------------------
150 !
151 END SUBROUTINE read_nam_pgd_orography
subroutine read_nam_pgd_orography(HPROGRAM, HZS, HFILETYPE, PUNIF_ZS, HOROGTYPE, PENV, OIMP_ZS, HSLOPE, HSLOPEFILETYPE, OEXPLICIT_SLOPE)
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)