SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
treat_global_lake_depth.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 treat_global_lake_depth (DTCO, UG, U, USS, &
7  hprogram,pdepth,kstatus)
8 ! ##############################################################
9 !
10 !!**** *TREAT_GLOBAL_LAKE_DEPTH* monitor for averaging and interpolations of ISBA physiographic fields
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 !! S. Faroux Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 17/02/11
37 !!
38 !----------------------------------------------------------------------------
39 !
40 !* 0. DECLARATION
41 ! -----------
42 !
43 !
44 !
45 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
50 !
51 USE modd_surf_par, ONLY : xundef
52 USE modd_pgd_grid, ONLY : nl
53 USE modd_pgdwork, ONLY : xtng, nsize
54 USE modd_data_lake, ONLY : clakeldb, cstatusldb, ngraddepth_ldb, ngradstatus_ldb
55 !
56 USE modi_get_luout
57 USE modi_treat_field
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 USE modi_abor1_sfx
64 USE modi_get_surf_mask_n
65 USE modi_get_type_dim_n
66 !
67 IMPLICIT NONE
68 !
69 !* 0.1 Declaration of arguments
70 ! ------------------------
71 !
72 !
73 TYPE(data_cover_t), INTENT(INOUT) :: dtco
74 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
75 TYPE(surf_atm_t), INTENT(INOUT) :: u
76 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
77 !
78  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
79 REAL, DIMENSION(:),INTENT(OUT):: pdepth ! physiographic field
80 INTEGER, DIMENSION(:),INTENT(OUT):: kstatus ! physiographic field
81 !
82 !
83 !* 0.2 Declaration of local variables
84 ! ------------------------------
85 !
86 INTEGER :: ilu ! expected physical size of full surface array
87 INTEGER :: iluout ! output listing logical unit
88 INTEGER, DIMENSION(:), POINTER :: imask ! mask for packing from complete field to nature field
89 INTEGER :: idim !
90 INTEGER :: ji
91 !
92  CHARACTER(LEN=6) :: ymask
93 INTEGER, DIMENSION(NL) :: istatus
94 REAL, DIMENSION(NL) :: zdepth, zstatus ! physiographic field on full grid
95 REAL(KIND=JPRB) :: zhook_handle
96 !-------------------------------------------------------------------------------
97 !
98 !* 1. Initializations
99 ! ---------------
100 !
101 IF (lhook) CALL dr_hook('TREAT_GLOBAL_LAKE_DEPTH',0,zhook_handle)
102 zdepth(:) = xundef
103 zstatus(:) = xundef
104 !-------------------------------------------------------------------------------
105 !
106 !* 2. Output listing logical unit
107 ! ---------------------------
108 !
109  CALL get_luout(hprogram,iluout)
110 !
111 !-------------------------------------------------------------------------------
112 !
113 !* 4. Averages the field
114 ! ------------------
115 !
116 ALLOCATE(nsize(nl))
117 ALLOCATE(xtng(nl,ngraddepth_ldb))
118 !
119 nsize(:) = 0.
120 xtng(:,:) = 0.
121 !
122  CALL treat_field(ug, u, uss, &
123  hprogram,'SURF ','DIRECT','A_LDBD', clakeldb, &
124  'water depth ',zdepth,'WAT' )
125 !
126 DEALLOCATE(xtng)
127 ALLOCATE(xtng(nl,ngradstatus_ldb))
128 !
129 nsize(:) = 0.
130 xtng(:,:) = 0.
131 !
132  CALL treat_field(ug, u, uss, &
133  hprogram,'SURF ','DIRECT','A_LDBS', cstatusldb, &
134  'water status ',zstatus,'WAT' )
135 !
136 istatus = nint(zstatus)
137 !
138 DEALLOCATE(nsize)
139 DEALLOCATE(xtng)
140 !
141 !-------------------------------------------------------------------------------
142 !
143 !* 5. Consistancy check
144 ! ------------------
145 !
146 DO ji = 1, SIZE(zdepth)
147  IF (u%XWATER(ji).GT.0.) THEN
148  IF (istatus(ji).LE.2) zdepth(ji) = 10.
149  IF (istatus(ji)==3.AND.zdepth(ji)==0.) zdepth(ji) = 10.
150  ELSE
151  zdepth(ji) = 0.
152  ENDIF
153 ENDDO
154 !
155 !* 6. Mask for the field
156 ! ------------------
157 !
158 ymask='WATER '
159  CALL get_type_dim_n(dtco, u, &
160  ymask,idim)
161 IF (idim/=SIZE(pdepth) .OR. idim/=SIZE(kstatus)) THEN
162  WRITE(iluout,*)'Wrong dimension of MASK: ',idim,SIZE(pdepth),SIZE(kstatus)
163  CALL abor1_sfx('TREAT_GLOBAL_LAKE_DEPTH: WRONG DIMENSION OF MASK')
164 ENDIF
165 
166 ALLOCATE(imask(idim))
167 ilu=0
168  CALL get_surf_mask_n(dtco, u, &
169  ymask,idim,imask,ilu,iluout)
170  CALL pack_same_rank(imask,zdepth(:),pdepth(:))
171  CALL pack_same_rank(imask,istatus(:),kstatus(:))
172 DEALLOCATE(imask)
173 !
174 IF (lhook) CALL dr_hook('TREAT_GLOBAL_LAKE_DEPTH',1,zhook_handle)
175 !
176 !-------------------------------------------------------------------------------
177 !
178 END SUBROUTINE treat_global_lake_depth
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine treat_field(UG, U, USS, HPROGRAM, HSCHEME, HFILETYPE, HSUBROUTINE, HFILENAME, HFIELD, PPGDARRAY, HSFTYPE)
Definition: treat_field.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine get_surf_mask_n(DTCO, U, HTYPE, KDIM, KMASK, KLU, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine treat_global_lake_depth(DTCO, UG, U, USS, HPROGRAM, PDEPTH, KSTATUS)