SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
mode_gridtype_cartesian.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_cartesian(PGRID_PAR,PLAT0,PLON0, &
22  kimax,kjmax,px,py,pdx,pdy )
23 ! ####################################################################
24 !
25 !!**** *PUT_GRIDTYPE_CARTESIAN* - routine to store in PGRID_PAR the horizontal grid
26 !!
27 !! AUTHOR
28 !! ------
29 !! V. Masson *Meteo France*
30 !!
31 !! MODIFICATIONS
32 !! -------------
33 !! Original 01/2004
34 !-------------------------------------------------------------------------------
35 !
36 !* 0. DECLARATIONS
37 ! ------------
38 !
39 IMPLICIT NONE
40 !
41 !
42 !* 0.1 Declarations of arguments
43 ! -------------------------
44 !
45 REAL, INTENT(IN) :: plat0 ! reference latitude
46 REAL, INTENT(IN) :: plon0 ! reference longitude
47 INTEGER, INTENT(IN) :: kimax ! number of points in I direction
48 INTEGER, INTENT(IN) :: kjmax ! number of points in J direction
49 REAL, DIMENSION(:), INTENT(IN) :: px ! X conformal coordinate of left boundary of grid mesh
50 REAL, DIMENSION(:), INTENT(IN) :: py ! Y conformal coordinate of bottom boundary of grid mesh
51 REAL, DIMENSION(:), INTENT(IN) :: pdx ! X grid mesh size
52 REAL, DIMENSION(:), INTENT(IN) :: pdy ! Y grid mesh size
53 REAL, DIMENSION(:), POINTER :: pgrid_par! parameters defining this grid
54 !
55 !
56 !* 0.2 Declarations of local variables
57 ! -------------------------------
58 !
59 INTEGER :: il ! number of points
60 REAL(KIND=JPRB) :: zhook_handle
61 !-------------------------------------------------------------------------------
62 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_CARTESIAN:PUT_GRIDTYPE_CARTESIAN',0,zhook_handle)
63 il = SIZE(px)
64 ALLOCATE(pgrid_par(4+4*il))
65 pgrid_par(1) = plat0
66 pgrid_par(2) = plon0
67 pgrid_par(3) = float(kimax)
68 pgrid_par(4) = float(kjmax)
69 pgrid_par(4 +1:4+ il) = px(:)
70 pgrid_par(4+ il+1:4+2*il) = py(:)
71 pgrid_par(4+2*il+1:4+3*il) = pdx(:)
72 pgrid_par(4+3*il+1:4+4*il) = pdy(:)
73 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_CARTESIAN:PUT_GRIDTYPE_CARTESIAN',1,zhook_handle)
74 !-------------------------------------------------------------------------------
75 END SUBROUTINE put_gridtype_cartesian
76 !############################################################################
77 !############################################################################
78 !############################################################################
79 ! ####################################################################
80  SUBROUTINE get_gridtype_cartesian(PGRID_PAR,PLAT0,PLON0, &
81  kimax,kjmax,px,py,pdx,pdy,kl )
82 ! ####################################################################
83 !
84 !!**** *GET_GRIDTYPE_CARTESIAN* - routine to get from PGRID_PAR the horizontal grid
85 !!
86 !! AUTHOR
87 !! ------
88 !! V. Masson *Meteo France*
89 !!
90 !! MODIFICATIONS
91 !! -------------
92 !! Original 01/2004
93 !-------------------------------------------------------------------------------
94 !
95 !* 0. DECLARATIONS
96 ! ------------
97 !
98 IMPLICIT NONE
99 !
100 !
101 !* 0.1 Declarations of arguments
102 ! -------------------------
103 !
104 REAL, DIMENSION(:), INTENT(IN) :: pgrid_par! parameters defining this grid
105 REAL, INTENT(OUT), OPTIONAL :: plat0 ! reference latitude
106 REAL, INTENT(OUT), OPTIONAL :: plon0 ! reference longitude
107 INTEGER, INTENT(OUT), OPTIONAL :: kimax ! number of points in I direction
108 INTEGER, INTENT(OUT), OPTIONAL :: kjmax ! number of points in J direction
109 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: px ! X conformal coor. of grid mesh
110 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: py ! Y conformal coor. of grid mesh
111 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: pdx ! X grid mesh size
112 REAL, DIMENSION(:), INTENT(OUT), OPTIONAL :: pdy ! Y grid mesh size
113 INTEGER, INTENT(OUT), OPTIONAL :: kl ! number of points
114 !
115 !
116 !* 0.2 Declarations of local variables
117 ! -------------------------------
118 !
119 INTEGER :: il
120 REAL(KIND=JPRB) :: zhook_handle
121 !-------------------------------------------------------------------------------
122 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_CARTESIAN:GET_GRIDTYPE_CARTESIAN',0,zhook_handle)
123 IF (present(plat0)) plat0 = pgrid_par(1)
124 IF (present(plon0)) plon0 = pgrid_par(2)
125 IF (present(kimax)) kimax = nint(pgrid_par(3))
126 IF (present(kjmax)) kjmax = nint(pgrid_par(4))
127 !
128 IF (present(px)) THEN
129  il = SIZE(px)
130  px(:) = pgrid_par(4+1:4+il)
131 END IF
132 
133 IF (present(py)) THEN
134  il = SIZE(py)
135  py(:) = pgrid_par(4+il+1:4+2*il)
136 END IF
137 
138 IF (present(pdx)) THEN
139  il = SIZE(pdx)
140  pdx(:)= pgrid_par(4+2*il+1:4+3*il)
141 END IF
142 
143 IF (present(pdy)) THEN
144  il = SIZE(pdy)
145  pdy(:)= pgrid_par(4+3*il+1:4+4*il)
146 END IF
147 !
148 IF (present(kl)) kl = (SIZE(pgrid_par)-4)/4
149 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_CARTESIAN:GET_GRIDTYPE_CARTESIAN',1,zhook_handle)
150 !
151 !-------------------------------------------------------------------------------
152 END SUBROUTINE get_gridtype_cartesian
153 !############################################################################
154 !############################################################################
155 !############################################################################
156 ! ###################################################
157  SUBROUTINE latlon_cartesian(PLAT0,PLON0,PLAT,PLON)
158 ! ###################################################
159 !
160 !!**** *LATLON_CARTESIAN * - Routine to compute geographical coordinates
161 !!
162 !! PURPOSE
163 !! -------
164 !
165 !
166 !!** METHOD
167 !! ------
168 !!
169 !! AUTHOR
170 !! ------
171 !! V. Masson *Meteo France*
172 !!
173 !! MODIFICATION
174 !! ------------
175 !! Original 06/2004
176 !-------------------------------------------------------------------------------
177 !
178 !* 0. DECLARATIONS
179 ! ------------
180 !
181 !
182 IMPLICIT NONE
183 !
184 !* 0.1 Declarations of arguments and results
185 !
186 REAL, INTENT(IN) :: plat0 ! Reference latitude
187 REAL, INTENT(IN) :: plon0 ! Reference longitude
188 REAL, DIMENSION(:), INTENT(OUT):: plat,plon
189 REAL(KIND=JPRB) :: zhook_handle
190  ! returned geographic latitudes and
191  ! longitudes of the processed points
192  ! (degrees).
193 !
194 !* 0.2 Declarations of local variables
195 !
196 !--------------------------------------------------------------------------------
197 !
198 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_CARTESIAN:LATLON_CARTESIAN',0,zhook_handle)
199 plon(:) = plon0
200 plat(:) = plat0
201 IF (lhook) CALL dr_hook('MODE_GRIDTYPE_CARTESIAN:LATLON_CARTESIAN',1,zhook_handle)
202 !
203 !---------------------------------------------------------------------------------
204 END SUBROUTINE latlon_cartesian
205 !---------------------------------------------------------------------------------
206 !
207 END MODULE mode_gridtype_cartesian
subroutine put_gridtype_cartesian(PGRID_PAR, PLAT0, PLON0, KIMAX, KJMAX, PX, PY, PDX, PDY)
subroutine latlon_cartesian(PLAT0, PLON0, PLAT, PLON)
subroutine get_gridtype_cartesian(PGRID_PAR, PLAT0, PLON0, KIMAX, KJMAX, PX, PY, PDX, PDY, KL)