SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_hor_watflux_field.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_hor_watflux_field (DTCO, U, &
7  wg, w, &
8  hprogram,hsurf,hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
9 ! #################################################################################
10 !
11 !!**** *PREP_HOR_WATFLUX_FIELD* - Reads, interpolates and prepares a water field
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 !!** METHOD
17 !! ------
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !!
23 !! AUTHOR
24 !! ------
25 !! S. Malardel
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 01/2004
30 !! P. Le Moigne 10/2005, Phasage Arome
31 !!------------------------------------------------------------------
32 !
33 !
34 !
35 !
36 !
37 !
38 !
40 USE modd_surf_atm_n, ONLY : surf_atm_t
41 !
43 USE modd_watflux_n, ONLY : watflux_t
44 !
45 USE modd_prep, ONLY : cingrid_type, cinterp_type, xzs_ls, xlat_out, xlon_out, &
46  xx_out, xy_out, cmask
47 !
48 USE modi_read_prep_watflux_conf
49 USE modi_prep_watflux_grib
50 USE modi_prep_watflux_unif
51 USE modi_prep_watflux_buffer
52 USE modi_hor_interpol
53 USE modi_get_luout
54 USE modi_prep_watflux_extern
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 USE modi_abor1_sfx
60 IMPLICIT NONE
61 !
62 !* 0.1 declarations of arguments
63 !
64 !
65 !
66 TYPE(data_cover_t), INTENT(INOUT) :: dtco
67 TYPE(surf_atm_t), INTENT(INOUT) :: u
68 !
69 TYPE(watflux_grid_t), INTENT(INOUT) :: wg
70 TYPE(watflux_t), INTENT(INOUT) :: w
71 !
72  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
73  CHARACTER(LEN=7), INTENT(IN) :: hsurf ! type of field
74  CHARACTER(LEN=28), INTENT(IN) :: hatmfile ! name of the Atmospheric file
75  CHARACTER(LEN=6), INTENT(IN) :: hatmfiletype! type of the Atmospheric file
76  CHARACTER(LEN=28), INTENT(IN) :: hpgdfile ! name of the Atmospheric file
77  CHARACTER(LEN=6), INTENT(IN) :: hpgdfiletype! type of the Atmospheric file
78 !
79 !* 0.2 declarations of local variables
80 !
81  CHARACTER(LEN=6) :: yfiletype ! type of input file
82  CHARACTER(LEN=28) :: yfile ! name of file
83  CHARACTER(LEN=6) :: yfilepgdtype ! type of input file
84  CHARACTER(LEN=28) :: yfilepgd ! name of file
85 REAL, POINTER, DIMENSION(:,:) :: zfieldin ! field to interpolate horizontally
86 REAL, ALLOCATABLE, DIMENSION(:,:) :: zfieldout ! field interpolated horizontally
87 INTEGER :: iluout ! output listing logical unit
88 !
89 LOGICAL :: gunif ! flag for prescribed uniform field
90 REAL(KIND=JPRB) :: zhook_handle
91 !-------------------------------------------------------------------------------------
92 !
93 !
94 !* 1. Reading of input file name and type
95 !
96 IF (lhook) CALL dr_hook('PREP_HOR_WATFLUX_FIELD',0,zhook_handle)
97  CALL get_luout(hprogram,iluout)
98 !
99  CALL read_prep_watflux_conf(hprogram,hsurf,yfile,yfiletype,yfilepgd,yfilepgdtype,&
100  hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,iluout,gunif)
101 !
102  cmask = 'WATER'
103 !
104 !-------------------------------------------------------------------------------------
105 !
106 !* 2. Reading of input configuration (Grid and interpolation type)
107 !
108 IF (gunif) THEN
109  CALL prep_watflux_unif(iluout,hsurf,zfieldin)
110 ELSE IF (yfiletype=='GRIB ') THEN
111  CALL prep_watflux_grib(hprogram,hsurf,yfile,iluout,zfieldin)
112 ELSE IF (yfiletype=='MESONH' .OR. yfiletype=='ASCII ' .OR. yfiletype=='LFI '.OR. yfiletype=='FA ') THEN
113  CALL prep_watflux_extern(&
114  hprogram,hsurf,yfile,yfiletype,yfilepgd,yfilepgdtype,iluout,zfieldin)
115 ELSE IF (yfiletype=='BUFFER') THEN
116  CALL prep_watflux_buffer(hprogram,hsurf,iluout,zfieldin)
117 ELSE
118  CALL abor1_sfx('PREP_HOR_WATFLUX_FIELD: data file type not supported : '//yfiletype)
119 END IF
120 !
121 !
122 !* 4. Horizontal interpolation
123 !
124 ALLOCATE(zfieldout(SIZE(wg%XLAT),SIZE(zfieldin,2)))
125 !
126  CALL hor_interpol(dtco, u, &
127  iluout,zfieldin,zfieldout)
128 !
129 !* 5. Return to historical variable
130 !
131 SELECT CASE (hsurf)
132  CASE('ZS ')
133  ALLOCATE(xzs_ls(SIZE(zfieldout,1)))
134  xzs_ls(:) = zfieldout(:,1)
135  CASE('TSWATER')
136  ALLOCATE(w%XTS(SIZE(zfieldout,1)))
137  w%XTS(:) = zfieldout(:,1)
138 END SELECT
139 !
140 !-------------------------------------------------------------------------------------
141 !
142 !* 6. Deallocations
143 !
144 DEALLOCATE(zfieldin )
145 DEALLOCATE(zfieldout)
146 IF (lhook) CALL dr_hook('PREP_HOR_WATFLUX_FIELD',1,zhook_handle)
147 !
148 !-------------------------------------------------------------------------------------
149 !
150 END SUBROUTINE prep_hor_watflux_field
subroutine read_prep_watflux_conf(HPROGRAM, HVAR, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, KLUOUT, OUNIF)
subroutine prep_watflux_extern(HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, PFIELD)
subroutine prep_watflux_unif(KLUOUT, HSURF, PFIELD)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine hor_interpol(DTCO, U, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:6
subroutine prep_watflux_buffer(HPROGRAM, HSURF, KLUOUT, PFIELD)
subroutine prep_hor_watflux_field(DTCO, U, WG, W, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE)
subroutine prep_watflux_grib(HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6