SURFEX v8.1
General documentation of Surfex
prep_isba_extern.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_isba_extern (DTCO, IO, U, GCP, &
7  HPROGRAM,HSURF,HFILE,HFILETYPE,HFILEPGD,HFILEPGDTYPE,KLUOUT,PFIELD,OKEY)
8 ! #################################################################################
9 !
10 !!**** *PREP_ISBA_EXTERN* - initializes ISBA fields from operational GRIB
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! V. Masson
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2004
29 !! B. Decharme 04/2014, external init with FA files
30 !!------------------------------------------------------------------
31 !
34 USE modd_surf_atm_n, ONLY : surf_atm_t
36 !
37 USE modd_surfex_mpi, ONLY : nrank,npio
39 USE modd_prep_isba, ONLY : xgrid_soil, xwr_def
40 USE modd_surf_par, ONLY : xundef
41 !
43 !
44 USE modi_make_choice_array
45 USE modi_prep_grid_extern
48 USE modi_open_aux_io_surf
49 USE modi_close_aux_io_surf
50 !
51 USE modi_abor1_sfx
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 IMPLICIT NONE
57 !
58 !* 0.1 declarations of arguments
59 !
60 !
61 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
62 TYPE(isba_options_t), INTENT(INOUT) :: IO
63 TYPE(surf_atm_t), INTENT(INOUT) :: U
64 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
65 !
66  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
67  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
68  CHARACTER(LEN=28), INTENT(IN) :: HFILE ! name of file
69  CHARACTER(LEN=6), INTENT(IN) :: HFILETYPE ! type of input file
70  CHARACTER(LEN=28), INTENT(IN) :: HFILEPGD ! name of file
71  CHARACTER(LEN=6), INTENT(IN) :: HFILEPGDTYPE ! type of input file
72 INTEGER, INTENT(IN) :: KLUOUT ! logical unit of output listing
73 REAL,DIMENSION(:,:,:), POINTER :: PFIELD ! field to interpolate horizontally (on final soil grid)
74 LOGICAL, OPTIONAL, INTENT(INOUT):: OKEY
75 !
76 !* 0.2 declarations of local variables
77 !
78  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
79 INTEGER :: IRESP ! reading return code
80 INTEGER :: INI ! total 1D dimension
81 INTEGER :: IPATCH ! number of patch
82 LOGICAL :: GGLACIER
83  CHARACTER(LEN=3) :: YPHOTO
84 !
85 REAL, DIMENSION(:,:,:), POINTER :: ZFIELD=>null() ! field read on initial MNH vertical soil grid, all patches
86 REAL, DIMENSION(:,:,:), POINTER :: ZD=>null() ! layer thicknesses
87 REAL, DIMENSION(:), ALLOCATABLE :: ZMASK
88 INTEGER :: JP, JL ! loop counter for patch
89 INTEGER :: IVERSION, IBUGFIX
90 LOGICAL :: GDIM
91 REAL(KIND=JPRB) :: ZHOOK_HANDLE
92 !
93 !------------------------------------------------------------------------------
94 !
95 !* 1. Preparation of IO for reading in the file
96 ! -----------------------------------------
97 !
98 !* Note that all points are read, even those without physical meaning.
99 ! These points will not be used during the horizontal interpolation step.
100 ! Their value must be defined as XUNDEF.
101 !
102 IF (lhook) CALL dr_hook('PREP_ISBA_EXTERN',0,zhook_handle)
103 !
104 !------------------------------------------------------------------------------
105 !
106 !* 2. Reading of grid
107 ! ---------------
108 !
109  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'FULL ')
110 !
111  CALL prep_grid_extern(gcp,hfilepgdtype,kluout,cingrid_type,cinterp_type,ini)
112 !
113 !
114 yrecfm='VERSION'
115  CALL read_surf(hfilepgdtype,yrecfm,iversion,iresp)
116 !
117 IF (nrank/=npio) ini = 0
118 !
119 ALLOCATE(zmask(ini))
120 IF (iversion>=7) THEN
121  yrecfm='FRAC_NATURE'
122  CALL read_surf(hfilepgdtype,yrecfm,zmask,iresp,hdir='A')
123 ELSE
124  zmask(:) = 1.
125 ENDIF
126 !
127  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
128 !
129  CALL open_aux_io_surf(hfile,hfiletype,'FULL ')
130 yrecfm='VERSION'
131  CALL read_surf(hfiletype,yrecfm,iversion,iresp)
132 yrecfm='BUG'
133  CALL read_surf(hfiletype,yrecfm,ibugfix,iresp)
134 gdim = (iversion>8 .OR. iversion==8 .AND. ibugfix>0)
135 IF (gdim) CALL read_surf(hfiletype,'SPLIT_PATCH',gdim,iresp)
136  CALL close_aux_io_surf(hfile,hfiletype)
137 !
138 IF (nrank/=npio) ini = 0
139 !
140 !---------------------------------------------------------------------------------------
141 !
142 !* 3. Transformation into physical quantity to be interpolated
143 ! --------------------------------------------------------
144 !
145 SELECT CASE(hsurf)
146 !
147 !* 3. Orography
148 ! ---------
149 !
150  CASE('ZS ')
151  ALLOCATE(pfield(ini,1,1))
152  pfield(:,:,:) = xundef
153  yrecfm='ZS'
154  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'FULL ')
155  CALL read_surf(hfilepgdtype,yrecfm,pfield(:,1,1),iresp,hdir='E')
156  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
157 !
158 !--------------------------------------------------------------------------
159 !
160 !
161 !* 3.1 Profile of temperature, water or ice in the soil
162 !
163  CASE('TG ','WG ','WGI ')
164 !* reading of the profile and its depth definition
165  CALL read_extern_isba(u, dtco, gcp, io, hfile,hfiletype,hfilepgd,hfilepgdtype,&
166  kluout,ini,hsurf,hsurf,zfield,zd,okey)
167 !
168  IF (ini>0) THEN
169  ALLOCATE(pfield(SIZE(zfield,1),SIZE(xgrid_soil),SIZE(zfield,3)))
170  DO jp=1,SIZE(zfield,3)
171  CALL interp_grid_nat(zd(:,:,jp),zfield(:,:,jp),xgrid_soil,pfield(:,:,jp))
172  END DO
173  !
174  DO jp=1,SIZE(pfield,3)
175  DO jl=1,SIZE(pfield,2)
176  WHERE (zmask(:)==0.) pfield(:,jl,jp) = xundef
177  ENDDO
178  ENDDO
179  !
180  ENDIF
181  !
182  DEALLOCATE(zfield)
183  DEALLOCATE(zd)
184 !
185 !--------------------------------------------------------------------------
186 !
187 !* 3.4 Water content intercepted on leaves, LAI
188 !
189  CASE('WR ')
190  !* number of tiles
191  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'NATURE')
192  yrecfm='PATCH_NUMBER'
193  CALL read_surf(hfilepgdtype,yrecfm,ipatch,iresp,hdir='-')
194  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
195  ALLOCATE(pfield(ini,1,ipatch))
196  pfield(:,:,:) = xundef
197  yrecfm = 'WR'
198  CALL open_aux_io_surf(hfile,hfiletype,'NATURE')
199  CALL make_choice_array(hfiletype, ipatch, gdim, yrecfm, pfield(:,1,:),hdir='E')
200  CALL close_aux_io_surf(hfile,hfiletype)
201  DO jp=1,SIZE(pfield,3)
202  WHERE (zmask(:)==0.) pfield(:,1,jp) = xundef
203  ENDDO
204 !
205  CASE('LAI ')
206  !* number of tiles
207  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'NATURE')
208  yrecfm='PATCH_NUMBER'
209  CALL read_surf(hfilepgdtype,yrecfm,ipatch,iresp,hdir='-')
210  yrecfm='PHOTO'
211  CALL read_surf(hfilepgdtype,yrecfm,yphoto,iresp,hdir='-')
212  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
213  ALLOCATE(pfield(ini,1,ipatch))
214  pfield(:,:,:) = xundef
215  IF (yphoto=='NIT' .OR. yphoto=='NCB') THEN
216  CALL open_aux_io_surf(hfile,hfiletype,'NATURE')
217  yrecfm = 'LAI'
218  CALL make_choice_array(hfiletype, ipatch, gdim, yrecfm, pfield(:,1,:),hdir='E')
219  CALL close_aux_io_surf(hfile,hfiletype)
220  DO jp=1,SIZE(pfield,3)
221  WHERE (zmask(:)==0.) pfield(:,1,jp) = xundef
222  ENDDO
223  ENDIF
224 !
225  CASE('ICE_STO')
226  !* number of tiles
227  CALL open_aux_io_surf(hfilepgd,hfilepgdtype,'NATURE')
228  yrecfm='PATCH_NUMBER'
229  CALL read_surf(hfilepgdtype,yrecfm,ipatch,iresp,hdir='-')
230  CALL close_aux_io_surf(hfilepgd,hfilepgdtype)
231  CALL open_aux_io_surf(hfile,hfiletype,'NATURE')
232  yrecfm='GLACIER'
233  CALL read_surf(hfiletype,yrecfm,gglacier,iresp,hdir='-')
234  ALLOCATE(pfield(ini,1,ipatch))
235  pfield(:,:,:) = 0.0
236  IF(gglacier)THEN
237  yrecfm = 'ICE_STO'
238  CALL make_choice_array(hfiletype, ipatch, gdim, yrecfm, pfield(:,1,:),hdir='E')
239  ENDIF
240  CALL close_aux_io_surf(hfile,hfiletype)
241  DO jp=1,SIZE(pfield,3)
242  WHERE (zmask(:)==0.) pfield(:,1,jp) = xundef
243  ENDDO
244 !
245  CASE DEFAULT
246  CALL abor1_sfx('PREP_ISBA_EXTERN: '//trim(hsurf)//" initialization not implemented !")
247 !
248 END SELECT
249 !
250 DEALLOCATE(zmask)
251 !
252 !---------------------------------------------------------------------------
253 !
254 !* 6. End of IO
255 ! ---------
256 !
257 IF (lhook) CALL dr_hook('PREP_ISBA_EXTERN',1,zhook_handle)
258 !
259 !---------------------------------------------------------------------------
260 !---------------------------------------------------------------------------
261 END SUBROUTINE prep_isba_extern
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
character(len=10) cingrid_type
Definition: modd_prep.F90:39
subroutine make_choice_array(HPROGRAM, KNPATCH, ODIM, HRECFM, PWORK, HDIR, KPATCH)
subroutine prep_isba_extern(DTCO, IO, U, GCP, HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, PFIELD, OKEY)
character(len=6) cinterp_type
Definition: modd_prep.F90:40
subroutine close_aux_io_surf(HFILE, HFILETYPE)
subroutine prep_grid_extern(GCP, HFILETYPE, KLUOUT, HGRIDTYPE, HINTER
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine read_extern_isba(U, DTCO, GCP, IO, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, KNI, HFIELD, HNAME, PFIELD, PDEPTH, OKEY)
logical lhook
Definition: yomhook.F90:15
subroutine open_aux_io_surf(HFILE, HFILETYPE, HMASK, HDIR)