SURFEX v8.1
General documentation of Surfex
urban_exch_coef.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 urban_exch_coef(HZ0H, PZ0_O_Z0H, PTG, PQS, PEXNS, PEXNA, PTA, PQA, &
7  PZREF, PUREF, PVMOD, PZ0, &
8  PRI, PCD, PCDN, PAC, PRA, PCH )
9 ! #######################################################################
10 !
11 !!**** *URBAN_DRAG*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 ! Computes the surface drag coefficients over roof, road or town
17 ! according several scientific formulations
18 !
19 !
20 !!** METHOD
21 !! ------
22 !
23 !
24 !
25 !
26 !! EXTERNAL
27 !! --------
28 !!
29 !!
30 !! IMPLICIT ARGUMENTS
31 !! ------------------
32 !!
33 !!
34 !! REFERENCE
35 !! ---------
36 !!
37 !!
38 !! AUTHOR
39 !! ------
40 !!
41 !! V. Masson * Meteo-France *
42 !!
43 !! MODIFICATIONS
44 !! -------------
45 !! Original 01/2009 from urban_drag.f90 (modified by S. Leroyer at CMC)
46 ! 01/2009 (S. Leroyer) option (HZ0H) for z0h applied on roof, road and town
47 !! B. Decharme 06/2009 limitation of Ri
48 !! B. Decharme 09/2009 limitation of Ri in surface_ri.F90
49 !
50 !-------------------------------------------------------------------------------
51 
52 USE modi_surface_ri
53 USE modi_surface_cd
54 USE modi_surface_aero_cond
55 USE modi_wind_threshold
56 !
57 USE modd_csts, ONLY : xkarman
58 !
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 USE modi_flxsurf3bx
64 !
65 IMPLICIT NONE
66 !
67  CHARACTER(LEN=6) :: HZ0H ! TEB option for z0h roof & road
68 REAL, INTENT(IN) :: PZ0_O_Z0H! z0/z0h ratio used in Mascart (1995)
69 REAL, DIMENSION(:), INTENT(IN) :: PTG ! surface temperature
70 REAL, DIMENSION(:), INTENT(IN) :: PQS ! surface specific humidity
71 REAL, DIMENSION(:), INTENT(IN) :: PEXNS ! surface exner function
72 REAL, DIMENSION(:), INTENT(IN) :: PTA ! temperature at the lowest level
73 REAL, DIMENSION(:), INTENT(IN) :: PQA ! specific humidity
74  ! at the lowest level
75 REAL, DIMENSION(:), INTENT(IN) :: PEXNA ! exner function
76  ! at the lowest level
77 REAL, DIMENSION(:), INTENT(IN) :: PVMOD ! module of the horizontal wind
78 !
79 REAL, DIMENSION(:), INTENT(IN) :: PZ0 ! roughness length for momentum
80 REAL, DIMENSION(:), INTENT(IN) :: PZREF ! reference height of the first
81  ! atmospheric level
82 REAL, DIMENSION(:), INTENT(IN) :: PUREF ! reference height of the wind
83 ! ! NOTE this is different from ZZREF
84 ! ! ONLY in stand-alone/forced mode,
85 ! ! NOT when coupled to a model (MesoNH)
86 REAL, DIMENSION(:), INTENT(OUT) :: PRI ! Richardson number
87 !
88 REAL, DIMENSION(:), INTENT(OUT) :: PCD ! drag coefficient for momentum
89 REAL, DIMENSION(:), INTENT(OUT) :: PCDN ! neutral drag coefficient for momentum
90 REAL, DIMENSION(:), INTENT(OUT) :: PAC ! aerodynamical conductance
91 REAL, DIMENSION(:), INTENT(OUT) :: PRA ! aerodynamical resistance
92 REAL, DIMENSION(:), INTENT(OUT) :: PCH ! drag coefficient for heat
93 !
94 !* local variables
95 !
96 REAL, DIMENSION(SIZE(PZ0)) :: ZZ0H ! roughness length for heat
97 !* BRUT82 & KAND07 cases
98 REAL,DIMENSION(SIZE(PTA)) :: cmu, ctu, rib,ftemp,fvap,ilmo ! temporary var for
99 REAL,DIMENSION(SIZE(PTA)) :: ue,fcor, hBL,lzz0,lzz0t,fm, fh ! flxsurf3
100 REAL,DIMENSION(SIZE(PTA)) :: z0h_roof,z0h_town,z0h_road ! local thermal roughness
101 REAL,DIMENSION(SIZE(PTA)) :: zustar, zta, ztg
102 REAL,DIMENSION(SIZE(PTA)) :: ZVMOD ! wind
103 INTEGER N
104 !
105 !* MASC95 case
106 REAL,DIMENSION(SIZE(PTA)) :: ZDIRCOSZW ! orography slope cosine
107 REAL(KIND=JPRB) :: ZHOOK_HANDLE
108 !-------------------------------------------------------------------------------
109 !
110 !* 1. Mascart 1995 exchange coefficients
111 ! ----------------------------------
112 !
113 IF (lhook) CALL dr_hook('URBAN_EXCH_COEF',0,zhook_handle)
114 IF (hz0h=='MASC95') THEN
115 !
116  zz0h = pz0 / pz0_o_z0h ! fixed ratio for MASC95
117  zdircoszw=1. ! no orography slope effect taken into account in TEB
118 !
119  CALL surface_ri(ptg, pqs, pexns, pexna, pta, pqa, &
120  pzref, puref, zdircoszw, pvmod, pri )
121 !
122  CALL surface_cd(pri, pzref, puref, pz0, zz0h, pcd, pcdn)
123 !
124  CALL surface_aero_cond(pri, pzref, puref, pvmod, pz0, zz0h, pac, pra, pch)
125 !
126 !
127 !* 2. Brutsaert 1982 or Kanda 2007 exchange coefficients
128 ! ---------------------------------------------------
129 !
130 ELSEIF(hz0h=='BRUT82' .OR. hz0h=='KAND07')THEN
131  ! initialisations
132  fcor(:)=1.0372462e-04
133 !RJ: can be removed
134  n=SIZE(pta)
135  !
136  ! Set a minimum threshold to the wind
137  zvmod(:) = wind_threshold(pvmod(:),puref(:))
138  !
139  ! First guess of u*
140  zustar(:) = 0.4 * zvmod(:) / log( puref/pz0(:) )
141  !
142  IF (hz0h=='KAND07') THEN ! Kanda 2007
143  zz0h(:)= pz0(:) * 7.4 * exp( - 1.29 *( pz0(:)*zustar(:)/1.461e-5)**0.25)
144  ELSEIF (hz0h=='BRUT82') THEN ! Brutsaert 1982
145  zz0h(:)= pz0(:) * 7.4 * exp( - 2.46 *( pz0(:)*zustar(:)/1.461e-5)**0.25)
146  ENDIF
147 
148  zta = pta/pexna
149  ztg = ptg/pexns
150  CALL flxsurf3bx( cmu, ctu, pri,ftemp,fvap,ilmo, &
151  ue, fcor, zta, pqa, &
152  puref, pzref, zvmod, ztg, pqs,&
153  hbl, pz0,zz0h, &
154  lzz0, lzz0t, fm, fh,n )
155 !
156  pcd(:) = (cmu(:)/ue(:))**2
157  pcdn(:) = (xkarman/log(puref(:)/pz0(:)))**2
158  pac(:) = (cmu(:)*ctu(:)/ue(:)**2) * zvmod(:)
159  pra(:) = 1. / pac(:)
160  pch(:) = 1. / (pra(:) * zvmod(:))
161 !
162 END IF
163 IF (lhook) CALL dr_hook('URBAN_EXCH_COEF',1,zhook_handle)
164 
165 END SUBROUTINE urban_exch_coef
real function, dimension(size(pwind)) wind_threshold(PWIND, PUREF)
subroutine surface_ri(PTG, PQS, PEXNS, PEXNA, PTA, PQA, PZREF, PUREF, PDIRCOSZW, PVMOD, PRI)
Definition: surface_ri.F90:8
real, save xkarman
Definition: modd_csts.F90:48
subroutine surface_aero_cond(PRI, PZREF, PUREF, PVMOD, PZ0, PZ0H, PAC, PRA, PCH)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine surface_cd(PRI, PZREF, PUREF, PZ0EFF, PZ0H, PCD, PCDN)
Definition: surface_cd.F90:8
logical lhook
Definition: yomhook.F90:15
subroutine flxsurf3bx(CMU, CTU, RIB, FTEMP, FVAP, ILMO, UE, FCOR, TA, QA, ZU, ZT, VA, TG, QG, H, Z0, Z0T, LZZ0, LZZ0T, FM, FH, N)
Definition: flxsurf3bx.F90:27
subroutine urban_exch_coef(HZ0H, PZ0_O_Z0H, PTG, PQS, PEXNS, PEXNA, PTA, PQA, PZREF, PUREF, PVMOD, PZ0, PRI, PCD, PCDN, PAC, PRA, PCH)