SURFEX v8.1
General documentation of Surfex
prep_watflux.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 prep_watflux (DTCO, UG, U, GCP, WG, W, SB, &
7  HPROGRAM,HATMFILE,HATMFILETYPE,HPGDFILE,HPGDFILETYPE,YDCTL)
8 ! #################################################################################
9 !
10 !!**** *PREP_WATFLUX* - prepares WATFLUX fields
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! S. Malardel
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2004
29 !! S. Riette 06/2009 PREP_WATFLUX_SBL has no more argument
30 !! P. Marguinaud10/2014, Support for a 2-part PREP
31 !!------------------------------------------------------------------
32 !
33 USE modd_sfx_grid_n, ONLY : grid_t
34 USE modd_watflux_n, ONLY : watflux_t
35 USE modd_canopy_n, ONLY : canopy_t
36 !
38 !
40 USE modd_surf_atm_n, ONLY : surf_atm_t
42 !
43 USE modi_prep_hor_watflux_field
44 USE modi_prep_ver_watflux
45 USE modi_prep_output_grid
46 USE modi_get_luout
47 USE modi_prep_sbl
48 !
49 USE modd_read_namelist, ONLY : lnam_read
51 USE modd_prep, ONLY : xzs_ls
52 USE modd_surf_atm, ONLY : lvertshift
53 !
54 USE mode_prep_ctl, ONLY : prep_ctl
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 USE modi_clean_prep_output_grid
60 !
61 IMPLICIT NONE
62 !
63 !* 0.1 declarations of arguments
64 !
65 !
66 !
67 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
68 !
69 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
70 TYPE(surf_atm_t), INTENT(INOUT) :: U
71  TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
72 TYPE(grid_t), INTENT(INOUT) :: WG
73 TYPE(watflux_t), INTENT(INOUT) :: W
74 TYPE(canopy_t), INTENT(INOUT) :: SB
75 type(prep_ctl), INTENT(INOUT) :: ydctl
76 !
77  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
78  CHARACTER(LEN=28), INTENT(IN) :: HATMFILE ! name of the Atmospheric file
79  CHARACTER(LEN=6), INTENT(IN) :: HATMFILETYPE! type of the Atmospheric file
80  CHARACTER(LEN=28), INTENT(IN) :: HPGDFILE ! name of the Atmospheric file
81  CHARACTER(LEN=6), INTENT(IN) :: HPGDFILETYPE! type of the Atmospheric file
82 !
83 !* 0.2 declarations of local variables
84 !
85 INTEGER :: JMTH, INMTH
86 !
87 INTEGER :: ILUOUT
88 LOGICAL :: GFOUND ! Return code when searching namelist
89 INTEGER :: ILUNAM ! logical unit of namelist file
90 REAL(KIND=JPRB) :: ZHOOK_HANDLE
91 !-------------------------------------------------------------------------------------
92 !
93 !* 1. Default of configuration
94 !
95 !
96 IF (lhook) CALL dr_hook('PREP_WATFLUX',0,zhook_handle)
97  CALL get_luout(hprogram,iluout)
98 !
99  CALL prep_output_grid(ug%G, wg, u%NSIZE_FULL, iluout)
100 !
101 !-------------------------------------------------------------------------------------
102 !
103 !* 2. Reading and horizontal interpolations
104 !
105 !
106 !* 2.0 Large scale orography
107 !
108  CALL prep_hor_watflux_field(dtco, u, gcp, SIZE(wg%XLAT), w, &
109  hprogram,'ZS ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,ydctl)
110 !
111 !* 2.1 Temperature
112 !
113  CALL prep_hor_watflux_field(dtco, u, gcp, SIZE(wg%XLAT), w, &
114  hprogram,'TSWATER',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,ydctl)
115 !
117 !
118 IF (ydctl%LPART6) THEN
119 
120 !* 2.2 Roughness
121 !
122  ALLOCATE(w%XZ0(SIZE(w%XTS)))
123  w%XZ0 = 0.001
124 !
125 !-------------------------------------------------------------------------------------
126 !
127 !* 3. Vertical interpolations of all variables
128 !
129  IF(lvertshift)THEN
130  CALL prep_ver_watflux(w)
131  ENDIF
132 !
133  DEALLOCATE(xzs_ls)
134 !-------------------------------------------------------------------------------------
135 !
136 !* 4. Preparation of optional interpolation of monthly ts water
137 !
138  w%LINTERPOL_TS=.false.
139  IF(w%CINTERPOL_TS/='NONE ')THEN
140  w%LINTERPOL_TS=.true.
141  ENDIF
142 !
143  IF(w%LINTERPOL_TS)THEN
144 !
145 ! Precedent, Current, Next, and Second-next Monthly TS water
146  inmth=4
147 !
148  ALLOCATE(w%XTS_MTH(SIZE(w%XTS),inmth))
149  DO jmth=1,inmth
150  w%XTS_MTH(:,jmth)=w%XTS(:)
151  ENDDO
152 !
153  ENDIF
154 !
155 !-------------------------------------------------------------------------------------
156 !
157 !* 5. Preparation of SBL air variables
158 !
159  w%LSBL = lwat_sbl
160  IF (w%LSBL) CALL prep_sbl(wg%NDIM, sb)
161 !
162 ENDIF
163 !
164 IF (lhook) CALL dr_hook('PREP_WATFLUX',1,zhook_handle)
165 !
166 !-------------------------------------------------------------------------------------
167 !
168 END SUBROUTINE prep_watflux
subroutine prep_sbl(KDIM, SB)
Definition: prep_sbl.F90:7
subroutine prep_ver_watflux(W)
subroutine prep_hor_watflux_field(DTCO, U, GCP, KLAT, W, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, YDCTL)
subroutine prep_watflux(DTCO, UG, U, GCP, WG, W, SB, HPROGRAM, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, YDCTL)
Definition: prep_watflux.F90:8
subroutine clean_prep_output_grid
real, dimension(:), allocatable xzs_ls
Definition: modd_prep.F90:45
integer, parameter jprb
Definition: parkind1.F90:32
subroutine prep_output_grid(UG, G, KSIZE_FULL, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15
logical lvertshift