SURFEX v8.1
General documentation of Surfex
read_nam_pgd_cover.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_cover(HPROGRAM, HCOVER, HFILETYPE, PUNIF_COVER, &
7  PRM_COVER, PRM_COAST, PRM_LAKE, ORM_RIVER, &
8  PRM_SEA, OORCA_GRID, PLAT_ANT, OIMP_COVER )
9 ! ##############################################################
10 !
11 !!**** *READ_NAM_PGD_COVER* reads namelist for Cover
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 !----------------------------------------------------------------------------
39 !
40 !* 0. DECLARATION
41 ! -----------
42 !
43 USE modd_data_cover_par, ONLY : ncover
44 !
45 USE modi_get_luout
46 USE modi_open_namelist
47 USE modi_close_namelist
48 !
49 USE mode_pos_surf
50 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declaration of arguments
58 ! ------------------------
59 !
60  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! Type of program
61  CHARACTER(LEN=28), INTENT(OUT) :: HCOVER ! file name for cover types
62  CHARACTER(LEN=6), INTENT(OUT) :: HFILETYPE ! data file type
63 REAL, DIMENSION(:), INTENT(OUT) :: PUNIF_COVER ! value of each cover (cover will be uniform on the horizontal)
64 REAL, INTENT(OUT) :: PRM_COVER ! limit of coverage under which the cover is removed. Default is 1.E-6
65 REAL, INTENT(OUT) :: PRM_COAST ! limit of coast coverage
66 REAL, INTENT(OUT) :: PRM_LAKE ! limit of inland lake coverage
67 LOGICAL, INTENT(OUT) :: ORM_RIVER ! delete river coverage
68 REAL, INTENT(OUT) :: PRM_SEA ! limit of sea coverage
69 LOGICAL, INTENT(OUT) :: OORCA_GRID ! flag to compatibility between Surfex and Orca grid
70 REAL, INTENT(OUT) :: PLAT_ANT ! Lattitude limit from Orca grid (Antartic)
71 LOGICAL, INTENT(OUT) :: OIMP_COVER ! Imposed values for Cover from another PGD file
72 !
73 !
74 !* 0.2 Declaration of local variables
75 ! ------------------------------
76 !
77 INTEGER :: ILUOUT ! output listing logical unit
78 INTEGER :: ILUNAM ! namelist file logical unit
79 LOGICAL :: GFOUND ! flag when namelist is present
80 !
81 !* 0.3 Declaration of namelists
82 ! ------------------------
83 !
84 REAL, DIMENSION(NCOVER) :: XUNIF_COVER ! value of each cover (cover will be
85 ! uniform on the horizontal)
86 !
87  CHARACTER(LEN=28) :: YCOVER ! file name for cover types
88  CHARACTER(LEN=6) :: YCOVERFILETYPE ! data file type
89 REAL :: XRM_COVER ! limit of coverage under which the
90  ! cover is removed. Default is 1.E-6
91 REAL :: XRM_COAST ! limit of coast coverage under which
92  ! the coast is replaced by sea or
93  ! inland water. Default is 1.
94 !
95 REAL :: XRM_LAKE ! limit of inland lake coverage under which
96  ! the water is removed. Default is 0.0
97 !
98 LOGICAL :: LRM_RIVER ! delete inland river coverage. Default is false
99 !
100 REAL :: XRM_SEA ! limit of sea coverage under which
101  ! the sea is removed. Default is 0.0
102 !
103 LOGICAL :: LORCA_GRID ! flag to compatibility between Surfex and Orca grid
104  ! (Earth Model over Antarctic)
105 REAL :: XLAT_ANT ! Lattitude limit from Orca grid (Antartic)
106 !
107 LOGICAL :: LIMP_COVER ! Imposed values for Cover from another PGD file
108 !
109 REAL(KIND=JPRB) :: ZHOOK_HANDLE
110 !
111 NAMELIST/nam_cover/ ycover, ycoverfiletype, xunif_cover, xrm_cover, xrm_coast, &
112  xrm_lake, lrm_river, xrm_sea, lorca_grid, xlat_ant, limp_cover
113 !
114 !-------------------------------------------------------------------------------
115 !
116 !* 1. Initializations of defaults
117 ! ---------------------------
118 !
119 IF (lhook) CALL dr_hook('READ_NAM_PGD_COVER',0,zhook_handle)
120 xunif_cover(:) = 0.
121 ycover = ' '
122 ycoverfiletype = ' '
123 xrm_cover = 1.e-6
124 xrm_coast = 1.0
125 xrm_lake = 0.0
126 lrm_river = .false.
127 xrm_sea = 0.0
128 !
129 lorca_grid = .false.
130 xlat_ant = -77.0
131 !
132 limp_cover = .false.
133 !
134  CALL get_luout(hprogram,iluout)
135 !
136 !-------------------------------------------------------------------------------
137 !
138 !* 2. Reading of namelist
139 ! -------------------
140 !
141  CALL open_namelist(hprogram,ilunam)
142 !
143  CALL posnam(ilunam,'NAM_COVER',gfound,iluout)
144 IF (gfound) READ(unit=ilunam,nml=nam_cover)
145 !
146  CALL close_namelist(hprogram,ilunam)
147 !
148 !-------------------------------------------------------------------------------
149 !
150 hcover = ycover ! file name for cover types
151 hfiletype = ycoverfiletype ! data file type
152 punif_cover = xunif_cover(1:SIZE(punif_cover)) ! value of each cover (cover will be uniform on the horizontal)
153 prm_cover = xrm_cover ! limit of coverage under which the cover is removed. Default is 1.E-6
154 prm_coast = xrm_coast ! limit of coast coverage
155 prm_lake = xrm_lake ! limit of inland lake coverage
156 orm_river = lrm_river ! delete river coverage
157 prm_sea = xrm_sea ! limit of sea coverage
158 oorca_grid = lorca_grid ! flag to compatibility between Surfex and Orca grid
159 plat_ant = xlat_ant ! Lattitude limit from Orca grid (Antartic)
160 oimp_cover = limp_cover ! Imposed values for Cover from another PGD file
161 IF (lhook) CALL dr_hook('READ_NAM_PGD_COVER',1,zhook_handle)
162 !
163 !-------------------------------------------------------------------------------
164 !
165 END SUBROUTINE read_nam_pgd_cover
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
subroutine read_nam_pgd_cover(HPROGRAM, HCOVER, HFILETYPE, PUNIF_C