SURFEX v8.1
General documentation of Surfex
pgd_frac.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 pgd_frac (DTCO, UG, U, USS, HPROGRAM)
7 ! ##############################################################
8 !
9 !!**** *PGD_FRAC* monitor for averaging and interpolations of cover fractions
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !! AUTHOR
28 !! ------
29 !!
30 !! V. Masson Meteo-France
31 !!
32 !! MODIFICATION
33 !! ------------
34 !!
35 !! Original 10/12/97
36 !!
37 !! Modified 08/12/05, P. Le Moigne: user defined fields
38 !! Modified 04/2013 V. Masson : set a cover containing garden for TOWN default
39 !----------------------------------------------------------------------------
40 !
41 !* 0. DECLARATION
42 ! -----------
43 !
44 !
45 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 USE modd_sso_n, ONLY : sso_t
50 !
51 USE modd_surf_par, ONLY : xundef
52 USE modd_pgd_grid, ONLY : nl, cgrid
53 USE modd_data_cover_par, ONLY : jpcover, ncover, ntype
54 !
55 USE modd_pgdwork, ONLY : catype
56 !
57 USE modi_get_luout
58 USE modi_open_namelist
59 USE modi_close_namelist
61 USE modi_sum_on_all_procs
62 !
63 USE mode_pos_surf
64 !
65 !
66 USE yomhook ,ONLY : lhook, dr_hook
67 USE parkind1 ,ONLY : jprb
68 !
69 USE modi_abor1_sfx
70 !
71 IMPLICIT NONE
72 !
73 !* 0.1 Declaration of arguments
74 ! ------------------------
75 !
76 !
77 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
78 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
79 TYPE(surf_atm_t), INTENT(INOUT) :: U
80 TYPE(sso_t), INTENT(INOUT) :: USS
81 !
82  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! Type of program
83 !
84 !* 0.2 Declaration of local variables
85 ! ------------------------------
86 !
87 INTEGER :: ILUOUT ! output listing logical unit
88 INTEGER :: ILUNAM ! namelist file logical unit
89 LOGICAL :: GFOUND ! true if namelist is found
90 !
91 INTEGER :: JCOVER ! loop counter on covers
92 !
93 REAL, DIMENSION(NL) :: ZSUM ! sum of 4 tiles fractions
94 !
95 !* 0.3 Declaration of namelists
96 ! ------------------------
97 !
98 LOGICAL :: LECOCLIMAP ! F if ecoclimap is not used
99 LOGICAL :: LECOSG ! F if ecosg is not used
100 REAL :: XUNIF_SEA ! value of sea fraction
101 REAL :: XUNIF_WATER ! value of water fraction
102 REAL :: XUNIF_NATURE! value of nature fraction
103 REAL :: XUNIF_TOWN ! value of town fraction
104 !
105 ! name of files containing data
106 !
107  CHARACTER(LEN=28) :: CFNAM_SEA ! name of sea file
108  CHARACTER(LEN=28) :: CFNAM_WATER ! name of water file
109  CHARACTER(LEN=28) :: CFNAM_NATURE ! name of nature file
110  CHARACTER(LEN=28) :: CFNAM_TOWN ! name of town file
111 !
112 ! type of files containing data
113 !
114  CHARACTER(LEN=6) :: CFTYP_SEA ! type of sea file
115  CHARACTER(LEN=6) :: CFTYP_WATER ! type of water file
116  CHARACTER(LEN=6) :: CFTYP_NATURE ! type of nature file
117  CHARACTER(LEN=6) :: CFTYP_TOWN ! type of town file
118 !
119 INTEGER, DIMENSION(4) :: ID_COV
120 INTEGER :: ICOVER ! 0 if cover is not present, >1 if present somewhere
121 ! ! (even on another processor)
122 INTEGER :: ICPT
123 !
124 REAL(KIND=JPRB) :: ZHOOK_HANDLE
125 !
126 !
127 NAMELIST/nam_frac/ lecoclimap, lecosg, &
128  xunif_sea, xunif_water, xunif_nature, xunif_town, &
129  cfnam_sea, cfnam_water, cfnam_nature, cfnam_town, &
130  cftyp_sea, cftyp_water, cftyp_nature, cftyp_town
131 !-------------------------------------------------------------------------------
132 !
133 !* 1. Initializations
134 ! ---------------
135 !
136 IF (lhook) CALL dr_hook('PGD_FRAC',0,zhook_handle)
137 xunif_sea = xundef
138 xunif_water = xundef
139 xunif_nature = xundef
140 xunif_town = xundef
141 lecoclimap = .true.
142 lecosg = .false.
143 CFNAM_SEA (:)= ' '
144 CFNAM_WATER (:)= ' '
145 CFNAM_NATURE(:)= ' '
146 CFNAM_TOWN (:)= ' '
147 CFTYP_SEA (:)= ' '
148 CFTYP_WATER (:)= ' '
149 CFTYP_NATURE(:)= ' '
150 CFTYP_TOWN (:)= ' '
151 !
152 u%LECOCLIMAP = .true.
153 u%LECOSG = .false.
154 !
155 !-------------------------------------------------------------------------------
156 !
157 !* 2. Input file for cover types
158 ! --------------------------
159 !
160  CALL get_luout(hprogram,iluout)
161  CALL open_namelist(hprogram,ilunam)
162 !
163  CALL posnam(ilunam,'NAM_FRAC',gfound,iluout)
164 IF (gfound) READ(unit=ilunam,nml=nam_frac)
165 !
166  CALL close_namelist(hprogram,ilunam)
167 !
168 u%LECOSG = lecosg
169 !
170 !-------------------------------------------------------------------------------
171 !
172 IF ((len_trim(cfnam_sea)/=0 .OR. xunif_sea/=xundef) .AND. (len_trim(cfnam_water)/=0 .OR. xunif_water/=xundef) .AND. &
173  (len_trim(cfnam_nature)/=0 .OR. xunif_nature/=xundef) .AND. (len_trim(cfnam_town)/=0 .OR. xunif_town/=xundef)) THEN
174 !
175  ALLOCATE(u%XSEA (nl))
176  ALLOCATE(u%XWATER (nl))
177  ALLOCATE(u%XNATURE(nl))
178  ALLOCATE(u%XTOWN (nl))
179 !
180 !* 3. Uniform fractions are prescribed
181 ! --------------------------------
182 !
183  IF (xunif_sea/=xundef .AND. xunif_water/=xundef .AND. xunif_nature/=xundef .AND. xunif_town/=xundef) THEN
184 !
185 !* 3.1 Verification of the total input cover fractions
186 ! -----------------------------------------------
187 !
188  IF (abs(xunif_sea+xunif_water+xunif_nature+xunif_town-1.)>1.e-6) THEN
189  WRITE(iluout,*) ' '
190  WRITE(iluout,*) '*********************************************************'
191  WRITE(iluout,*) '* Error in fractions preparation *'
192  WRITE(iluout,*) '* The prescribed fractions do not fit *'
193  WRITE(iluout,*) '* The sum of all 4 fractions must be equal to 1 exactly *'
194  WRITE(iluout,*) '*********************************************************'
195  WRITE(iluout,*) ' '
196  CALL abor1_sfx('PGD_FRAC: SUM OF ALL FRACTIONS MUST BE 1.')
197 !
198 !* 3.2 Use of the presribed cover fractions
199 ! ------------------------------------
200 !
201  ELSE
202 !
203  u%XSEA = xunif_sea
204  u%XWATER = xunif_water
205  u%XNATURE = xunif_nature
206  u%XTOWN = xunif_town
207 
208  END IF
209 !
210 !* 3.3 No data
211 ! -------
212 !
213  ELSE
214 
215  catype = 'ARI'
216  IF (xunif_sea==xundef) THEN
217  CALL pgd_field(dtco, ug, u, uss, &
218  hprogram,'XSEA: sea fraction ','ALL', cfnam_sea , &
219  cftyp_sea , xunif_sea , u%XSEA(:) )
220  ELSE
221  u%XSEA(:) = xunif_sea
222  ENDIF
223  IF (xunif_water==xundef) THEN
224  CALL pgd_field(dtco, ug, u, uss, &
225  hprogram,'XWATER: water fraction ','ALL', cfnam_water , &
226  cftyp_water , xunif_water , u%XWATER(:) )
227  ELSE
228  u%XWATER(:) = xunif_water
229  ENDIF
230  IF (xunif_nature==xundef) THEN
231  CALL pgd_field(dtco, ug, u, uss, &
232  hprogram,'XNATURE: nature fraction','ALL', cfnam_nature, &
233  cftyp_nature, xunif_nature, u%XNATURE(:))
234  ELSE
235  u%XNATURE(:) = xunif_nature
236  ENDIF
237  IF (xunif_town==xundef) THEN
238  CALL pgd_field(dtco, ug, u, uss, &
239  hprogram,'XTOWN: town fraction ','ALL', cfnam_town , &
240  cftyp_town , xunif_town , u%XTOWN(:) )
241  ELSE
242  u%XTOWN(:) = xunif_town
243  ENDIF
244  ENDIF
245 
246 ELSE
247 !
248 !* 4. No prescription of fractions
249 ! ----------------------------
250 !
251  IF (lhook) CALL dr_hook('PGD_FRAC',1,zhook_handle)
252  RETURN
253 !
254 ENDIF
255 !-------------------------------------------------------------------------------
256 ! consistency check
257 ! ------------------
258 !
259 zsum(:) = u%XSEA(:) + u%XNATURE(:) + u%XWATER(:) + u%XTOWN(:)
260 
261 u%XSEA(:) = u%XSEA(:) / zsum(:)
262 u%XNATURE(:) = u%XNATURE(:) / zsum(:)
263 u%XWATER(:) = u%XWATER(:) / zsum(:)
264 u%XTOWN(:) = u%XTOWN(:) / zsum(:)
265 !
266 !-------------------------------------------------------------------------------
267 
268 WRITE(iluout,*) ' '
269 !-------------------------------------------------------------------------------
270 !
271 u%LECOCLIMAP = lecoclimap
272 !
273 !* 5. List of cover present
274 ! ---------------------
275 !
276 IF (.NOT.lecoclimap) THEN
277 
278  IF (.NOT.lecosg) THEN
279  id_cov(1) = 1
280  id_cov(2) = 2
281  id_cov(3) = 4
282  id_cov(4) = 151
283  jpcover = ncover
284  ELSE
285  id_cov(1) = 21
286  id_cov(2) = 22
287  id_cov(3) = 1
288  id_cov(4) = 20
289  jpcover = sum(ntype)
290  ENDIF
291 
292  ALLOCATE(u%LCOVER(jpcover))
293  u%LCOVER(:) = .false.
294  icover = 0
295  icpt= sum_on_all_procs(hprogram,cgrid,u%XSEA(:)/=0. ,'COV')
296  IF (icpt/=0) THEN
297  u%LCOVER(id_cov(1)) = .true.
298  icover=icover+1
299  ENDIF
300  icpt= sum_on_all_procs(hprogram,cgrid,u%XWATER(:)/=0. ,'COV')
301  IF (icpt/=0) THEN
302  u%LCOVER(id_cov(2)) = .true.
303  icover=icover+1
304  ENDIF
305  icpt= sum_on_all_procs(hprogram,cgrid,u%XNATURE(:)/=0. ,'COV')
306  IF (icpt/=0) THEN
307  u%LCOVER(id_cov(3)) = .true.
308  icover=icover+1
309  ENDIF
310  icpt= sum_on_all_procs(hprogram,cgrid,u%XTOWN(:)/=0. ,'COV')
311  IF (icpt/=0) THEN
312  u%LCOVER(id_cov(4)) = .true.
313  icover=icover+1
314  ENDIF
315 
316  ALLOCATE(u%XCOVER (nl,icover))
317 
318  icpt = 0
319  IF (u%LCOVER(id_cov(1))) THEN
320  icpt = icpt + 1
321  u%XCOVER(:,icpt) = u%XSEA(:)
322  ENDIF
323  IF (u%LCOVER(id_cov(2))) THEN
324  icpt = icpt + 1
325  u%XCOVER(:,icpt) = u%XWATER(:)
326  ENDIF
327  IF (u%LCOVER(id_cov(3))) THEN
328  icpt = icpt + 1
329  u%XCOVER(:,icpt) = u%XNATURE(:)
330  ENDIF
331  IF (u%LCOVER(id_cov(4))) THEN
332  icpt = icpt + 1
333  u%XCOVER(:,icpt) = u%XTOWN(:)
334  ENDIF
335 
336  ! comment V. Masson: to use this cover type for town by default avoids crashes
337  ! when garden fraction is specified but no garden vegetation parameters.
338  ! In this cas, the properties for garden come from the cover 151
339 !
340 !
341 !-------------------------------------------------------------------------------
342 !
343 !* 6. Land - sea fractions
344 ! --------------------
345 !
346  u%NSIZE_NATURE = count(u%XNATURE(:) > 0.0)
347  u%NSIZE_WATER = count(u%XWATER (:) > 0.0)
348  u%NSIZE_SEA = count(u%XSEA (:) > 0.0)
349  u%NSIZE_TOWN = count(u%XTOWN (:) > 0.0)
350  u%NSIZE_FULL = nl
351 !
352  u%NDIM_NATURE = sum_on_all_procs(hprogram,cgrid,u%XNATURE(:) > 0.0, 'DIM')
353  u%NDIM_WATER = sum_on_all_procs(hprogram,cgrid,u%XWATER (:) > 0.0, 'DIM')
354  u%NDIM_SEA = sum_on_all_procs(hprogram,cgrid,u%XSEA (:) > 0.0, 'DIM')
355  u%NDIM_TOWN = sum_on_all_procs(hprogram,cgrid,u%XTOWN (:) > 0.0, 'DIM')
356 !
357 ENDIF
358 IF (lhook) CALL dr_hook('PGD_FRAC',1,zhook_handle)
359 !-------------------------------------------------------------------------------
360 !
361 END SUBROUTINE pgd_frac
subroutine pgd_frac(DTCO, UG, U, USS, HPROGRAM)
Definition: pgd_frac.F90:7
character(len=3) catype
integer function sum_on_all_procs(HPROGRAM, HGRID, OIN, HNAME)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
intent(out) overrides sub arrays one Sort by the least significant key first sum(iindex(1:n))
logical lhook
Definition: yomhook.F90:15
character(len=10) cgrid
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
static int count
Definition: memory_hook.c:21