SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_hor_seaflux_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_seaflux_field (DTCO, UG, U, &
7  dts, o, or, sg, s, &
8  hprogram,hsurf,hatmfile,hatmfiletype,hpgdfile,hpgdfiletype)
9 ! #################################################################################
10 !
11 !!**** *PREP_HOR_SEAFLUX_FIELD* - reads, interpolates and prepares a sea 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 !! P. Le Moigne 09/2007, sst from clim
32 !! S. Senesi 09/2013, extends to fields of SSS and SIC
33 !!------------------------------------------------------------------
34 !
35 
36 !
37 !
38 !
39 !
40 !
41 !
42 !
43 !
46 USE modd_surf_atm_n, ONLY : surf_atm_t
47 !
49 USE modd_ocean_n, ONLY : ocean_t
50 USE modd_ocean_rel_n, ONLY : ocean_rel_t
52 USE modd_seaflux_n, ONLY : seaflux_t
53 !
54 USE modd_prep, ONLY : cingrid_type, cinterp_type, xzs_ls, xlat_out, xlon_out, &
55  xx_out, xy_out, cmask
56 !
57 USE modi_read_prep_seaflux_conf
58 USE modi_prep_seaflux_grib
59 USE modi_prep_seaflux_unif
60 USE modi_prep_seaflux_buffer
61 USE modi_prep_seaflux_netcdf
62 USE modi_hor_interpol
63 USE modi_get_luout
64 USE modi_prep_seaflux_extern
65 USE modi_prep_sst_init
66 !
67 USE modi_prep_hor_ocean_fields
68 !
69 USE yomhook ,ONLY : lhook, dr_hook
70 USE parkind1 ,ONLY : jprb
71 !
72 USE modi_abor1_sfx
73 IMPLICIT NONE
74 !
75 !* 0.1 declarations of arguments
76 !
77 !
78 !
79 TYPE(data_cover_t), INTENT(INOUT) :: dtco
80 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
81 TYPE(surf_atm_t), INTENT(INOUT) :: u
82 !
83 TYPE(data_seaflux_t), INTENT(INOUT) :: dts
84 TYPE(ocean_t), INTENT(INOUT) :: o
85 TYPE(ocean_rel_t), INTENT(INOUT) :: or
86 TYPE(seaflux_grid_t), INTENT(INOUT) :: sg
87 TYPE(seaflux_t), INTENT(INOUT) :: s
88 !
89  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
90  CHARACTER(LEN=7), INTENT(IN) :: hsurf ! type of field
91  CHARACTER(LEN=28), INTENT(IN) :: hatmfile ! name of the Atmospheric file
92  CHARACTER(LEN=6), INTENT(IN) :: hatmfiletype! type of the Atmospheric file
93  CHARACTER(LEN=28), INTENT(IN) :: hpgdfile ! name of the Atmospheric file
94  CHARACTER(LEN=6), INTENT(IN) :: hpgdfiletype! type of the Atmospheric file
95 !
96 !* 0.2 declarations of local variables
97 !
98  CHARACTER(LEN=6) :: yfiletype ! type of input file
99  CHARACTER(LEN=28) :: yfile ! name of file
100  CHARACTER(LEN=6) :: yfilepgdtype ! type of input file
101  CHARACTER(LEN=28) :: yfilepgd ! name of file
102 REAL, POINTER, DIMENSION(:,:) :: zfieldin ! field to interpolate horizontally
103 REAL, ALLOCATABLE, DIMENSION(:,:) :: zfieldout ! field interpolated horizontally
104 INTEGER :: iluout ! output listing logical unit
105 !
106 LOGICAL :: gunif ! flag for prescribed uniform 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_SEAFLUX_FIELD',0,zhook_handle)
114  CALL get_luout(hprogram,iluout)
115 !
116  CALL read_prep_seaflux_conf(o, &
117  hprogram,hsurf,yfile,yfiletype,yfilepgd,yfilepgdtype,&
118  hatmfile,hatmfiletype,hpgdfile,hpgdfiletype,iluout,gunif)
119 !
120  cmask = 'SEA'
121 !--------------------------------------------------------------------- ----------------
122 !
123 !* 2. Reading of input configuration (Grid and interpolation type)
124 !
125 IF (gunif) THEN
126  CALL prep_seaflux_unif(iluout,hsurf,zfieldin)
127 ELSE IF (yfiletype=='GRIB ') THEN
128  CALL prep_seaflux_grib(hprogram,hsurf,yfile,iluout,zfieldin)
129 ELSE IF (yfiletype=='MESONH' .OR. yfiletype=='ASCII ' .OR. yfiletype=='LFI '.OR. yfiletype=='FA ') THEN
130  CALL prep_seaflux_extern(&
131  hprogram,hsurf,yfile,yfiletype,yfilepgd,yfilepgdtype,iluout,zfieldin)
132 ELSE IF (yfiletype=='BUFFER') THEN
133  CALL prep_seaflux_buffer(hprogram,hsurf,iluout,zfieldin)
134 ELSE IF (yfiletype=='NETCDF') THEN
135  CALL prep_seaflux_netcdf(hprogram,hsurf,yfile,iluout,zfieldin)
136 ELSE
137  CALL abor1_sfx('PREP_HOR_SEAFLUX_FIELD: data file type not supported : '//yfiletype)
138 END IF
139 !
140 !
141 !* 4. Horizontal interpolation
142 !
143 ALLOCATE(zfieldout(SIZE(sg%XLAT),SIZE(zfieldin,2)))
144 !
145  CALL hor_interpol(dtco, u, &
146  iluout,zfieldin,zfieldout)
147 !
148 !* 5. Return to historical variable
149 !
150 SELECT CASE (hsurf)
151  CASE('ZS ')
152  ALLOCATE(xzs_ls(SIZE(zfieldout,1)))
153  xzs_ls(:) = zfieldout(:,1)
154  CASE('SST ')
155  ALLOCATE(s%XSST(SIZE(zfieldout,1)))
156  s%XSST(:) = zfieldout(:,1)
157  IF (dts%LSST_DATA) THEN
158  ! XSST is derived from array XDATA_SST from MODD_DATA_SEAFLUX, with time interpolation
159  CALL prep_sst_init(dts, s, &
160  s%XSST)
161  END IF
162  IF (o%LMERCATOR) THEN
163  ! Preparing input for ocean 1D model
164  CALL prep_hor_ocean_fields(dtco, ug, u, &
165  o, or, sg, s, &
166  hprogram,hsurf,yfile,yfiletype,iluout,gunif)
167  ENDIF
168  CASE('SSS ')
169  ALLOCATE(s%XSSS(SIZE(zfieldout,1)))
170  s%XSSS(:) = zfieldout(:,1)
171  CASE('SIC ')
172  ALLOCATE(s%XSIC(SIZE(zfieldout,1)))
173  s%XSIC(:) = zfieldout(:,1)
174 END SELECT
175 !
176 !-------------------------------------------------------------------------------------
177 !
178 !* 6. Deallocations
179 !
180 DEALLOCATE(zfieldin )
181 DEALLOCATE(zfieldout)
182 IF (lhook) CALL dr_hook('PREP_HOR_SEAFLUX_FIELD',1,zhook_handle)
183 !
184 !-------------------------------------------------------------------------------------
185 !
186 END SUBROUTINE prep_hor_seaflux_field
subroutine prep_hor_ocean_fields(DTCO, UG, U, O, OR, SG, S, HPROGRAM, HSURF, HFILE, HFILETYPE, KLUOUT, OUNIF)
subroutine prep_hor_seaflux_field(DTCO, UG, U, DTS, O, OR, SG, S, HPROGRAM, HSURF, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine hor_interpol(DTCO, U, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:6
subroutine prep_seaflux_buffer(HPROGRAM, HSURF, KLUOUT, PFIELD)
subroutine prep_seaflux_unif(KLUOUT, HSURF, PFIELD)
subroutine prep_seaflux_extern(HPROGRAM, HSURF, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, KLUOUT, PFIELD)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine prep_sst_init(DTS, S, PSST)
subroutine prep_seaflux_grib(HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD)
subroutine read_prep_seaflux_conf(O, HPROGRAM, HVAR, HFILE, HFILETYPE, HFILEPGD, HFILEPGDTYPE, HATMFILE, HATMFILETYPE, HPGDFILE, HPGDFILETYPE, KLUOUT, OUNIF)
subroutine prep_seaflux_netcdf(HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD)