SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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 !-------------------------------------------------------------------------------
70 !
71 ! change water (not lake) to nature and/or town to rock : arrange cover properly
72 !
73  LOGICAL :: LWATER_TO_NATURE ! T: Change Wetland treated as inland water into nature
74  LOGICAL :: LTOWN_TO_ROCK ! T: Change Town into Rock
75 !
76 !-------------------------------------------------------------------------------
77 !
78 ! include urban green areas for urbanized covers
79 !
80  LOGICAL :: LGARDEN ! T: define urban green areas
81 ! ! F: no urban green areas
82 !
83 !-----------------------------------------------------------------------------------------------------
84 !
85 ! Masks and number of grid elements for each tile surface
86 !
87 ! Sea/Ocean:
88 !
89  INTEGER :: NSIZE_SEA ! number of grid points by proc containing a
90 ! ! sea surface (-)
91  INTEGER :: NDIM_SEA ! total number of grid points containing a
92 ! ! sea surface (-)
93  INTEGER, POINTER, DIMENSION(:) :: NR_SEA ! sea/ocean surface mask (-)
94 !
95 ! Inland Water:
96 !
97  INTEGER :: NSIZE_WATER ! number of grid points containing an
98 ! ! inland water surface (-)
99  INTEGER :: NDIM_WATER ! total number of grid points by proc containing an
100 ! ! inland surface
101  INTEGER, POINTER, DIMENSION(:) :: NR_WATER
102 !
103 ! Town:
104 !
105  INTEGER :: NSIZE_TOWN ! number of grid points by proc containing an
106 ! ! urban surface (-)
107  INTEGER :: NDIM_TOWN ! total number of grid points containing an
108 ! ! urban surface
109  INTEGER, POINTER, DIMENSION(:) :: NR_TOWN ! urban surface mask (-)
110 !
111 ! Natural surface:
112 !
113  INTEGER :: NSIZE_NATURE ! number of grid points by proc containing a
114 ! ! natural surface (-)
115  INTEGER :: NDIM_NATURE ! total number of grid points containing a
116 ! ! natural surface (-)
117  INTEGER, POINTER, DIMENSION(:) :: NR_NATURE ! natural surface mask (-)
118 !
119 ! All surfaces:
120 !
121  INTEGER :: NSIZE_FULL ! total number of grid points by proc (-)
122  INTEGER :: NDIM_FULL ! total number of grid points (-)
123 !
124 !-----------------------------------------------------------------------------------------------------
125 !
126 ! Surface fields (only 1 horizontal dimension)
127 !
128  REAL, POINTER, DIMENSION(:,:) :: XCOVER ! fraction of each ecosystem for each grid box (-)
129  LOGICAL, POINTER, DIMENSION(:):: LCOVER ! GCOVER(i)=T --> ith cover field is not 0.
130  REAL, POINTER, DIMENSION(:) :: XZS ! orography (m)
131 !
132 !-------------------------------------------------------------------------------
133 !
134  TYPE (date_time) :: TTIME ! current date and time
135 !
136  REAL :: XOUT_TSTEP ! output writing time step
137 !
138 !-----------------------------------------------------------------------------------------------------
139 !
140 ! physical fields need into the restart file for ARPEGE/ALADIN run
141 !
142  REAL, POINTER, DIMENSION(:) :: XRAIN ! Rainfall rate at surface (kg/m2/s)
143  REAL, POINTER, DIMENSION(:) :: XSNOW ! snowfall rate at surface (kg/m2/s)
144  REAL, POINTER, DIMENSION(:) :: XZ0 ! surface roughness length for momentum (m)
145  REAL, POINTER, DIMENSION(:) :: XZ0H ! surface roughness length for heat (m)
146  REAL, POINTER, DIMENSION(:) :: XQSURF ! specific humidity at surface (kg/kg)
147 !
148 !-----------------------------------------------------------------------------------------------------
149 !
150 !
151 END TYPE surf_atm_t
152 !
153 
154 
155  CONTAINS
156 
157 
158 !
159 
160 
161 !
162 !
163 SUBROUTINE surf_atm_init(YSURF_ATM)
164 TYPE(surf_atm_t), INTENT(INOUT) :: ysurf_atm
165 REAL(KIND=JPRB) :: zhook_handle
166 IF (lhook) CALL dr_hook("MODD_SURF_ATM_N:SURF_ATM_INIT",0,zhook_handle)
167  nullify(ysurf_atm%XTOWN)
168  nullify(ysurf_atm%XNATURE)
169  nullify(ysurf_atm%XWATER)
170  nullify(ysurf_atm%XSEA)
171  nullify(ysurf_atm%NR_SEA)
172  nullify(ysurf_atm%NR_WATER)
173  nullify(ysurf_atm%NR_TOWN)
174  nullify(ysurf_atm%NR_NATURE)
175  nullify(ysurf_atm%XCOVER)
176  nullify(ysurf_atm%LCOVER)
177  nullify(ysurf_atm%XZS)
178  nullify(ysurf_atm%XRAIN)
179  nullify(ysurf_atm%XSNOW)
180  nullify(ysurf_atm%XZ0)
181  nullify(ysurf_atm%XZ0H)
182  nullify(ysurf_atm%XQSURF)
183 ysurf_atm%CTOWN=' '
184 ysurf_atm%CNATURE=' '
185 ysurf_atm%CWATER=' '
186 ysurf_atm%CSEA=' '
187 ysurf_atm%LECOCLIMAP=.false.
188 ysurf_atm%LWATER_TO_NATURE=.false.
189 ysurf_atm%LTOWN_TO_ROCK=.false.
190 ysurf_atm%LGARDEN=.false.
191 ysurf_atm%NSIZE_SEA=0
192 ysurf_atm%NDIM_SEA=0
193 ysurf_atm%NSIZE_WATER=0
194 ysurf_atm%NDIM_WATER=0
195 ysurf_atm%NSIZE_TOWN=0
196 ysurf_atm%NDIM_TOWN=0
197 ysurf_atm%NSIZE_NATURE=0
198 ysurf_atm%NDIM_NATURE=0
199 ysurf_atm%NSIZE_FULL=0
200 ysurf_atm%NDIM_FULL=0
201 ysurf_atm%XOUT_TSTEP=0.
202 IF (lhook) CALL dr_hook("MODD_SURF_ATM_N:SURF_ATM_INIT",1,zhook_handle)
203 END SUBROUTINE surf_atm_init
204 
205 
206 
207 END MODULE modd_surf_atm_n
208 
subroutine surf_atm_init(YSURF_ATM)