SURFEX v8.1
General documentation of Surfex
modd_surf_atmn.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 ! ####################
7 ! ######################
8 !
9 !!**** *MODD_SURF_ATM - declaration of surface parameters
10 !!
11 !! PURPOSE
12 !! -------
13 ! Declaration of surface parameters
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! None
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !! AUTHOR
24 !! ------
25 !! V. Masson and A. Boone *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 01/2004
30 !
31 !* 0. DECLARATIONS
32 ! ------------
33 !
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 
43 !
44 !-----------------------------------------------------------------------------------------------------
45 !
46 ! Type of each surface scheme
47 !
48  CHARACTER(LEN=6) :: ctown ! name of the urban surface scheme
49  CHARACTER(LEN=6) :: cnature ! name of the soil&vegetation surface scheme
50  CHARACTER(LEN=6) :: cwater ! name of the scheme for inland water
51  CHARACTER(LEN=6) :: csea ! name for the ocean scheme
52 !
53 !-----------------------------------------------------------------------------------------------------
54 !
55 ! Surface/Tile Fractions:
56 !
57  REAL, POINTER, DIMENSION(:) :: xtown ! urban surface fraction of the grid box (-)
58  REAL, POINTER, DIMENSION(:) :: xnature ! natural surface fraction of the grid box (-)
59  REAL, POINTER, DIMENSION(:) :: xwater ! inland water fraction of the grid box (-)
60  REAL, POINTER, DIMENSION(:) :: xsea ! sea/ocean fraction of the grid box (-)
61 !
62 !-------------------------------------------------------------------------------
63 !
64 ! type of initialization of vegetation: from cover types (ecoclimap) or parameters prescribed
65 !
66  LOGICAL :: lecoclimap ! T: parameters computed from ecoclimap
67 ! ! F: they are read in the file
68 !
69  LOGICAL :: lecosg ! T: parameters computed from ecosg
70 !-------------------------------------------------------------------------------
71 !
72 ! change water (not lake) to nature and/or town to rock : arrange cover properly
73 !
74  LOGICAL :: lwater_to_nature ! T: Change Wetland treated as inland water into nature
75  LOGICAL :: ltown_to_rock ! T: Change Town into Rock
76 !
77 !-------------------------------------------------------------------------------
78 !
79 ! include urban green areas for urbanized covers
80 !
81  LOGICAL :: lgarden ! T: define urban green areas
82 ! ! F: no urban green areas
83 !
84 !-----------------------------------------------------------------------------------------------------
85 !
86 ! Masks and number of grid elements for each tile surface
87 !
88 ! Sea/Ocean:
89 !
90  INTEGER :: nsize_sea ! number of grid points by proc containing a
91 ! ! sea surface (-)
92  INTEGER :: ndim_sea ! total number of grid points containing a
93 ! ! sea surface (-)
94  INTEGER, POINTER, DIMENSION(:) :: nr_sea ! sea/ocean surface mask (-)
95 !
96 ! Inland Water:
97 !
98  INTEGER :: nsize_water ! number of grid points containing an
99 ! ! inland water surface (-)
100  INTEGER :: ndim_water ! total number of grid points by proc containing an
101 ! ! inland surface
102  INTEGER, POINTER, DIMENSION(:) :: nr_water
103 !
104 ! Town:
105 !
106  INTEGER :: nsize_town ! number of grid points by proc containing an
107 ! ! urban surface (-)
108  INTEGER :: ndim_town ! total number of grid points containing an
109 ! ! urban surface
110  INTEGER, POINTER, DIMENSION(:) :: nr_town ! urban surface mask (-)
111 !
112 ! Natural surface:
113 !
114  INTEGER :: nsize_nature ! number of grid points by proc containing a
115 ! ! natural surface (-)
116  INTEGER :: ndim_nature ! total number of grid points containing a
117 ! ! natural surface (-)
118  INTEGER, POINTER, DIMENSION(:) :: nr_nature ! natural surface mask (-)
119 !
120 ! All surfaces:
121 !
122  INTEGER :: nsize_full ! total number of grid points by proc (-)
123  INTEGER :: ndim_full ! total number of grid points (-)
124 !
125 ! global sizes of the physical domain
126 !
127  INTEGER :: nimax_surf_ll
128  INTEGER :: njmax_surf_ll
129 !
130 ! local sizes of the physical domain
131 !
132  INTEGER :: nimax_surf_loc
133  INTEGER :: njmax_surf_loc
134 !
135 !-----------------------------------------------------------------------------------------------------
136 !
137 ! Surface fields (only 1 horizontal dimension)
138 !
139  REAL, POINTER, DIMENSION(:,:) :: xcover ! fraction of each ecosystem for each grid box (-)
140  LOGICAL, POINTER, DIMENSION(:):: lcover ! GCOVER(i)=T --> ith cover field is not 0.
141  REAL, POINTER, DIMENSION(:) :: xzs ! orography (m)
142 !
143 !-------------------------------------------------------------------------------
144 !
145  type(date_time) :: ttime ! current date and time
146 !
147  REAL :: xout_tstep ! output writing time step
148 !
149 !-----------------------------------------------------------------------------------------------------
150 !
151 ! physical fields need into the restart file for ARPEGE/ALADIN run
152 !
153  REAL, POINTER, DIMENSION(:) :: xrain ! Rainfall rate at surface (kg/m2/s)
154  REAL, POINTER, DIMENSION(:) :: xsnow ! snowfall rate at surface (kg/m2/s)
155  REAL, POINTER, DIMENSION(:) :: xz0 ! surface roughness length for momentum (m)
156  REAL, POINTER, DIMENSION(:) :: xz0h ! surface roughness length for heat (m)
157  REAL, POINTER, DIMENSION(:) :: xqsurf ! specific humidity at surface (kg/kg)
158 !
159 !-----------------------------------------------------------------------------------------------------
160 !
161 !
162 END TYPE surf_atm_t
163 !
164 
165 
166 CONTAINS
167 
168 
169 !
170 
171 
172 !
173 !
174 SUBROUTINE surf_atm_init(YSURF_ATM)
175 TYPE(surf_atm_t), INTENT(INOUT) :: YSURF_ATM
176 REAL(KIND=JPRB) :: ZHOOK_HANDLE
177 IF (lhook) CALL dr_hook("MODD_SURF_ATM_N:SURF_ATM_INIT",0,zhook_handle)
178  NULLIFY(ysurf_atm%XTOWN)
179  NULLIFY(ysurf_atm%XNATURE)
180  NULLIFY(ysurf_atm%XWATER)
181  NULLIFY(ysurf_atm%XSEA)
182  NULLIFY(ysurf_atm%NR_SEA)
183  NULLIFY(ysurf_atm%NR_WATER)
184  NULLIFY(ysurf_atm%NR_TOWN)
185  NULLIFY(ysurf_atm%NR_NATURE)
186  NULLIFY(ysurf_atm%XCOVER)
187  NULLIFY(ysurf_atm%LCOVER)
188  NULLIFY(ysurf_atm%XZS)
189  NULLIFY(ysurf_atm%XRAIN)
190  NULLIFY(ysurf_atm%XSNOW)
191  NULLIFY(ysurf_atm%XZ0)
192  NULLIFY(ysurf_atm%XZ0H)
193  NULLIFY(ysurf_atm%XQSURF)
194 ysurf_atm%CTOWN=' '
195 ysurf_atm%CNATURE=' '
196 ysurf_atm%CWATER=' '
197 ysurf_atm%CSEA=' '
198 ysurf_atm%LECOCLIMAP=.false.
199 ysurf_atm%LECOSG=.false.
200 ysurf_atm%LWATER_TO_NATURE=.false.
201 ysurf_atm%LTOWN_TO_ROCK=.false.
202 ysurf_atm%LGARDEN=.false.
203 ysurf_atm%NSIZE_SEA=0
204 ysurf_atm%NDIM_SEA=0
205 ysurf_atm%NSIZE_WATER=0
206 ysurf_atm%NDIM_WATER=0
207 ysurf_atm%NSIZE_TOWN=0
208 ysurf_atm%NDIM_TOWN=0
209 ysurf_atm%NSIZE_NATURE=0
210 ysurf_atm%NDIM_NATURE=0
211 ysurf_atm%NSIZE_FULL=0
212 ysurf_atm%NDIM_FULL=0
213 ysurf_atm%NIMAX_SURF_ll=0
214 ysurf_atm%NJMAX_SURF_ll=0
215 ysurf_atm%NIMAX_SURF_LOC=0
216 ysurf_atm%NJMAX_SURF_LOC=0
217 ysurf_atm%XOUT_TSTEP=0.
218 IF (lhook) CALL dr_hook("MODD_SURF_ATM_N:SURF_ATM_INIT",1,zhook_handle)
219 END SUBROUTINE surf_atm_init
220 
221 
222 
223 END MODULE modd_surf_atm_n
224 
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine surf_atm_init(YSURF_ATM)