SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
tsz0.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 tsz0 (DTZ, &
7  ptime, ptstep, pwfc, ptg, pwg )
8 ! ################################################################
9 !
10 !
11 !!**** *TSZ0*
12 !!
13 !! PURPOSE
14 !! -------
15 ! This subroutine computes the surface fluxes when the soil temperature,
16 ! humidity and rugisty length are prescribed. It uses these values and the
17 ! atmospheric fields at the first level located at dz/2 to compute a
18 ! vertical gradient and a drag coefficient is computed according to a
19 ! stability index ( Richardson number )
20 !
21 !!** METHOD
22 !! ------
23 !!
24 !! EXTERNAL
25 !! --------
26 !!
27 !! IMPLICIT ARGUMENTS
28 !! ------------------
29 !!
30 !! REFERENCE
31 !! ---------
32 !!
33 !!
34 !! AUTHOR
35 !! ------
36 !! J. Stein * Meteo-France *
37 !!
38 !! MODIFICATIONS
39 !! -------------
40 !! Original 25/01/96
41 !! 25/03/96 spatialize the input TS, WG, SST fields
42 !! 22/05/96 correct igrid value for the rain rate
43 !! 27/11/96 set realistic values for z0 fields on sea
44 !! V.Masson 09/07/97 add directional z0 computations and RESA correction
45 !! V.Masson 15/03/99 some computations are now done in GROUND_PARAMn
46 !! V.Masson 04/01/00 all computations are now done in ISBA
47 !! P. Le Moigne 03/2015 tsz0 time management
48 !-------------------------------------------------------------------------------
49 !
50 !* 0. DECLARATIONS
51 ! ------------
52 !
53 !
54 USE modd_data_tsz0_n, ONLY : data_tsz0_t
55 !
56 USE modd_csts, ONLY : xpi
57 USE modd_surf_par, ONLY : xundef
58 !
59 USE yomhook ,ONLY : lhook, dr_hook
60 USE parkind1 ,ONLY : jprb
61 !
62 IMPLICIT NONE
63 !
64 !* 0.1 declarations of arguments
65 !
66 !
67 !* general variables
68 ! -----------------
69 !
70 TYPE(data_tsz0_t), INTENT(INOUT) :: dtz
71 !
72 REAL, INTENT(IN) :: ptime ! Current time
73 REAL, INTENT(IN) :: ptstep ! timestep of the integration
74 !
75 !* soil variables
76 ! --------------
77 !
78 REAL, DIMENSION(:,:), INTENT(IN) :: pwfc ! field capacity
79 !
80 !* prognostic variables
81 ! --------------------
82 !
83 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: ptg ! surface temperature
84 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: pwg ! near-surface volumetric water
85 !
86 !
87 !* 0.2 declarations of local variables
88 !
89 !
90 !* local variables for Ts time interpolation
91 ! ----------------------------------------
92 !
93 REAL :: za,ztimep ! weigths and instant for the temporal interpolation
94 INTEGER :: ihourp ! hourly data index for intant t +dt
95 INTEGER :: jpatch ! loop counter on patches
96 !
97 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
98 ! enter here the temporal variations of the soil fields increments
99 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
100 !
101 ! prescribed values of the surface temperature increment over land (K)
102 REAL :: zdts_hour
103 ! prescribed values of the soil humidity increment at every hour (fraction)
104 REAL :: zdhugrd_hour
105 REAL(KIND=JPRB) :: zhook_handle
106 !-------------------------------------------------------------------------------
107 !
108 !* 1. TEMPORAL INTERPOLATION OF THE SURFACE TEMPERATURES AT T+DT
109 ! ----------------------------------------------------------
110 !
111 IF (lhook) CALL dr_hook('TSZ0',0,zhook_handle)
112 !
113 IF (dtz%NTIME==25) THEN
114  ztimep = mod(ptime+ptstep,86400.) ! recover the time from O HTU
115 ELSE
116  ztimep = ptime+ptstep ! accumulated time since beginning of run
117 ENDIF
118 !
119 ihourp = int(ztimep/3600.)+1
120 !
121 IF (dtz%NTIME==1) THEN
122  zdts_hour = dtz%XDATA_DTS (1)
123  zdhugrd_hour = dtz%XDATA_DHUGRD(1)
124 ELSE
125  zdts_hour = dtz%XDATA_DTS (ihourp)
126  zdhugrd_hour = dtz%XDATA_DHUGRD(ihourp)
127 ENDIF
128 !
129 ! temporal interpolation of the surface temperature increment over land at time t
130 za= zdts_hour /3600. * ptstep
131 WHERE (ptg(:,:,:)/=xundef)
132  ptg(:,:,:)= ptg(:,:,:) + za
133 END WHERE
134 !
135 ! temporal interpolation of the soil humidity increment at time t
136 za= zdhugrd_hour /3600.* ptstep
137 DO jpatch=1,SIZE(pwg,3)
138  WHERE (pwg(:,:,jpatch)/=xundef)
139  pwg(:,:,jpatch)= acos( 1. &
140  - 2.* min( 0.5 * (1. - cos( xpi * min(pwg(:,:,jpatch) /pwfc(:,:),1.) )) + za , 1.) &
141  ) / xpi * pwfc(:,:)
142  END WHERE
143 END DO
144 !
145 IF (lhook) CALL dr_hook('TSZ0',1,zhook_handle)
146 !-------------------------------------------------------------------------------
147 !
148 END SUBROUTINE tsz0
subroutine tsz0(DTZ, PTIME, PTSTEP, PWFC, PTG, PWG)
Definition: tsz0.F90:6