SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_binllvfast.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_binllvfast (USS, &
7  hprogram,hsubroutine,hfilename)
8 ! ##############################################################
9 !
10 !!**** *READ_BINLLVFAST* reads a binary latlonvalue file and call treatment
11 !! subroutine : optimized version of READ_BINLLV routine.
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !! AUTHOR
21 !! ------
22 !!
23 !! D. Gazen L.A.
24 !!
25 !! MODIFICATION
26 !! ------------
27 !!
28 !! Original 29/11/2002
29 !! 03/2004 externalization (V. Masson)
30 !!
31 !----------------------------------------------------------------------------
32 !
33 !* 0. DECLARATION
34 ! -----------
35 !
36 !
37 !
39 !
40 USE modd_surf_par, ONLY : xundef
41 USE modd_pgd_grid, ONLY : llatlonmask
42 !
43 USE modi_open_file
44 USE modi_close_file
45 USE modi_pt_by_pt_treatment
46 USE modi_get_luout
47 !
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54 !* 0.1 Declaration of arguments
55 ! ------------------------
56 !
57 !
58 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
59 !
60  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
61  CHARACTER(LEN=6), INTENT(IN) :: hsubroutine ! Name of the subroutine to call
62  CHARACTER(LEN=28), INTENT(IN) :: hfilename ! Name of the field file.
63 !
64 !
65 !* 0.2 Declaration of local variables
66 ! ------------------------------
67 !
68 INTEGER :: iglb ! logical units
69 INTEGER :: jlat, jlon ! indexes of LLATLONMASK array
70 INTEGER :: inelt ! number of data points in file
71 INTEGER :: icpt ! number of data points to be computed
72 REAL,DIMENSION(:,:),ALLOCATABLE,TARGET :: zllv ! ZLLV(1,:) :: latitude of data points
73  ! ZLLV(2,:) :: longitude of data points
74  ! ZLLV(3,:) :: value of data points
75 REAL,DIMENSION(:,:),POINTER :: zllvwork ! point on ZLLV array
76 INTEGER :: ji ! loop counter
77 !
78 INTEGER :: iluout ! output listing
79 REAL(KIND=JPRB) :: zhook_handle
80 !----------------------------------------------------------------------------
81 !
82 !
83 !* 1. Open the global file
84 ! --------------------
85 !
86 IF (lhook) CALL dr_hook('READ_BINLLVFAST',0,zhook_handle)
87  CALL open_file(hprogram,iglb,hfilename,'UNFORMATTED',haction='READ')
88 !
89  CALL get_luout(hprogram,iluout)
90 !
91 !----------------------------------------------------------------------------
92 !
93 !* 3. Reading of a data point
94 ! -----------------------
95 !
96 READ(iglb) inelt ! number of data points
97 ALLOCATE(zllv(3,inelt))
98 READ(iglb) zllv
99 !
100 !----------------------------------------------------------------------------
101 !
102 !* 4. Test if point is in the domain
103 ! ------------------------------
104 !
105 zllv(2,:) = zllv(2,:)+nint((180.-zllv(2,:))/360.)*360.
106 !
107 icpt = 0
108 DO ji=1,inelt
109  jlat = 1 + int( ( zllv(1,ji)+ 90. ) * 2. )
110  jlat = min(jlat,360)
111  jlon = 1 + int( ( zllv(2,ji) ) * 2. )
112  jlon = min(jlon,720)
113  IF (llatlonmask(jlon,jlat)) THEN
114  icpt = icpt+1
115  zllv(:,icpt) = zllv(:,ji)
116  END IF
117 END DO
118 !
119 !-------------------------------------------------------------------------------
120 !
121 !* 5. Call to the adequate subroutine (point by point treatment)
122 ! ----------------------------------------------------------
123 !
124 IF (icpt > 0) THEN
125  zllvwork=>zllv(:,1:icpt)
126  CALL pt_by_pt_treatment(uss, &
127  iluout,zllvwork(1,:),zllvwork(2,:),zllvwork(3,:),hsubroutine)
128 END IF
129 !
130 !----------------------------------------------------------------------------
131 !
132 !* 6. Closing of the data file
133 ! ------------------------
134 !
135  CALL close_file(hprogram,iglb)
136 !
137 !-------------------------------------------------------------------------------
138 !
139 DEALLOCATE(zllv)
140 IF (lhook) CALL dr_hook('READ_BINLLVFAST',1,zhook_handle)
141 !
142 !-------------------------------------------------------------------------------
143 !
144 END SUBROUTINE read_binllvfast
subroutine pt_by_pt_treatment(USS, KLUOUT, PLAT, PLON, PVALUE, HSUBROUTINE, KNBLINES, PNODATA)
subroutine read_binllvfast(USS, HPROGRAM, HSUBROUTINE, HFILENAME)
subroutine close_file(HPROGRAM, KUNIT)
Definition: close_file.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine open_file(HPROGRAM, KUNIT, HFILE, HFORM, HACTION, HACCESS, KRECL)
Definition: open_file.F90:6