SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
surface_ri.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 surface_ri(PTG, PQS, PEXNS, PEXNA, PTA, PQA, &
7  pzref, puref, pdircoszw, pvmod, pri )
8 ! ######################################################################
9 !
10 !!**** *SURFACE_RI*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 ! Computes the richardson number near the ground
16 !
17 !
18 !!** METHOD
19 !! ------
20 !
21 !
22 !
23 !
24 !! EXTERNAL
25 !! --------
26 !!
27 !!
28 !! IMPLICIT ARGUMENTS
29 !! ------------------
30 !!
31 !! MODD_CST
32 !! MODD_GROUND_PAR
33 !!
34 !!
35 !! REFERENCE
36 !! ---------
37 !!
38 !!
39 !! AUTHOR
40 !! ------
41 !!
42 !! V. Masson * Meteo-France *
43 !!
44 !! MODIFICATIONS
45 !! -------------
46 !! Original 22/09/98
47 !-------------------------------------------------------------------------------
48 !
49 !* 0. DECLARATIONS
50 ! ------------
51 !
52 USE modd_csts, ONLY : xrv, xrd, xg
53 USE modd_surf_atm, ONLY : xrimax
54 USE modi_wind_threshold
55 !
56 !
57 USE yomhook ,ONLY : lhook, dr_hook
58 USE parkind1 ,ONLY : jprb
59 !
60 IMPLICIT NONE
61 !
62 !* 0.1 declarations of arguments
63 !
64 !
65 REAL, DIMENSION(:), INTENT(IN) :: ptg ! surface temperature
66 REAL, DIMENSION(:), INTENT(IN) :: pqs ! surface specific humidity
67 REAL, DIMENSION(:), INTENT(IN) :: pexns ! surface exner function
68 REAL, DIMENSION(:), INTENT(IN) :: pta ! temperature at the lowest level
69 REAL, DIMENSION(:), INTENT(IN) :: pqa ! specific humidity
70  ! at the lowest level
71 REAL, DIMENSION(:), INTENT(IN) :: pexna ! exner function
72  ! at the lowest level
73 REAL, DIMENSION(:), INTENT(IN) :: pvmod ! module of the horizontal wind
74 !
75 REAL, DIMENSION(:), INTENT(IN) :: pzref ! reference height of the first
76  ! atmospheric level
77 REAL, DIMENSION(:), INTENT(IN) :: puref ! reference height of the wind
78 ! ! NOTE this is different from ZZREF
79 ! ! ONLY in stand-alone/forced mode,
80 ! ! NOT when coupled to a model (MesoNH)
81 REAL, DIMENSION(:), INTENT(IN) :: pdircoszw! Cosine of the angle between
82 ! ! the normal to the surface and
83 ! ! the vertical
84 !
85 REAL, DIMENSION(:), INTENT(OUT) :: pri ! Richardson number
86 !
87 !* 0.2 declarations of local variables
88 !
89 !
90 REAL, DIMENSION(SIZE(PTG)) :: zthva, zthvs
91 REAL, DIMENSION(SIZE(PVMOD)) :: zvmod
92 REAL(KIND=JPRB) :: zhook_handle
93 !-------------------------------------------------------------------------------
94 !
95 ! 1. Richardson number
96 ! -----------------
97 !
98 ! virtual potential
99 ! temperature at the
100 ! first atmospheric level and
101 ! at the surface
102 !
103 IF (lhook) CALL dr_hook('SURFACE_RI',0,zhook_handle)
104 !
105 zthva(:)=pta(:)/pexna(:)*( 1.+(xrv/xrd-1.)*pqa(:) )
106 zthvs(:)=ptg(:)/pexns(:)*( 1.+(xrv/xrd-1.)*pqs(:) )
107 !
108 zvmod(:) = wind_threshold(pvmod(:),puref(:))
109 !
110  ! Richardson's number
111 pri(:) = xg * pdircoszw(:) * puref(:) * puref(:) &
112  * (zthva(:)-zthvs(:)) / (0.5 * (zthva(:)+zthvs(:)) ) &
113  / (zvmod(:)*zvmod(:)) /pzref(:)
114 !
115 pri(:) = min(pri(:),xrimax)
116 !
117 IF (lhook) CALL dr_hook('SURFACE_RI',1,zhook_handle)
118 !-------------------------------------------------------------------------------
119 !
120 END SUBROUTINE surface_ri
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:6