SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_z1d_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 read_z1d_netcdf
7 ! ##############################################################
8 !
9 !!**** *READ_Z1D_NETCDF* reads the vertical grid in a netcdf file
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! AUTHOR
15 !! ------
16 !!
17 !! C. Lebeaupin Brossier Meteo-France
18 !!
19 !! MODIFICATION
20 !! ------------
21 !!
22 !! Original 11/2014
23 !! initialisation of NOCKMAX,XZHOC
24 !!
25 !----------------------------------------------------------------------------
26 !
27 !* 0. DECLARATION
28 ! -----------
29 !
31 USE modd_surf_par, ONLY : nundef
32 USE modd_prep_seaflux, ONLY : cfile_seaflx,ctype_seaflx
34 !
35 !
36 USE yomhook ,ONLY : lhook, dr_hook
37 !
38 IMPLICIT NONE
39 !
40 !* 0.1 Declaration of arguments
41 ! ------------------------
42 !
43  CHARACTER (LEN=28) :: yfilename
44  CHARACTER (LEN=28) :: yncvarname
45 INTEGER :: jdimension
46 !
47 !* 0.2 Declaration of local variables
48 ! ------------------------------
49 !
50 REAL(KIND=JPRB) :: zhook_handle
51  ! and ZLON arrays
52 !----------------------------------------------------------------------------
53 !
54 IF (lhook) CALL dr_hook('READ_Z1D_NETCDF',0,zhook_handle)
55 !
56 nockmax=-nundef
57 !
58 !* 1. Read the netcdf arrays dimensions
59 ! ---------------------------------
60 IF (ctype_seaflx=="NETCDF") THEN
61  yfilename=trim(cfile_seaflx)
62  yncvarname="depth"
63  CALL read_dim_cdf(yfilename,yncvarname,jdimension)
64  nockmax=jdimension
65  ALLOCATE(xzhoc(0:jdimension))
66  xzhoc(0)=0.
67 !
68 !* 2. Read the array in the netcdf file
69 ! ---------------------------------
70  CALL read_z1d_cdf(yfilename,yncvarname,xzhoc(1:jdimension))
71  IF (xzhoc(2)>0) xzhoc(:)=-xzhoc(:)
72 ! WRITE(0,*) 'Oceanic vertical grid readed in netcdf file'
73 ! WRITE(0,*) 'Number of level',NOCKMAX+1
74 ! WRITE(0,*) 'Depth of vertical level',XZHOC(:)
75 !
76 !----------------------------------------------------------------------------
77 ELSE
78  WRITE(*,*) 'ERROR IN READ_Z1D_NETCF: ', yfilename, ' HAS NOT A NETCDF TYPE'
79  WRITE(*,*) 'CHECK CTYPE_SEAFLX IN NAM_PREP_SEAFLUX'
80 ENDIF
81 !
82 !-------------------------------------------------------------------------------
83 IF (lhook) CALL dr_hook('READ_Z1D_NETCDF',1,zhook_handle)
84 !
85 !-------------------------------------------------------------------------------
86 !
87 END SUBROUTINE read_z1d_netcdf
subroutine read_z1d_netcdf
subroutine read_dim_cdf(HFILENAME, HNCVARNAME, KDIM)
subroutine read_z1d_cdf(HFILENAME, HNCVARNAME, PVAL)