SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
zoom_pgd_seaflux.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 ! ######spl
6  SUBROUTINE zoom_pgd_seaflux (DTCO, DTS, SG, S, UG, U, &
7  hprogram,hinifile,hinifiletype,hfile,hfiletype)
8 ! ##############################################################
9 !
10 !!**** *PGD_SEAFLUX* monitor for averaging and interpolations of SEAFLUX physiographic fields
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! METHOD
16 !! ------
17 !!
18 !
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 !! P. Le Moigne Meteo-France
32 !!
33 !! MODIFICATION
34 !! ------------
35 !!
36 !! Original 09/2008
37 !! G. TANGUY 03/2009 : add reading and interpolation of XDATA_SST and
38 !! TDATA_SST in the case LDATA_SST=T
39 !!
40 !----------------------------------------------------------------------------
41 !
42 !* 0. DECLARATION
43 ! -----------
44 !
45 !
46 !
47 !
48 !
52 USE modd_seaflux_n, ONLY : seaflux_t
54 USE modd_surf_atm_n, ONLY : surf_atm_t
55 !
56 USE modd_data_cover_par, ONLY : jpcover
57 USE modd_prep, ONLY : cingrid_type, cinterp_type, linterp
58 !
59 !
60 USE modi_get_luout
61 USE modi_open_aux_io_surf
62 USE modi_get_surf_size_n
63 USE modi_pack_pgd
64 USE modi_prep_grid_extern
65 USE modi_prep_output_grid
67 USE modi_hor_interpol
68 USE modi_read_pgd_seaflux_par_n
69 USE modi_close_aux_io_surf
70 USE modi_clean_prep_output_grid
71 !
72 USE yomhook ,ONLY : lhook, dr_hook
73 USE parkind1 ,ONLY : jprb
74 !
75 IMPLICIT NONE
76 !
77 !* 0.1 Declaration of arguments
78 ! ------------------------
79 !
80 !
81 TYPE(data_cover_t), INTENT(INOUT) :: dtco
82 TYPE(data_seaflux_t), INTENT(INOUT) :: dts
83 TYPE(seaflux_grid_t), INTENT(INOUT) :: sg
84 TYPE(seaflux_t), INTENT(INOUT) :: s
85 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
86 TYPE(surf_atm_t), INTENT(INOUT) :: u
87 !
88  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
89  CHARACTER(LEN=28), INTENT(IN) :: hinifile ! input atmospheric file name
90  CHARACTER(LEN=6), INTENT(IN) :: hinifiletype! input atmospheric file type
91  CHARACTER(LEN=28), INTENT(IN) :: hfile ! output file name
92  CHARACTER(LEN=6), INTENT(IN) :: hfiletype ! output file type
93 !
94 !
95 !* 0.2 Declaration of local variables
96 ! ------------------------------
97 !
98 !* 0.3 Declaration of namelists
99 ! ------------------------
100 !
101 REAL, DIMENSION(:,:), ALLOCATABLE :: zseabathy, zwork
102 INTEGER :: iluout
103 INTEGER :: ini
104 INTEGER :: iresp
105 INTEGER :: jtime ! loop index
106 INTEGER :: iversion, ibugfix
107 REAL(KIND=JPRB) :: zhook_handle
108 !
109 !-------------------------------------------------------------------------------
110 !
111 IF (lhook) CALL dr_hook('ZOOM_PGD_SEAFLUX',0,zhook_handle)
112  CALL get_luout(hprogram,iluout)
113 !
114 !* 1. Preparation of IO for reading in the file
115 ! -----------------------------------------
116 !
117 !* Note that all points are read, even those without physical meaning.
118 ! These points will not be used during the horizontal interpolation step.
119 ! Their value must be defined as XUNDEF.
120 !
121 !
122  CALL open_aux_io_surf(&
123  hinifile,hinifiletype,'FULL ')
124 !
125 !-------------------------------------------------------------------------------
126 !
127 !* 5. Number of points and packing
128 ! ----------------------------
129 !
130  CALL get_surf_size_n(dtco, u, &
131  'SEA ',sg%NDIM)
132 !
133 ALLOCATE(s%LCOVER (jpcover))
134 ALLOCATE(s%XZS (sg%NDIM))
135 ALLOCATE(sg%XLAT (sg%NDIM))
136 ALLOCATE(sg%XLON (sg%NDIM))
137 ALLOCATE(sg%XMESH_SIZE (sg%NDIM))
138 !
139  CALL pack_pgd(dtco, u, &
140  hprogram, 'SEA ', &
141  sg%CGRID, sg%XGRID_PAR, s%LCOVER, &
142  s%XCOVER, s%XZS, &
143  sg%XLAT, sg%XLON, sg%XMESH_SIZE )
144 !
145 !------------------------------------------------------------------------------
146 !
147 !* 2. Reading of grid
148 ! ---------------
149 !
150  CALL prep_grid_extern(&
151  hinifiletype,iluout,cingrid_type,cinterp_type,ini)
152 !
153  CALL prep_output_grid(ug, u, &
154  iluout,sg%CGRID,sg%XGRID_PAR,sg%XLAT,sg%XLON)
155 !
156 !* mask where interpolations must be done
157 !
158 linterp(:) = .true.
159 !
160 !------------------------------------------------------------------------------
161 !
162 !* 3. Reading of fields
163 ! -----------------
164 !
165 ALLOCATE(zseabathy(ini,1))
166  CALL read_surf(&
167  hprogram,'BATHY',zseabathy(:,1),iresp,hdir='A')
168 !
169 ALLOCATE(zwork(sg%NDIM,1))
170  CALL hor_interpol(dtco, u, &
171  iluout,zseabathy(:,1:1),zwork(:,1:1))
172 ALLOCATE(s%XSEABATHY (sg%NDIM))
173 s%XSEABATHY(:) = zwork(:,1)
174 DEALLOCATE(zseabathy,zwork)
175 !
176 !============================================================
177 ! G. TANGUY 03/2009
178 ! reading of fields for SST_DATA
179  CALL read_surf(&
180  hprogram,'SST_DATA',dts%LSST_DATA,iresp)
181 !
182 IF (dts%LSST_DATA) CALL read_pgd_seaflux_par_n(dtco, u, dts, sg, &
183  hprogram,ini,hdir='A')
184 !
185 !============================================================
186 !
187  CALL close_aux_io_surf(hinifile,hinifiletype)
188 !
189 !============================================================
190 !
192 IF (lhook) CALL dr_hook('ZOOM_PGD_SEAFLUX',1,zhook_handle)
193 !-------------------------------------------------------------------------------
194 !
195 END SUBROUTINE zoom_pgd_seaflux
subroutine get_surf_size_n(DTCO, U, HTYPE, KL)
subroutine pack_pgd(DTCO, U, HPROGRAM, HSURF, HGRID, PGRID_PAR, OCOVER, PCOVER, PZS, PLAT, PLON, PMESH_SIZE, PDIR)
Definition: pack_pgd.F90:6
subroutine zoom_pgd_seaflux(DTCO, DTS, SG, S, UG, U, HPROGRAM, HINIFILE, HINIFILETYPE, HFILE, HFILETYPE)
subroutine clean_prep_output_grid
subroutine close_aux_io_surf(HFILE, HFILETYPE)
subroutine hor_interpol(DTCO, U, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:6
subroutine open_aux_io_surf(HFILE, HFILETYPE, HMASK)
subroutine read_pgd_seaflux_par_n(DTCO, U, DTS, SG, HPROGRAM, KSIZE, HDIR)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine prep_grid_extern(HFILETYPE, KLUOUT, HGRIDTYPE, HINTERP_TYPE, KNI)
subroutine prep_output_grid(UG, U, KLUOUT, HGRID, PGRID_PAR, PLAT, PLON)