SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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, WM, &
7  hprogram,hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
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 !!------------------------------------------------------------------
31 !
32 !
33 !
35 !
36 !
38 !
40 USE modd_surf_atm_n, ONLY : surf_atm_t
41 !
42 USE modi_prep_hor_watflux_field
43 USE modi_prep_ver_watflux
44 USE modi_prep_output_grid
45 USE modi_get_luout
46 USE modi_prep_watflux_sbl
47 !
48 USE modd_read_namelist, ONLY : lnam_read
50 USE modd_prep, ONLY : xzs_ls
51 USE modd_surf_atm, ONLY : lvertshift
52 
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 USE modi_clean_prep_output_grid
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 declarations of arguments
62 !
63 !
64 !
65 TYPE(data_cover_t), INTENT(INOUT) :: dtco
66 !
67 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
68 TYPE(surf_atm_t), INTENT(INOUT) :: u
69 TYPE(watflux_model_t), INTENT(INOUT) :: wm
70 !
71  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
72  CHARACTER(LEN=28), INTENT(IN) :: hatmfile ! name of the Atmospheric file
73  CHARACTER(LEN=6), INTENT(IN) :: hatmfiletype! type of the Atmospheric file
74  CHARACTER(LEN=28), INTENT(IN) :: hpgdfile ! name of the Atmospheric file
75  CHARACTER(LEN=6), INTENT(IN) :: hpgdfiletype! type of the Atmospheric file
76 !
77 !* 0.2 declarations of local variables
78 !
79 INTEGER :: jmth, inmth
80 !
81 INTEGER :: iluout
82 LOGICAL :: gfound ! Return code when searching namelist
83 INTEGER :: ilunam ! logical unit of namelist file
84 REAL(KIND=JPRB) :: zhook_handle
85 !-------------------------------------------------------------------------------------
86 !
87 !* 1. Default of configuration
88 !
89 !
90 IF (lhook) CALL dr_hook('PREP_WATFLUX',0,zhook_handle)
91  CALL get_luout(hprogram,iluout)
92 !
93  CALL prep_output_grid(ug, u, &
94  iluout,wm%WG%CGRID,wm%WG%XGRID_PAR,wm%WG%XLAT,wm%WG%XLON)
95 !
96 !-------------------------------------------------------------------------------------
97 !
98 !* 2. Reading and horizontal interpolations
99 !
100 !
101 !* 2.0 Large scale orography
102 !
103  CALL prep_hor_watflux_field(dtco, u, &
104  wm%WG, wm%W, &
105  hprogram,'ZS ',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
106 !
107 !* 2.1 Temperature
108 !
109  CALL prep_hor_watflux_field(dtco, u, &
110  wm%WG, wm%W, &
111  hprogram,'TSWATER',hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
112 !
113 !* 2.2 Roughness
114 !
115 ALLOCATE(wm%W%XZ0(SIZE(wm%W%XTS)))
116 wm%W%XZ0 = 0.001
117 !
118 !-------------------------------------------------------------------------------------
120 !-------------------------------------------------------------------------------------
121 !
122 !* 3. Vertical interpolations of all variables
123 !
124 IF(lvertshift)THEN
125  CALL prep_ver_watflux(wm%W)
126 ENDIF
127 !
128 DEALLOCATE(xzs_ls)
129 !-------------------------------------------------------------------------------------
130 !
131 !* 4. Preparation of optional interpolation of monthly ts water
132 !
133 wm%W%LINTERPOL_TS=.false.
134 IF(wm%W%CINTERPOL_TS/='NONE ')THEN
135  wm%W%LINTERPOL_TS=.true.
136 ENDIF
137 !
138 IF(wm%W%LINTERPOL_TS)THEN
139 !
140 ! Precedent, Current, Next, and Second-next Monthly TS water
141  inmth=4
142 !
143  ALLOCATE(wm%W%XTS_MTH(SIZE(wm%W%XTS),inmth))
144  DO jmth=1,inmth
145  wm%W%XTS_MTH(:,jmth)=wm%W%XTS(:)
146  ENDDO
147 !
148 ENDIF
149 !
150 !-------------------------------------------------------------------------------------
151 !
152 !* 5. Preparation of SBL air variables
153 !
154 wm%W%LSBL = lwat_sbl
155 IF (wm%W%LSBL) CALL prep_watflux_sbl(wm%WG, wm%WSB)
156 IF (lhook) CALL dr_hook('PREP_WATFLUX',1,zhook_handle)
157 !
158 !-------------------------------------------------------------------------------------
159 !
160 END SUBROUTINE prep_watflux
subroutine prep_ver_watflux(W)
subroutine clean_prep_output_grid
subroutine prep_watflux_sbl(WG, WSB)
subroutine prep_hor_watflux_field(DTCO, U, WG, W, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine prep_watflux(DTCO, UG, U, WM, HPROGRAM, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE)
Definition: prep_watflux.F90:6
subroutine prep_output_grid(UG, U, KLUOUT, HGRID, PGRID_PAR, PLAT, PLON)