SURFEX v8.1
General documentation of Surfex
prep_ocean_netcdf.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_netcdf(HPROGRAM,HSURF,HFILE,HFILETYPE,&
7  KLUOUT,HNCVARNAME,PFIELD)
8 ! #################################################################################
9 !
10 !!**** *PREP_OCEAN_NETCDF* - prepares oceanic fields from Mercator analysis
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! C. Lebeaupin Brossier
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2008
29 !!------------------------------------------------------------------
30 !
33 !
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 !
42 !* 0.1 declarations of arguments
43 !
44  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
45  CHARACTER(LEN=7), INTENT(IN) :: HSURF ! type of field
46  CHARACTER(LEN=28), INTENT(IN) :: HFILE ! file name
47  CHARACTER(LEN=6), INTENT(IN) :: HFILETYPE ! file type
48 INTEGER, INTENT(IN) :: KLUOUT ! output listing logical unit
49  CHARACTER(LEN=28), INTENT(IN), OPTIONAL :: HNCVARNAME!var to read
50 REAL, POINTER, DIMENSION(:,:,:) :: PFIELD ! field to interpolate horizontally
51 !
52 !* 0.2 declarations of local variables
53 REAL,DIMENSION(:), ALLOCATABLE :: ZLATI
54 REAL,DIMENSION(:), ALLOCATABLE :: ZLONG
55 REAL,DIMENSION(:), ALLOCATABLE :: ZDEPTH
56 REAL,DIMENSION(:,:,:), ALLOCATABLE :: ZFIELD
57 REAL(KIND=JPRB) :: ZHOOK_HANDLE
58 !
59 !
60 !-------------------------------------------------------------------------------------
61 !* 1. Grid type
62 ! ---------
63 IF (lhook) CALL dr_hook('PREP_OCEAN_NETCDF',0,zhook_handle)
64 cingrid_type='LATLON'
65 !
66 !
67 IF (.NOT. ALLOCATED(xilonarray)) CALL prep_netcdf_grid(hfile,hncvarname)
68 !
69 ALLOCATE(zlati(nilength) )
70 ALLOCATE(zlong(nilength) )
71 ALLOCATE(zdepth(nindepth))
72 !
73 ALLOCATE(zfield(nilength,nindepth,1))
74 !
75 !* 2. Reading of field
76 ! ----------------
77  CALL read_latlondepval_cdf(hfile,hncvarname,zlong,zlati,zdepth,zfield(:,:,1))
78 ALLOCATE(pfield(1:SIZE(zfield,1),1:SIZE(zfield,2),1:SIZE(zfield,3)))
79 pfield=zfield
80 !
81 !* 3. Interpolation method
82 ! --------------------
83 !
84 cinterp_type='HORIBL'
85 !
86 !* 4. Deallocations
87 ! -------------
88 !
89 IF (ALLOCATED(zlong )) DEALLOCATE(zlong )
90 IF (ALLOCATED(zlati )) DEALLOCATE(zlati )
91 IF (ALLOCATED(zdepth )) DEALLOCATE(zdepth )
92 IF (ALLOCATED(zfield )) DEALLOCATE(zfield )
93 IF (lhook) CALL dr_hook('PREP_OCEAN_NETCDF',1,zhook_handle)
94 !
95 !-------------------------------------------------------------------------------------
96 END SUBROUTINE prep_ocean_netcdf
character(len=10) cingrid_type
Definition: modd_prep.F90:39
subroutine prep_ocean_netcdf(HPROGRAM, HSURF, HFILE, HFILETYPE, KLUOUT, HNCVARNAME, PFIELD)
subroutine read_latlondepval_cdf(HFILENAME, HNCVARNAME, PLON, PLAT, PDEP, PVAL)
subroutine prep_netcdf_grid(HFILENAME, HNCVARNAME)
character(len=6) cinterp_type
Definition: modd_prep.F90:40
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:), allocatable xilonarray
logical lhook
Definition: yomhook.F90:15