SURFEX v8.1
General documentation of Surfex
prep_hor_flake_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_flake_field (DTCO, UG, U, USS, GCP, KLAT, F, &
7  HPROGRAM,HSURF,HATMFILE,HATMFILETYPE,&
8  HPGDFILE,HPGDFILETYPE,ONOVALUE)
9 ! #################################################################################
10 !
11 !!**** *PREP_HOR_FLAKE_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 !! E. Kourzeneva 09/2010, Make possible to interpolate
32 !! only lake surface temperature,
33 !! but not profiles
34 !!------------------------------------------------------------------
35 !
38 USE modd_surf_atm_n, ONLY : surf_atm_t
39 USE modd_sso_n, ONLY : sso_t
41 !
42 USE modd_flake_n, ONLY : flake_t
43 !
44 USE modd_surf_par, ONLY : xundef
46 USE modd_surfex_mpi, ONLY : nrank, npio, ncomm, nproc
48 USE modd_grid_grib, ONLY : cinmodel
49 !
50 USE modd_csts, ONLY : xtt
51 USE modd_prep_flake, ONLY : lclim_lake
52 !
53 USE modi_prep_grib_grid
54 USE modi_read_prep_flake_conf
55 USE modi_prep_flake_grib
56 USE modi_prep_flake_ascllv
57 USE modi_prep_flake_unif
58 USE modi_prep_flake_buffer
59 USE modi_hor_interpol
60 USE modi_get_luout
61 USE modi_prep_flake_extern
62 !
63 USE yomhook ,ONLY : lhook, dr_hook
64 USE parkind1 ,ONLY : jprb
65 !
66 USE modi_abor1_sfx
67 IMPLICIT NONE
68 !
69 #ifdef SFX_MPI
70 include "mpif.h"
71 #endif
72 !
73 !* 0.1 declarations of arguments
74 !
75 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
76 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
77 TYPE(surf_atm_t), INTENT(INOUT) :: U
78 TYPE(sso_t), INTENT(INOUT) :: USS
79 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
80 !
81 INTEGER, INTENT(IN) :: KLAT
82 TYPE(flake_t), INTENT(INOUT) :: F
83 !
84  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
85  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
86  CHARACTER(LEN=28), INTENT(IN) :: HATMFILE ! name of the Atmospheric file
87  CHARACTER(LEN=6), INTENT(IN) :: HATMFILETYPE! type of the Atmospheric file
88  CHARACTER(LEN=28), INTENT(IN) :: HPGDFILE ! name of the Atmospheric file
89  CHARACTER(LEN=6), INTENT(IN) :: HPGDFILETYPE! type of the Atmospheric file
90 LOGICAL, OPTIONAL, INTENT(OUT) :: ONOVALUE ! flag for the not given value
91 !
92 !
93 !* 0.2 declarations of local variables
94 !
95  CHARACTER(LEN=6) :: YFILETYPE ! type of input file
96  CHARACTER(LEN=28) :: YFILE ! name of file
97  CHARACTER(LEN=6) :: YFILEPGDTYPE ! type of input file
98  CHARACTER(LEN=28) :: YFILEPGD ! name of file
99  type(date_time) :: tztime_grib ! current date and time
100 REAL, POINTER, DIMENSION(:,:) :: ZFIELDIN=>null() ! field to interpolate horizontally
101 REAL, ALLOCATABLE, DIMENSION(:,:) :: ZFIELDOUT ! field interpolated horizontally
102 INTEGER :: ILUOUT ! output listing logical unit
103 INTEGER :: INL, INFOMPI
104 !
105 LOGICAL :: GUNIF ! flag for prescribed uniform field
106 LOGICAL :: GDEFAULT ! flag for prescribed default field
107 REAL(KIND=JPRB) :: ZHOOK_HANDLE
108 !-------------------------------------------------------------------------------------
109 !
110 !
111 !* 1. Reading of input file name and type
112 !
113 IF (lhook) CALL dr_hook('PREP_HOR_FLAKE_FIELD',0,zhook_handle)
114  CALL get_luout(hprogram,iluout)
115 !
116  CALL read_prep_flake_conf(hprogram,hsurf,yfile,yfiletype,yfilepgd,yfilepgdtype,&
117  hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,iluout,gunif)
118 !
119 cmask = 'WATER'
120 !
121 gdefault = (yfiletype==' ' .OR. (hsurf(1:2)/='ZS' .AND. hsurf(1:2)/='TS' &
122  .AND. klat.NE.1)) .AND. .NOT.gunif
123 IF (PRESENT(onovalue)) onovalue = gdefault
124 !
125 IF (.NOT. gdefault) THEN
126 !
127 !-------------------------------------------------------------------------------------
128 !
129 !* 2. Reading of input configuration (Grid and interpolation type)
130 !
131  IF (gunif) THEN
132  CALL prep_flake_unif(iluout,hsurf,zfieldin)
133  ELSE IF (yfiletype=='ASCLLV') THEN
134  CALL prep_flake_ascllv(dtco, ug, u, uss, hprogram,hsurf,iluout,zfieldin)
135  ELSE IF (yfiletype=='GRIB ') THEN
136  CALL prep_grib_grid(yfile,iluout,cinmodel,cingrid_type,cinterp_type,tztime_grib)
137  IF (nrank==npio) CALL prep_flake_grib(hprogram,hsurf,yfile,iluout,zfieldin)
138  ELSE IF (yfiletype=='MESONH' .OR. yfiletype=='ASCII ' .OR. yfiletype=='LFI '.OR. yfiletype=='FA '&
139  .OR.yfiletype=='NC ') THEN
140  CALL prep_flake_extern(gcp,hprogram,hsurf,yfile,yfiletype,yfilepgd,yfilepgdtype,iluout,zfieldin)
141  ELSE IF (yfiletype=='BUFFER') THEN
142  CALL prep_flake_buffer(hprogram,hsurf,iluout,zfieldin)
143  ELSE
144  CALL abor1_sfx('PREP_HOR_FLAKE_FIELD: data file type not supported : '//yfiletype)
145  END IF
146 !
147 !
148 !* 4. Horizontal interpolation
149 !
150 IF (nrank==npio) THEN
151  inl = SIZE(zfieldin,2)
152 ELSEIF (.NOT.ASSOCIATED(zfieldin)) THEN
153  ALLOCATE(zfieldin(0,0))
154 ENDIF
155 !
156 IF (nproc>1) THEN
157 #ifdef SFX_MPI
158  CALL mpi_bcast(inl,kind(inl)/4,mpi_integer,npio,ncomm,infompi)
159 #endif
160 ENDIF
161  !ALLOCATE(ZFIELDOUT(SIZE(XLAT),SIZE(ZFIELDIN,2)))
162  ALLOCATE(zfieldout(klat,1))
163 !
164 !Impossible to interpolate lake profiles, only the lake surface temperature!
165 !But in uniform case and 1 point case
166  IF(gunif .OR. klat.EQ.1) THEN
167  CALL hor_interpol(dtco, u, gcp, iluout,zfieldin,zfieldout)
168  ELSE IF(hsurf(1:2)=='ZS' .OR. hsurf(1:2)=='TS') THEN
169  WRITE(iluout,*) "WARNING! Impossible to interpolate lake profiles in horisontal!"
170  WRITE(iluout,*) "So, interoplate only surface temperature and start from lakes mixed down to the bottom"
171  CALL hor_interpol(dtco, u, gcp, iluout,zfieldin,zfieldout)
172  END IF
173 !
174 !* 5. Return to historical variable
175 !
176  SELECT CASE (hsurf)
177  CASE('ZS ')
178  ALLOCATE(xzs_ls(SIZE(zfieldout,1)))
179  xzs_ls(:) = zfieldout(:,1)
180  CASE('TS ')
181  ALLOCATE(f%XTS(SIZE(zfieldout,1)))
182  f%XTS(:) = zfieldout(:,1)
183  CASE('T_SNOW ')
184  ALLOCATE(f%XT_SNOW(SIZE(zfieldout,1)))
185  f%XT_SNOW(:) = zfieldout(:,1)
186  CASE('T_ICE ')
187  ALLOCATE(f%XT_ICE(SIZE(zfieldout,1)))
188  f%XT_ICE(:) = zfieldout(:,1)
189  CASE('T_WML ')
190  ALLOCATE(f%XT_WML(SIZE(zfieldout,1)))
191  f%XT_WML(:) = zfieldout(:,1)
192  CASE('T_BOT ')
193  ALLOCATE(f%XT_BOT(SIZE(zfieldout,1)))
194  f%XT_BOT(:) = zfieldout(:,1)
195  CASE('T_B1 ')
196  ALLOCATE(f%XT_B1(SIZE(zfieldout,1)))
197  f%XT_B1(:) = zfieldout(:,1)
198  CASE('CT ')
199  ALLOCATE(f%XCT(SIZE(zfieldout,1)))
200  f%XCT(:) = zfieldout(:,1)
201  CASE('H_SNOW ')
202  ALLOCATE(f%XH_SNOW(SIZE(zfieldout,1)))
203  f%XH_SNOW(:) = zfieldout(:,1)
204  CASE('H_ICE ')
205  ALLOCATE(f%XH_ICE(SIZE(zfieldout,1)))
206  f%XH_ICE(:) = zfieldout(:,1)
207  CASE('H_ML ')
208  ALLOCATE(f%XH_ML(SIZE(zfieldout,1)))
209  f%XH_ML(:) = zfieldout(:,1)
210  CASE('H_B1 ')
211  ALLOCATE(f%XH_B1(SIZE(zfieldout,1)))
212  f%XH_B1(:) = zfieldout(:,1)
213  END SELECT
214 !* 6. Deallocations
215 !
216  IF (all(zfieldout==xundef)) gdefault = .true.
217 !
218  DEALLOCATE(zfieldin )
219  DEALLOCATE(zfieldout)
220 !
221 END IF
222 
223 !
224 IF (gdefault) THEN
225 !
226 !* 7. Initial values of FLAKE variables are computed from TS
227 ! when uniform values are not prescribed
228  IF (hsurf(1:2)/='ZS') WRITE(iluout,*) 'NO FILE FOR FIELD ',hsurf, &
229  ': UNIFORM DEFAULT FIELD IS PRESCRIBED'
230 
231 END IF
232 !
233 IF (lhook) CALL dr_hook('PREP_HOR_FLAKE_FIELD',1,zhook_handle)
234 !
235 !-------------------------------------------------------------------------------------
236 !
237 END SUBROUTINE prep_hor_flake_field
subroutine prep_grib_grid(HGRIB, KLUOUT, HINMODEL, HGRIDTYPE, HINTERP_
character(len=10) cingrid_type
Definition: modd_prep.F90:39
subroutine prep_flake_unif(KLUOUT, HSURF, PFIELD)
real, dimension(:), allocatable xzs_ls
Definition: modd_prep.F90:45
character(len=6) cmask
Definition: modd_prep.F90:41
character(len=6) cinterp_type
Definition: modd_prep.F90:40
subroutine read_prep_flake_conf(HPROGRAM, HVAR, HFILE, HFILETYPE, HFIL
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
subroutine prep_flake_grib(HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD)
real, parameter xundef
character(len=6) cinmodel
subroutine hor_interpol(DTCO, U, GCP, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:7
integer, parameter jprb
Definition: parkind1.F90:32
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
subroutine prep_flake_buffer(HPROGRAM, HSURF, KLUOUT, PFIELD)
logical lhook
Definition: yomhook.F90:15
subroutine prep_hor_flake_field(DTCO, UG, U, USS, GCP, KLAT, F, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, ONOVALUE)
real, save xtt
Definition: modd_csts.F90:66
subroutine prep_flake_extern(GCP, HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, PFIELD)
subroutine prep_flake_ascllv(DTCO, UG, U, USS, HPROGRAM, HSURF, KLUOUT, PFIELD)