SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
explicit_slope.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 explicit_slope (UG, &
7  pzs,psso_slope)
8 ! #########################################################################
9 !! AUTHOR
10 !! ------
11 !! M. Lafaysse * Meteo-France *
12 !!
13 !! MODIFICATIONS
14 !! -------------
15 !! Original 19/07/13
16 !
17 !* 0. DECLARATIONS
18 ! ------------
19 !
20 
21 !
23 !
24 USE modi_get_grid_dim
25 USE modi_get_mesh_dim
26 
27 IMPLICIT NONE
28 !
29 !* 0.1 DECLARATIONS OF DUMMY ARGUMENTS :
30 !
31 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
32 !
33 REAL,DIMENSION(:),INTENT(IN)::pzs ! resolved model orography
34 REAL,DIMENSION(:),INTENT(OUT)::psso_slope ! resolved slope tangent
35 
36 
37 
38 !
39 !
40 !* 0.2 DECLARATIONS OF LOCAL VARIABLES
41 !
42 
43 INTEGER :: ix ! number of points in X direction
44 INTEGER :: iy ! number of points in Y direction
45 
46 INTEGER :: innx ! number of points in X direction for large domain
47 INTEGER :: inny ! number of points in Y direction for large domain
48 
49 LOGICAL::grect=.true.
50 
51 INTEGER :: jx ! loop counter
52 INTEGER :: jy ! loop counter
53 
54 REAL, DIMENSION(:,:), ALLOCATABLE :: zmap ! map factor
55 REAL, DIMENSION(:,:), ALLOCATABLE :: zzs ! orography in a 2D array
56 REAL, DIMENSION(:,:), ALLOCATABLE :: zsso_slope ! explicit slope in a 2D array
57 REAL, DIMENSION(:,:), ALLOCATABLE :: zzs_xy ! orography at southwest corner of the mesh
58 REAL, DIMENSION(:,:),ALLOCATABLE :: zzsl ! orography in a 2D array
59 REAL, DIMENSION(:),ALLOCATABLE :: zxhat ! X coordinate
60 REAL, DIMENSION(:),ALLOCATABLE :: zyhat ! Y coordinate
61 
62 
63 REAL,DIMENSION(:), ALLOCATABLE :: zdx ! grid mesh size in x direction
64 REAL,DIMENSION(:), ALLOCATABLE :: zdy ! grid mesh size in y direction
65 
66 ! parameters
67 REAL, PARAMETER :: xpi=4.*atan(1.) ! Pi
68 INTEGER, PARAMETER :: jphext = 1 ! number of points around the physical domain
69 !
70 INTEGER :: iib, iie, ijb, ije
71 INTEGER :: ji, jj, jb
72 INTEGER :: jt
73 !
74 REAL :: zdzsdx ! slope in X and Y direction
75 REAL :: zdzsdy ! of a triangle surface
76 REAL :: zsurf ! surface of 4 triangles
77 !
78 
79 
80 
81 !-------------------------------------------------------------------------------
82 !
83 !* 1.1 Gets the geometry of the grid
84 ! -----------------------------
85 !
86  CALL get_grid_dim(ug%CGRID,SIZE(ug%XGRID_PAR),ug%XGRID_PAR,grect,ix,iy)
87 !
88 innx=ix+2
89 inny=iy+2
90 
91 !
92 
93 !* 1.2 Grid dimension (meters)
94 ! -----------------------
95 !
96 ALLOCATE(zdx(ix*iy))
97 ALLOCATE(zdy(ix*iy))
98 
99 
100  CALL get_mesh_dim(ug%CGRID,SIZE(ug%XGRID_PAR),ix*iy,ug%XGRID_PAR,zdx,zdy,ug%XMESH_SIZE)
101 
102 
103 !
104 !* 2. If grid is not rectangular, nothing is done
105 ! -------------------------------------------
106 !
107 !IF (.NOT. GRECT) RETURN
108 !
109 IF (SIZE(pzs) /= ix * iy) RETURN
110 !
111 !-------------------------------------------------------------------------------
112 !
113 !* 3.1 Grid rectangular: orography is put in a 2D array
114 ! ------------------------------------------------
115 !
116 ALLOCATE(zzs(ix,iy))
117 ALLOCATE(zzsl(innx,inny))
118 
119 DO jy=1,iy
120  DO jx=1,ix
121  zzs(jx,jy) = pzs( jx + (jy-1)*ix )
122  END DO
123 END DO
124 
125 zzsl(2:innx-1,2:inny-1) = zzs(:,:)
126 zzsl(1,:) = zzsl(2,:)
127 zzsl(innx,:) = zzsl(innx-1,:)
128 zzsl(:,1) = zzsl(:,2)
129 zzsl(:,inny) = zzsl(:,inny-1)
130 
131 !------------------------------------------------------------------------------------------
132 !
133 !* 3.2. Orography of SW corner of grid meshes
134 ! -------------------------------------
135 !
136 
137 ALLOCATE(zzs_xy(innx,inny))
138 
139 zzs_xy(2:innx,2:inny) = 0.25*( zzsl(2:innx,2:inny) + zzsl(1:innx-1,2:inny) &
140  + zzsl(2:innx,1:inny-1) + zzsl(1:innx-1,1:inny-1) )
141 !
142 zzs_xy(1,:) = zzs_xy(2,:)
143 zzs_xy(:,1) = zzs_xy(:,2)
144 
145 !
146 !* 3.3 Initialize Grid meshes
147 ! -----------
148 !
149 ALLOCATE(zxhat(innx))
150 ALLOCATE(zyhat(inny))
151 
152 DO jx=1,innx
153  zxhat(jx) = zdx(1)*jx
154 END DO
155 DO jy=1,inny
156  zyhat(jy) = zdy(1)*jy
157 END DO
158 
159 DEALLOCATE(zdx,zdy)
160 
161 !-------------------------------------------------------------------------------
162 !
163 iib= 1+jphext
164 iie=innx-jphext
165 ijb=1+jphext
166 ije=inny-jphext
167 !
168 ALLOCATE(zmap(innx,inny))
169 zmap(:,:)=1.0
170 ALLOCATE(zsso_slope(ix,iy))
171 
172 !-------------------------------------------------------------------------------
173 !
174 !* 1. LOOP ON GRID MESHES
175 ! -------------------
176 !
177 !* discretization of the grid mesh in four triangles
178 !
179 !
180 DO jj=ijb,ije
181  DO ji=iib,iie
182  zsurf=0.
183  DO jt=1,4
184 !
185 !* slopes in x and y
186 !
187  SELECT CASE (jt)
188  CASE (1)
189  zdzsdx=( 2.* zzsl(ji,jj) &
190  - (zzs_xy(ji,jj)+zzs_xy(ji,jj+1)) ) &
191  / (zxhat(ji+1)-zxhat(ji)) * zmap(ji,jj)
192  zdzsdy=( zzs_xy(ji,jj+1) - zzs_xy(ji,jj) ) &
193  / (zyhat(jj+1)-zyhat(jj)) * zmap(ji,jj)
194  CASE (2)
195  zdzsdx=( zzs_xy(ji+1,jj+1) -zzs_xy(ji,jj+1)) &
196  / (zxhat(ji+1)-zxhat(ji)) * zmap(ji,jj)
197  zdzsdy=( (zzs_xy(ji+1,jj+1)+zzs_xy(ji,jj+1)) &
198  - 2.* zzsl(ji,jj) ) &
199  / (zyhat(jj+1)-zyhat(jj)) * zmap(ji,jj)
200  CASE (3)
201  zdzsdx=( (zzs_xy(ji+1,jj)+zzs_xy(ji+1,jj+1)) &
202  - 2.* zzsl(ji,jj) ) &
203  / (zxhat(ji+1)-zxhat(ji)) * zmap(ji,jj)
204  zdzsdy=( zzs_xy(ji+1,jj+1) - zzs_xy(ji+1,jj) ) &
205  / (zyhat(jj+1)-zyhat(jj)) * zmap(ji,jj)
206  CASE (4)
207  zdzsdx=( zzs_xy(ji+1,jj) - zzs_xy(ji,jj) ) &
208  / (zxhat(ji+1)-zxhat(ji)) * zmap(ji,jj)
209  zdzsdy=( 2.* zzsl(ji,jj) &
210  - (zzs_xy(ji+1,jj)+zzs_xy(ji,jj)) ) &
211  / (zyhat(jj+1)-zyhat(jj)) * zmap(ji,jj)
212  END SELECT
213 !
214 !
215  ! If slope is higher than 60 degrees : numerical problems
216  zdzsdx=min(2.0,max(-2.0,zdzsdx))
217  zdzsdy=min(2.0,max(-2.0,zdzsdy))
218 
219  ! total surface of 4 triangles
220  zsurf=zsurf+0.25*sqrt(1. + zdzsdx**2 + zdzsdy**2)
221 
222  END DO
223 
224  !equivalent tangent slope of a homogeneous surface with the same area
225  zsso_slope(ji-jphext,jj-jphext)=sqrt(zsurf**2-1)
226 
227  END DO
228 END DO
229 DEALLOCATE(zzsl)
230 DEALLOCATE(zzs)
231 DEALLOCATE(zzs_xy)
232 DEALLOCATE(zmap)
233 
234 DO jy=1,iy
235  DO jx=1,ix
236  psso_slope( jx + (jy-1)*ix )=zsso_slope(jx,jy)
237  END DO
238 END DO
239 
240 
241 
242 END SUBROUTINE explicit_slope
subroutine get_grid_dim(HGRID, KGRID_PAR, PGRID_PAR, ORECT, KDIM1, KDIM2)
Definition: get_grid_dim.F90:6
subroutine get_mesh_dim(HGRID, KGRID_PAR, KL, PGRID_PAR, PDX, PDY, PMESHSIZE)
Definition: get_mesh_dim.F90:6
subroutine explicit_slope(UG, PZS, PSSO_SLOPE)