SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
mode_gridtype_lonlatval.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 ! ##############################
7 ! ##############################
8 !
9 !############################################################################
10 !############################################################################
11 !############################################################################
12 !
13 USE yomhook ,ONLY : lhook, dr_hook
14 USE parkind1 ,ONLY : jprb
15 !
16  CONTAINS
17 !############################################################################
18 !############################################################################
19 !############################################################################
20 ! ####################################################################
21  SUBROUTINE put_gridtype_lonlatval(PGRID_PAR,PX,PY,PDX,PDY)
22 ! ####################################################################
23 !
24 !!**** *PUT_GRIDTYPE_LONLATVAL* - routine to store in PGRID_PAR the horizontal grid
25 !!
26 !! AUTHOR
27 !! ------
28 !! S.Faroux *Meteo France*
29 !!
30 !! MODIFICATIONS
31 !! -------------
32 !! Original 02/2010
33 !-------------------------------------------------------------------------------
34 !
35 !* 0. DECLARATIONS
36 ! ------------
37 !
38 IMPLICIT NONE
39 !
40 !
41 !* 0.1 Declarations of arguments
42 ! -------------------------
43 !
44 REAL, DIMENSION(:), INTENT(IN) :: px ! X coordinate of grid mesh center
45 REAL, DIMENSION(:), INTENT(IN) :: py ! Y coordinate of grid mesh center
46 REAL, DIMENSION(:), INTENT(IN) :: pdx ! X grid mesh size
47 REAL, DIMENSION(:), INTENT(IN) :: pdy ! Y grid mesh size
48 REAL, DIMENSION(:), POINTER :: pgrid_par! parameters defining this grid
49 !
50 !
51 !* 0.2 Declarations of local variables
52 ! -------------------------------
53 !
54 INTEGER :: il ! number of points
55 REAL(KIND=JPRB) :: zhook_handle
56 !-------------------------------------------------------------------------------
57 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_LONLATVAL:PUT_GRIDTYPE_LONLATVAL',0,zhook_handle)
58 il = SIZE(px)
59 ALLOCATE(pgrid_par(1+4*il))
60 
61 pgrid_par(1) = float(il)
62 pgrid_par(2:il+1) = px(:)
63 pgrid_par(il+2:2*il+1) = py(:)
64 pgrid_par(2*il+2:3*il+1) = pdx(:)
65 pgrid_par(3*il+2:4*il+1) = pdy(:)
66 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_LONLATVAL:PUT_GRIDTYPE_LONLATVAL',1,zhook_handle)
67 !
68 !-------------------------------------------------------------------------------
69 END SUBROUTINE put_gridtype_lonlatval
70 !############################################################################
71 !############################################################################
72 !############################################################################
73 ! ####################################################################
74  SUBROUTINE get_gridtype_lonlatval(PGRID_PAR,KL,PX,PY,PDX,PDY)
75 ! ####################################################################
76 !
77 !!**** *GET_GRIDTYPE_LONLATVAL* - routine to get from PGRID_PAR the horizontal grid
78 !!
79 !! AUTHOR
80 !! ------
81 !! S. Faroux *Meteo France*
82 !!
83 !! MODIFICATIONS
84 !! -------------
85 !! Original 02/2010
86 !-------------------------------------------------------------------------------
87 !
88 !* 0. DECLARATIONS
89 ! ------------
90 !
91 IMPLICIT NONE
92 !
93 !
94 !* 0.1 Declarations of arguments
95 ! -------------------------
96 !
97 INTEGER, INTENT(OUT), OPTIONAL :: kl ! number of points
98 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: px ! X coordinate of grid mesh center
99 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: py ! Y coordinate of grid mesh center
100 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: pdx ! X grid mesh size
101 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: pdy ! Y grid mesh size
102 REAL, DIMENSION(:), INTENT(IN) :: pgrid_par! parameters defining this grid
103 !
104 !
105 !* 0.2 Declarations of local variables
106 ! -------------------------------
107 !
108 INTEGER :: il
109 REAL(KIND=JPRB) :: zhook_handle
110 !-------------------------------------------------------------------------------
111 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_LONLATVAL:GET_GRIDTYPE_LONLATVAL',0,zhook_handle)
112 IF (present(kl)) kl = nint(pgrid_par(1))
113 !
114 IF (present(px)) THEN
115  il = nint(pgrid_par(1))
116  px(:) = pgrid_par(2:1+il)
117 END IF
118 
119 IF (present(py)) THEN
120  il = nint(pgrid_par(1))
121  py(:) = pgrid_par(1+il+1:1+2*il)
122 END IF
123 
124 IF (present(pdx)) THEN
125  il = nint(pgrid_par(1))
126  pdx(:)= pgrid_par(1+2*il+1:1+3*il)
127 END IF
128 
129 IF (present(pdy)) THEN
130  il = nint(pgrid_par(1))
131  pdy(:)= pgrid_par(1+3*il+1:1+4*il)
132 END IF
133 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_LONLATVAL:GET_GRIDTYPE_LONLATVAL',1,zhook_handle)
134 !
135 !-------------------------------------------------------------------------------
136 END SUBROUTINE get_gridtype_lonlatval
137 !############################################################################
138 !############################################################################
139 !############################################################################
140 ! ###################################################
141  SUBROUTINE latlon_lonlatval(PX,PY,PLAT,PLON)
142 ! ###################################################
143 !
144 !!**** *LATLON_LONLATVAL * - Routine to compute geographical coordinates
145 !!
146 !! PURPOSE
147 !! -------
148 ! This routine computes the latitude and longitude of
149 ! an array given in LAMBERT coordinates
150 !
151 !
152 !!** METHOD
153 !! ------
154 !!
155 !! EXTERNAL
156 !! --------
157 !! None
158 !!
159 !! REFERENCE
160 !! ---------
161 !!
162 !! AUTHOR
163 !! ------
164 !! S.Faroux *Meteo-France*
165 !!
166 !! MODIFICATION
167 !! ------------
168 !! Original 02/2010
169 !-------------------------------------------------------------------------------
170 !
171 !* 0. DECLARATIONS
172 ! ------------
173 !
174 IMPLICIT NONE
175 !
176 !* 0.1 Declarations of arguments and results
177 !
178 REAL, DIMENSION(:), INTENT(IN) :: px,py
179  ! given conformal coordinates of the
180  ! processed points (meters);
181 REAL, DIMENSION(:), INTENT(OUT):: plat,plon
182 REAL(KIND=JPRB) :: zhook_handle
183  ! returned geographic latitudes and
184  ! longitudes of the processed points
185  ! (degrees).
186 !
187 !
188  IF (lhook) CALL dr_hook('MODE_GRIDTYPE_LONLATVAL:LATLON_LONLATVAL',0,zhook_handle)
189  plon(:)=px(:)
190 !
191  plat(:)=py(:)
192 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_LONLATVAL:LATLON_LONLATVAL',1,zhook_handle)
193 !
194 !---------------------------------------------------------------------------------
195 END SUBROUTINE latlon_lonlatval
196 !---------------------------------------------------------------------------------
197 !
198 END MODULE mode_gridtype_lonlatval
subroutine put_gridtype_lonlatval(PGRID_PAR, PX, PY, PDX, PDY)
subroutine get_gridtype_lonlatval(PGRID_PAR, KL, PX, PY, PDX, PDY)
subroutine latlon_lonlatval(PX, PY, PLAT, PLON)