SURFEX v8.1
General documentation of Surfex
sso_z0_frictionn.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 sso_z0_friction_n (USS, PSEA,PUREF,PRHOA,PU,PV,PPEW_A_COEF,PPEW_B_COEF,PSFU,PSFV)
7 ! ################################################################################
8 !
9 !!**** *SSO_Z0_FRICTION_n * - Computes subgrid-scale orography friction
10 ! according to several options:
11 ! CROUGH='Z01D' : orographic roughness length
12 ! CROUGH='Z04D' : orographic roughness length
13 ! variable with wind direction
14 !!
15 !! PURPOSE
16 !! -------
17 !
18 !!** METHOD
19 !! ------
20 !!
21 !! REFERENCE
22 !! ---------
23 !!
24 !!
25 !! AUTHOR
26 !! ------
27 !! V. Masson
28 !!
29 !! MODIFICATIONS
30 !! -------------
31 !! Original 05/2010
32 !! E. Martin 01/2012 Correction masque (compatibilité XUNDEF)
33 !! B. Decharme 09/2012 new wind implicitation and sea fraction
34 !! B. Decharme 06/2013 CIMPLICIT_WIND in MODD_REPROD_OPER
35 !! J. Escobar 05/2014 for bug with ifort/10, replace WHERE by IF
36 !! J. Escobar 06/2015 bug with gfortran ZZ0EFF to small, change with > XSURF_EPSILON
37 !----------------------------------------------------------------
38 !
39 !
40 USE modd_sso_n, ONLY : sso_t
41 !
43 !
45 USE modd_csts, ONLY : xkarman, xpi
46 !
47 USE yomhook ,ONLY : lhook, dr_hook
48 USE parkind1 ,ONLY : jprb
49 !
50 IMPLICIT NONE
51 !
52 !* 0.1 declarations of arguments
53 !
54 !
55 TYPE(sso_t), INTENT(INOUT) :: USS
56 !
57 REAL, DIMENSION(:), INTENT(IN) :: PSEA ! Sea fraction (-)
58 REAL, DIMENSION(:), INTENT(IN) :: PUREF ! Wind forcing height (m)
59 REAL, DIMENSION(:), INTENT(IN) :: PRHOA ! air density (kg/m3)
60 REAL, DIMENSION(:), INTENT(IN) :: PU ! zonal wind (m/s)
61 REAL, DIMENSION(:), INTENT(IN) :: PV ! meridian wind (m/s)
62 REAL, DIMENSION(:), INTENT(IN) :: PPEW_A_COEF! implicit coefficients (m2s/kg)
63 REAL, DIMENSION(:), INTENT(IN) :: PPEW_B_COEF! needed if HCOUPLING='I' (m/s)
64 REAL, DIMENSION(:), INTENT(INOUT) :: PSFU ! zonal momentum flux (Pa)
65 REAL, DIMENSION(:), INTENT(INOUT) :: PSFV ! meridian momentum flux (Pa)
66 !
67 !* 0.2 declarations of local variables
68 !
69 REAL, DIMENSION(SIZE(PU)) :: ZWIND ! wind strength (m/s)
70 REAL, DIMENSION(SIZE(PU)) :: ZWORK ! work array
71 REAL, DIMENSION(SIZE(PU)) :: ZDIR ! wind direction (rad., clockwise)
72 REAL, DIMENSION(SIZE(PU)) :: ZALFA ! angle between z0eff J axis and wind direction (rad., clockwise)
73 REAL, DIMENSION(SIZE(PU)) :: ZCOS2, ZSIN2
74 REAL, DIMENSION(SIZE(PU)) :: ZZ0EFF ! Momentum Roughness length
75 REAL, DIMENSION(SIZE(PU)) :: ZCD ! drag coefficient
76 REAL, DIMENSION(SIZE(PU)) :: ZUSTAR2 ! square of friction velocity
77 REAL, DIMENSION(SIZE(PU)) :: ZSSO_SFU! zonal orographic momentum flux
78 REAL, DIMENSION(SIZE(PU)) :: ZSSO_SFV! meridian orographic momentum flux
79 LOGICAL, DIMENSION(SIZE(PU)) :: GMASK ! mask where SSO exists
80 INTEGER :: II
81 REAL(KIND=JPRB) :: ZHOOK_HANDLE
82 
83 !-------------------------------------------------------------------------------------
84 !
85 IF (lhook) CALL dr_hook('SSO_Z0_FRICTION_N',0,zhook_handle)
86 !
87 zwork(:) = xundef
88 !
89 !* 1. roughness length formalism
90 ! --------------------------
91 !
92 !* wind strength
93 !
94 zwind(:) = sqrt(pu(:)**2+pv(:)**2)
95 !
96 !* wind direction
97 !
98 zdir(:) = 0.
99 WHERE (zwind(:)>0.) zdir(:)=atan2(pu(:),pv(:))
100 !
101 !* default value
102 !
103 gmask(:)=(psea(:)/=1..AND. uss%XZ0REL(:)/=0.)
104 zz0eff(:) = xundef
105 !
106 !* 2. Constant orographic roughness length
107 ! ------------------------------------
108 !
109 IF (uss%CROUGH=="Z01D") zz0eff(:) = uss%XZ0REL(:)
110 !
111 !* 3. Directionnal roughness length
112 ! -----------------------------
113 !
114 IF (uss%CROUGH=="Z04D") THEN
115  DO ii=1,SIZE(gmask)
116  IF (gmask(ii)) THEN
117  !
118  zalfa(ii) = zdir(ii) - uss%XZ0EFFJPDIR(ii) * xpi/180.
119  !
120  IF (zalfa(ii)<=-xpi) THEN
121  zalfa(ii) = zalfa(ii) + 2.*xpi
122  ELSEIF(zalfa(ii)> xpi) THEN
123  zalfa(ii) = zalfa(ii) - 2.*xpi
124  END IF
125  !
126  IF (zalfa(ii)>=-xpi.AND.zalfa(ii)<=xpi) THEN
127  !
128  zsin2(ii) = sin(zalfa(ii))**2
129  zcos2(ii) = cos(zalfa(ii))**2
130  !
131  IF (zalfa(ii)<0.) THEN
132  zz0eff(ii)=uss%XZ0EFFIM(ii)*zsin2(ii)
133  ELSE
134  zz0eff(ii)=uss%XZ0EFFIP(ii)*zsin2(ii)
135  END IF
136  !
137  IF (zalfa(ii)>=-xpi/2. .AND. zalfa(ii)<xpi/2.) THEN
138  zz0eff(ii) = zz0eff(ii) + uss%XZ0EFFJP(ii)*zcos2(ii)
139  ELSE
140  zz0eff(ii) = zz0eff(ii) + uss%XZ0EFFJM(ii)*zcos2(ii)
141  END IF
142  !
143  END IF
144  !
145  END IF
146  END DO
147 ENDIF
148 !
149 !* 4. Friction coefficient
150 ! --------------------
151 !
152 zcd(:) = 0.
153 zustar2(:) = 0.
154 !
155 gmask(:)=(gmask(:).AND.zz0eff(:)>xsurf_epsilon)
156 !
157 DO ii=1,SIZE(gmask)
158  !
159  IF (gmask(ii)) THEN
160  !
161  !* sets a limit to roughness length
162  zz0eff(ii) = min(zz0eff(ii),puref(ii)/uss%XFRACZ0)
163  !
164  ! neutral case
165  zcd(ii) = (xkarman/log(puref(ii)/zz0eff(ii)))**2
166  END IF
167  !
168 END DO
169 !
170 !* 5. Friction due to orography
171 ! -------------------------
172 !
173 ! Modify flux-form implicit coupling coefficients:
174 !
175 IF(cimplicit_wind=='OLD')THEN
176 ! old implicitation
177  zustar2(:) = zcd(:)*zwind(:)*ppew_b_coef(:) &
178  / (1.0-prhoa(:)*zcd(:)*zwind(:)*ppew_a_coef(:))
179 ELSE
180 ! new implicitation
181  zustar2(:) = (zcd(:)*zwind(:)*(2.*ppew_b_coef(:)-zwind(:)) ) &
182  / (1.0-2.0*prhoa(:)*zcd(:)*zwind(:)*ppew_a_coef(:))
183 ENDIF
184 !
185 WHERE (gmask(:))
186 !
187  zwork(:) = prhoa(:)*ppew_a_coef(:)*zustar2(:) + ppew_b_coef(:)
188  zwork(:) = max(zwork(:),0.)
189 !
190  WHERE(ppew_a_coef(:)/= 0.)
191  zustar2(:) = max( ( zwork(:) - ppew_b_coef(:) ) / (prhoa(:)*ppew_a_coef(:)), 0.)
192  ENDWHERE
193 !
194 END WHERE
195 !
196 !* 6. Projection of friction on wind components
197 ! -----------------------------------------
198 !
199 zsso_sfu(:) = 0.
200 zsso_sfv(:) = 0.
201 WHERE (zwind(:)>0.)
202  zsso_sfu(:) = - pu(:)/zwind(:) * zustar2(:) * prhoa(:)
203  zsso_sfv(:) = - pv(:)/zwind(:) * zustar2(:) * prhoa(:)
204 END WHERE
205 !
206 !* 7. Adds orographic friction to other sources of friction
207 ! -----------------------------------------------------
208 !
209 psfu(:) = psfu(:) + zsso_sfu(:) * (1.0-psea(:))
210 psfv(:) = psfv(:) + zsso_sfv(:) * (1.0-psea(:))
211 !
212 IF (lhook) CALL dr_hook('SSO_Z0_FRICTION_N',1,zhook_handle)
213 !
214 !-------------------------------------------------------------------------------------
215 !
216 END SUBROUTINE sso_z0_friction_n
character(len=3) cimplicit_wind
real, save xpi
Definition: modd_csts.F90:43
real, save xkarman
Definition: modd_csts.F90:48
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
real, parameter xsurf_epsilon
logical lhook
Definition: yomhook.F90:15
subroutine sso_z0_friction_n(USS, PSEA, PUREF, PRHOA, PU, PV, PPEW_A_COEF, PPEW_B_COEF, PSFU, PSFV)