SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
z0rel_1d.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 z0rel_1d(PAOSIP,PAOSIM,PAOSJP,PAOSJM, &
7  pho2ip,pho2im,pho2jp,pho2jm, &
8  pz0rel,omask )
9 ! ######################################################################
10 !
11 !!*SUBSCALE_Z0EFF computes an effective roughness lenght deduced
12 !! from the subgrid-scale orography.
13 !!
14 !!
15 !! METHOD
16 !! ------
17 !! See M.Georgelin and al. July 1994, Monthly Weather Review.
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! M. Georgelin Laboratoire d'Aerologie
33 !!
34 !! MODIFICATION
35 !! ------------
36 !!
37 !! Original 18/12/95
38 !! 22/12/97 (V Masson) call with dummy arguments
39 !!
40 !----------------------------------------------------------------------------
41 !
42 !* 0. DECLARATION
43 ! -----------
44 !
45 USE modd_surf_par, ONLY : xundef
46 USE modd_csts, ONLY : xkarman
47 USE modd_isba_par, ONLY : xcdz0eff
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54 !* 0.1 Declaration of dummy arguments
55 ! ------------------------------
56 !
57 REAL, DIMENSION(:), INTENT(IN) :: paosip ! A/S for increasing x
58 REAL, DIMENSION(:), INTENT(IN) :: paosim ! A/S for decreasing x
59 REAL, DIMENSION(:), INTENT(IN) :: paosjp ! A/S for increasing y
60 REAL, DIMENSION(:), INTENT(IN) :: paosjm ! A/S for decreasing y
61 REAL, DIMENSION(:), INTENT(IN) :: pho2ip ! h/2 for increasing x
62 REAL, DIMENSION(:), INTENT(IN) :: pho2im ! h/2 for decreasing x
63 REAL, DIMENSION(:), INTENT(IN) :: pho2jp ! h/2 for increasing y
64 REAL, DIMENSION(:), INTENT(IN) :: pho2jm ! h/2 for decreasing y
65 !
66 REAL, DIMENSION(:), INTENT(OUT) :: pz0rel ! roughness length
67 ! ! of SSO only
68 LOGICAL, DIMENSION(:), INTENT(IN) :: omask ! mask where computations
69  ! are done
70 !
71 !* 0.2 Declaration of other local variables
72 ! ------------------------------------
73 !
74 REAL, DIMENSION(SIZE(PAOSIP)) :: zloc
75 !
76 REAL(KIND=JPRB) :: zhook_handle
77 !----------------------------------------------------------------------------
78 IF (lhook) CALL dr_hook('Z0REL_1D',0,zhook_handle)
79 !
80 pz0rel=xundef
81 !
82 zloc(:) = 0.
83 !
84 WHERE (omask(:))
85  zloc(:) = 0.25 * xcdz0eff/(2.*xkarman**2) &
86  * (paosip(:)+paosim(:)+paosjp(:)+paosjm(:))
87  WHERE ( zloc(:) > 0. )
88  pz0rel(:) = 0.25 * (pho2ip(:)+pho2im(:)+pho2jp(:)+pho2jm(:)) &
89  * exp(-sqrt(1./zloc(:)))
90  pz0rel(:) = max(pz0rel(:),1e-10)
91  ELSEWHERE
92  pz0rel(:) = 0.
93  END WHERE
94 END WHERE
95 !
96 IF (lhook) CALL dr_hook('Z0REL_1D',1,zhook_handle)
97 !-------------------------------------------------------------------------------
98 END SUBROUTINE z0rel_1d
subroutine z0rel_1d(PAOSIP, PAOSIM, PAOSJP, PAOSJM, PHO2IP, PHO2IM, PHO2JP, PHO2JM, PZ0REL, OMASK)
Definition: z0rel_1d.F90:6