SURFEX v8.1
General documentation of Surfex
read_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 read_ascllv (UG, U, USS, &
7  HPROGRAM,HSUBROUTINE,HFILENAME)
8 ! ##############################################################
9 !
10 !!**** *READ_ASCLLV* reads a binary latlonvalue file and call treatment
11 !! subroutine
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !! AUTHOR
17 !! ------
18 !!
19 !! V. Masson Meteo-France
20 !!
21 !! MODIFICATION
22 !! ------------
23 !!
24 !! Original 12/09/95
25 !! 03/2004 externalization (V. Masson)
26 !!
27 !----------------------------------------------------------------------------
28 !
29 !* 0. DECLARATION
30 ! -----------
31 !
32 !
34 USE modd_surf_atm_n, ONLY : surf_atm_t
35 USE modd_sso_n, ONLY : sso_t
36 !
37 USE modd_pgd_grid, ONLY : llatlonmask
38 !
39 USE modi_open_file
40 USE modi_close_file
41 USE modi_pt_by_pt_treatment
42 USE modi_get_luout
43 !
44 !
45 USE yomhook ,ONLY : lhook, dr_hook
46 USE parkind1 ,ONLY : jprb
47 !
48 IMPLICIT NONE
49 !
50 !* 0.1 Declaration of arguments
51 ! ------------------------
52 !
53 !
54 TYPE(surf_atm_grid_t), INTENT(INOUT) :: UG
55 TYPE(surf_atm_t), INTENT(INOUT) :: U
56 TYPE(sso_t), INTENT(INOUT) :: USS
57 !
58  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! Type of program
59  CHARACTER(LEN=6), INTENT(IN) :: HSUBROUTINE ! Name of the subroutine to call
60  CHARACTER(LEN=28), INTENT(IN) :: HFILENAME ! Name of the field file.
61 !
62 !
63 !* 0.2 Declaration of local variables
64 ! ------------------------------
65 !
66 INTEGER :: IGLB ! logical unit
67 !
68 INTEGER :: JLAT, JLON ! indexes of OLATLONMASK array
69 !
70 INTEGER*4, PARAMETER :: ILONG=200000
71 !
72 REAL :: ZVALUER
73 REAL, DIMENSION(ILONG) :: ZVALUE ! values of a data point
74 REAL :: ZLATR
75 REAL, DIMENSION(ILONG) :: ZLAT ! latitude of data point
76 REAL :: ZLONR, ZLONR2
77 REAL, DIMENSION(ILONG) :: ZLON ! longitude of data point
78 !
79 INTEGER :: ICPT, ISTAT
80 INTEGER :: ILUOUT ! output listing
81 REAL(KIND=JPRB) :: ZHOOK_HANDLE
82 !----------------------------------------------------------------------------
83 !
84 !* 1. Open the file
85 ! -------------
86 !
87 IF (lhook) CALL dr_hook('READ_ASCLLV',0,zhook_handle)
88  CALL open_file('ASCII ',iglb,hfilename,'FORMATTED',haction='READ')
89 !
90  CALL get_luout(hprogram,iluout)
91 !
92 icpt = 0
93 !
94 zlat(:) = 0
95 zlon(:) = 0
96 zvalue(:) = 0
97 !
98 !----------------------------------------------------------------------------
99 DO
100 !----------------------------------------------------------------------------
101 !
102 !* 3. Reading of a data point
103 ! -----------------------
104 !
105  READ(iglb,*,iostat=istat) zlatr,zlonr,zvaluer
106 !
107 !----------------------------------------------------------------------------
108 !
109 !* 4. Test if point is in MESO-NH domain
110 ! ----------------------------------
111 !
112  IF (istat==0) THEN
113  !
114  zlonr2=zlonr+nint((180.-zlonr)/360.)*360.
115  !
116  jlat = 1 + int( ( zlatr + 90. ) * 2. )
117  jlat = min(jlat,360)
118  jlon = 1 + int( ( zlonr2 ) * 2. )
119  jlon = min(jlon,720)
120  !
121  IF (.NOT. llatlonmask(jlon,jlat)) cycle
122  !
123  icpt = icpt + 1
124  !
125  IF (icpt<=ilong) THEN
126  !
127  zlat(icpt) = zlatr
128  zlon(icpt) = zlonr
129  zvalue(icpt) = zvaluer
130  !
131  ENDIF
132  !
133  ENDIF
134  !
135  IF (istat==-1 .OR. icpt==ilong) THEN
136  !
137  !-------------------------------------------------------------------------------
138  !
139  !* 5. Call to the adequate subroutine (point by point treatment)
140  ! ----------------------------------------------------------
141  !
142  CALL pt_by_pt_treatment(ug, u, uss, iluout, &
143  zlat(1:icpt), zlon(1:icpt), zvalue(1:icpt), hsubroutine )
144  !
145  icpt = 0
146  zlat(:) = 0.
147  zlon(:) = 0.
148  zvalue(:) = 0.
149  !
150  ENDIF
151  !
152  IF (istat==-1) EXIT
153  !
154  !-------------------------------------------------------------------------------
155 ENDDO
156 !
157 !----------------------------------------------------------------------------
158 !
159 !* 8. Closing of the data file
160 ! ------------------------
161 !
162 99 CONTINUE
163  CALL close_file ('ASCII ',iglb)
164 IF (lhook) CALL dr_hook('READ_ASCLLV',1,zhook_handle)
165 !
166 !-------------------------------------------------------------------------------
167 !
168 END SUBROUTINE read_ascllv
subroutine open_file(HPROGRAM, KUNIT, HFILE, HFORM, HACTION, HACCESS, KR
Definition: open_file.F90:7
logical, dimension(720, 360) llatlonmask
integer, parameter jprb
Definition: parkind1.F90:32
subroutine close_file(HPROGRAM, KUNIT)
Definition: close_file.F90:7
subroutine read_ascllv(UG, U, USS, HPROGRAM, HSUBROUTINE, HFILENAME)
Definition: read_ascllv.F90:8
subroutine pt_by_pt_treatment(UG, U, USS, KLUOUT, PLAT, PLON, PVALUE, HSUBROUTINE
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15