SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
prep_ocean_ascllv.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_ocean_ascllv (DTCO, UG, U, &
7  hprogram,hsurf,hfile, &
8  & kluout,pfield)
9 ! #################################################################################
10 !
11 !!**** *PREP_OCEAN_ASCLLDV* - prepares oceanic fields from personal data in ascii
12 !! formed as lat,lon, depth, value
13 !!
14 !! PURPOSE
15 !! -------
16 !
17 !!** METHOD
18 !! ------
19 !! Read the input file which must be ascii typed, lat,lon,depth, value
20 !! Version 1:
21 !! The data must be on the same grid as the pgd and on the same
22 !! vertical grid as prescribed in oceanvergrid.f90
23 !! NDEPTH= a definirtn nlev=NOCKMAX (modd_ocean_gridn)
24 !!
25 !! Version 2: (not done yet)
26 !! - dummy or namlist for nb verticals levels
27 !! - file prescribing the vertical grid
28 !!
29 !! REFERENCE
30 !! ---------
31 !!
32 !!
33 !! AUTHOR
34 !! ------
35 !! P. PEYRILLE
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !! Original 01/2011
40 !! J.Escobar 11/2013 Add USE MODI_ABOR1_SFX and USE MODI_GET_SURF_MASK_N
41 !!------------------------------------------------------------------
42 !
43 !
44 !
45 !
48 USE modd_surf_atm_n, ONLY : surf_atm_t
49 !
50 USE modd_prep, ONLY : cinterp_type, cingrid_type
51 USE modd_pgd_grid, ONLY : nl,llatlonmask,cgrid,xgrid_par,ngrid_par
52 USE modd_ocean_grid , ONLY : nockmax
53 USE modd_pgdwork, ONLY : xsumval, nsize
54 !
55 USE modi_open_file
56 USE modi_close_file
57 USE modi_get_luout
58 USE modi_get_latlonmask_n
60 USE modi_abor1_sfx
61 USE modi_get_surf_mask_n
62 !
63 USE modi_get_type_dim_n
64 USE yomhook ,ONLY : lhook, dr_hook
65 USE parkind1 ,ONLY : jprb
66 !
67 IMPLICIT NONE
68 !
69 !* 0.1 declarations of arguments
70 !
71 !
72 TYPE(data_cover_t), INTENT(INOUT) :: dtco
73 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
74 TYPE(surf_atm_t), INTENT(INOUT) :: u
75 !
76  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling surf. schemes
77  CHARACTER(LEN=7), INTENT(IN) :: hsurf ! type of field
78  CHARACTER(LEN=28), INTENT(IN) :: hfile ! file name
79 INTEGER, INTENT(IN) :: kluout ! output listing logical unit
80 !CHARACTER(LEN=28), INTENT(IN), OPTIONAL :: HNCVARNAME!var to read
81 REAL, POINTER, DIMENSION(:,:,:) :: pfield ! field to interpolate horizontally
82 !
83 !
84 !* 0.2 declarations of local variables
85 REAL,DIMENSION(:), ALLOCATABLE :: zlat
86 REAL,DIMENSION(:), ALLOCATABLE :: zlon
87 REAL,DIMENSION(:), ALLOCATABLE :: zdepth
88 REAL,DIMENSION(:,:,:), ALLOCATABLE :: zfield
89 REAL,DIMENSION(:,:,:,:), ALLOCATABLE :: zfieldr
90 !
91 INTEGER :: il
92 INTEGER :: iglb ! logical unit
93 INTEGER :: idim, ilu
94 INTEGER :: ji,jk
95 !
96 INTEGER, DIMENSION(:), POINTER :: imask ! mask for packing from complete field to nature field
97  CHARACTER(LEN=6) :: ymask
98 REAL(KIND=JPRB) :: zhook_handle
99 
100 !-------------------------------------------------------------------------------------
101 IF (lhook) CALL dr_hook('PREP_OCEAN_ASCLLV',0,zhook_handle)
102 !
103  cingrid_type='CONF PROJ '
104 
105 !* 1. get full dimension of grid
106  CALL get_type_dim_n(dtco, u, &
107  'FULL ',nl)
108 !* 2. get Ocean dimension
109 !
110  CALL get_type_dim_n(dtco, u, &
111  'SEA ',il)
112 
113 !* 3. get grid informations known over full grid
114 !
115  CALL get_latlonmask_n(ug, &
116  llatlonmask,cgrid,xgrid_par,ngrid_par)
117 !
118 !!
119 
120 WRITE(kluout,*) "==================================== "
121 WRITE(kluout,*) "Control print in prep_ocean_ascllv "
122 WRITE(kluout,*) "NL, NOCKMAX", nl,nockmax
123 
124 ALLOCATE(zlat(nl))
125 ALLOCATE(zlon(nl))
126 ALLOCATE(zdepth(nockmax))
127 
128 ALLOCATE(zfieldr(nl,nockmax,4, 1))
129 ALLOCATE(zfield(nl,nockmax, 1))
130 
131 
132 WRITE(kluout,*) "ZFIELDR",shape(zfieldr)
133 WRITE(kluout,*) "File name used in ocean ascllv", hfile
134 
135 WRITE(kluout,*) "USURF= " , hsurf
136 WRITE(kluout,*) "NL (dim)=", nl
137 WRITE(kluout,*) "IL (dim)=", il
138 !
139 !* 2. Reading of field
140 ! ----------------
141  CALL open_file(hprogram,iglb,hfile,'FORMATTED',haction='READ')
142 !
143 
144 DO ji=1,nl
145  DO jk=1,nockmax
146  READ(iglb,*,end=99) zlat(ji),zlon(ji), zdepth(jk), &
147  zfieldr(ji,jk,1,1), zfieldr(ji,jk,2,1),zfieldr(ji,jk,3,1), &
148  zfieldr(ji,jk,4,1)
149  END DO
150 END DO
151 
152 
153 
154 ! 3. Close the file
155 
156 99 CONTINUE
157  CALL close_file(hprogram,iglb)
158 
159 WRITE(kluout,*) minval(zfieldr), maxval(zfieldr)
160 
161 !
162 ! Get the correct varaibles
163 SELECT CASE (hsurf)
164  CASE('TEMP_OC')
165  zfield(:,:,1) = zfieldr(:,:,1,1)
166  CASE('SALT_OC')
167  zfield(:,:,1) = zfieldr(:,:,2,1)
168  CASE('UCUR_OC')
169  zfield(:,:,1) = zfieldr(:,:,3,1)
170  CASE('VCUR_OC')
171  zfield(:,:,1) = zfieldr(:,:,4,1)
172 END SELECT
173 
174 
175 
176 !* 3. Interpolation method
177 ! --------------------
178 !
179  cinterp_type='NONE '
180 !CINTERP_TYPE='HORIBL'
181 !
182 
183 ymask = 'SEA '
184  CALL get_type_dim_n(dtco, u, &
185  ymask,idim)
186 WRITE(kluout,*) "IDIM (dim sea) =", idim
187 
188 ALLOCATE(pfield(1:idim,1:SIZE(zfield,2),1:SIZE(zfield,3)))
189 
190 IF (idim/=SIZE(pfield,1)) THEN
191  WRITE(kluout,*)'Wrong dimension of MASK: ',idim,SIZE(pfield)
192  CALL abor1_sfx('PGD_FIELD: WRONG DIMENSION OF MASK')
193 ENDIF
194 
195 ALLOCATE(imask(idim))
196 ilu=0
197  CALL get_surf_mask_n(dtco, u, &
198  ymask,idim,imask,ilu,kluout)
199 DO jk=1,nockmax
200  CALL pack_same_rank(imask,zfield(:,jk,1),pfield(:,jk,1))
201 END DO
202 DEALLOCATE(imask)
203 
204 !* 4. Deallocations
205 ! -------------
206 !
207 IF (ALLOCATED(zlon )) DEALLOCATE(zlon )
208 IF (ALLOCATED(zlat )) DEALLOCATE(zlat )
209 IF (ALLOCATED(zdepth )) DEALLOCATE(zdepth )
210 IF (ALLOCATED(zfield )) DEALLOCATE(zfield )
211 IF (ALLOCATED(zfieldr )) DEALLOCATE(zfieldr )
212 !
213 IF (lhook) CALL dr_hook('PREP_OCEAN_ASCLLV',1,zhook_handle)
214 !
215 !-------------------------------------------------------------------------------------
216 END SUBROUTINE prep_ocean_ascllv
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine prep_ocean_ascllv(DTCO, UG, U, HPROGRAM, HSURF, HFILE, KLUOUT, PFIELD)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine get_latlonmask_n(UG, OLATLONMASK, HGRID, PGRID_PAR, KGRID_PAR)
subroutine get_surf_mask_n(DTCO, U, HTYPE, KDIM, KMASK, KLU, KLUOUT)
subroutine close_file(HPROGRAM, KUNIT)
Definition: close_file.F90:6
subroutine open_file(HPROGRAM, KUNIT, HFILE, HFORM, HACTION, HACCESS, KRECL)
Definition: open_file.F90:6