SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_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_netcdf (USS, &
7  hprogram,hsubroutine,hfilename,hncvarname)
8 ! ##############################################################
9 !
10 !!**** *READ_NETCDF* reads a netcdf file and copy lat/lon/val then call treatment
11 !! subroutine
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !! AUTHOR
17 !! ------
18 !!
19 !! C. Lebeaupin Brossier Meteo-France
20 !!
21 !! MODIFICATION
22 !! ------------
23 !!
24 !! Original 01/2008
25 !!
26 !----------------------------------------------------------------------------
27 !
28 !* 0. DECLARATION
29 ! -----------
30 !
31 !
32 !
34 !
35 USE modd_pgd_grid, ONLY : llatlonmask
36 !
37 USE modi_pt_by_pt_treatment
38 USE mode_read_cdf
39 !
40 !
41 USE yomhook ,ONLY : lhook, dr_hook
42 USE parkind1 ,ONLY : jprb
43 !
44 USE modi_get_luout
45 IMPLICIT NONE
46 !
47 !* 0.1 Declaration of arguments
48 ! ------------------------
49 !
50 !
51 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
52 !
53  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
54  CHARACTER(LEN=6), INTENT(IN) :: hsubroutine ! Name of the subroutine to call
55  CHARACTER(LEN=28), INTENT(IN) :: hfilename ! Name of the field file.
56  CHARACTER(LEN=28), INTENT(IN) :: hncvarname ! Name of the variable in netcdf file
57 !
58 !
59 !* 0.2 Declaration of local variables
60 ! ------------------------------
61 !
62 INTEGER :: jlat, jlon ! indexes of OLATLONMASK array
63 REAL :: zvalue ! values of a data point
64 REAL :: zlat ! latitude of data point
65 REAL :: zlon ! longitude of data point
66 !
67 REAL, DIMENSION(:),ALLOCATABLE :: zvalu ! array of values extract from netcdf file
68 REAL, DIMENSION(:),ALLOCATABLE :: zlong ! array of values extract from netcdf file
69 REAL, DIMENSION(:),ALLOCATABLE :: zlati ! array of values extract from netcdf file
70 !
71 INTEGER :: iluout ! output listing
72 INTEGER :: jloop ! loop indice
73 INTEGER :: jdimension ! dimensions of ZVALU,ZLAT,
74 REAL(KIND=JPRB) :: zhook_handle
75  ! and ZLON arrays
76 !----------------------------------------------------------------------------
77 !
78 IF (lhook) CALL dr_hook('READ_NETCDF',0,zhook_handle)
79  CALL get_luout(hprogram,iluout)
80 !
81 !
82 !* 1. Read the netcdf file and lat/lon/val arrays dimensions
83 ! ------------------------------------------------------
84  CALL read_dim_cdf(hfilename,hncvarname,jdimension)
85 ALLOCATE(zvalu(jdimension))
86 ALLOCATE(zlati(jdimension))
87 ALLOCATE(zlong(jdimension))
88 
89 !* 1. Read the netcdf file and extract lat/lon/val
90 ! --------------------------------------------
91  CALL read_latlonval_cdf(hfilename,hncvarname,zlong(:),zlati(:),zvalu(:))
92 !
93 !----------------------------------------------------------------------------
94 !
95 !* 4. Test if point is in the domain
96 ! ------------------------------
97 !
98 DO jloop=1,SIZE(zvalu)
99 !
100  zlon = zlong(jloop)
101  zlat = zlati(jloop)
102  zvalue= zvalu(jloop)
103 !
104  zlon=zlon+nint((180.-zlon)/360.)*360.
105  !
106  jlat = 1 + int( ( zlat + 90. ) * 2. )
107  jlat = min(jlat,360)
108  jlon = 1 + int( ( zlon ) * 2. )
109  jlon = min(jlon,720)
110  !
111  IF (.NOT. llatlonmask(jlon,jlat)) cycle
112 !
113 !-------------------------------------------------------------------------------
114 !
115 !* 5. Call to the adequate subroutine (point by point treatment)
116 ! ----------------------------------------------------------
117 !
118  CALL pt_by_pt_treatment(uss, &
119  iluout, (/ zlat /) , (/ zlon /) , (/ zvalue /) , &
120  hsubroutine )
121 !
122 !-------------------------------------------------------------------------------
123 ENDDO
124 IF (ALLOCATED(zvalu )) DEALLOCATE(zvalu )
125 IF (ALLOCATED(zlong )) DEALLOCATE(zlong )
126 IF (ALLOCATED(zlati )) DEALLOCATE(zlati )
127 IF (lhook) CALL dr_hook('READ_NETCDF',1,zhook_handle)
128 !
129 !----------------------------------------------------------------------------
130 !
131 !-------------------------------------------------------------------------------
132 !
133 END SUBROUTINE read_netcdf
subroutine read_netcdf(USS, HPROGRAM, HSUBROUTINE, HFILENAME, HNCVARNAME)
Definition: read_netcdf.F90:6
subroutine pt_by_pt_treatment(USS, KLUOUT, PLAT, PLON, PVALUE, HSUBROUTINE, KNBLINES, PNODATA)
subroutine read_dim_cdf(HFILENAME, HNCVARNAME, KDIM)
subroutine read_latlonval_cdf(HFILENAME, HNCVARNAME, PLON, PLAT, PVAL)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6