SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
oi_latlon_conf_proj.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 oi_latlon_conf_proj(NDIM,PLAT0,PLON0,PRPK,PBETA,PLATOR,PLONOR, &
7  px,py,plat,plon )
8 ! ###################################################
9 !
10 !!**** *LATLON_CONF_PROJ * - Routine to compute geographical coordinates
11 !!
12 !! PURPOSE
13 !! -------
14 ! This routine computes the latitude and longitude of
15 ! an array given in cartesian conformal coordinates
16 ! Five map projections are available:
17 ! - polar-stereographic from south pole (PRPK=1),
18 ! - lambert conformal from south pole (0<PRPK<1),
19 ! - mercator (PRPK=0),
20 ! - lambert conformal from north pole (-1<PRPK<0),
21 ! - polar-stereographic from north pole (PRPK=-1).
22 !
23 !
24 !!** METHOD
25 !! ------
26 !! Spherical earth approximation is used. Longitude origin is
27 !! set in Greenwich, and is positive eastwards. An anticlockwise
28 !! rotation of PBETA degrees is applied to the conformal frame
29 !! with respect to the geographical directions.
30 !!
31 !! WARNING: ALL INPUT AND OUTPUT ANGLES ARE IN DEGREES...
32 !!
33 !! EXTERNAL
34 !! --------
35 !! None
36 !!
37 !! REFERENCE
38 !! ---------
39 !! Asencio N. et al., 1994, "Le projet de modele non-hydrostatique
40 !! commun CNRM-LA, specifications techniques",
41 !! Note CNRM/GMME, 26, 139p, (Chapter 2).
42 !! Ducrocq V., 1994, "Generation de la grille dans le modele",
43 !! Note interne MNH, 5 mai, 3p.
44 !! Joly A., 1992, "Geographic parameters for ARPEGE/ALADIN",
45 !! Internal note ARPEGE/ALADIN, february 27,28p.
46 !! Levallois J., 1970, "Geodesie generale", Tome 2, Collection
47 !! de l'IGN, Eyrolles, Paris, 408p.
48 !!
49 !! AUTHOR
50 !! ------
51 !! P.M. *LA*
52 !!
53 !! MODIFICATION
54 !! ------------
55 !! Original PM 24/05/94
56 !! Updated PM 27/07/94
57 !! Updated VD 23/08/94
58 !! Updated VM 24/10/95 projection from north pole (PRPK<0) and
59 !! longitudes set between PLON0-180. and PLON0+180.
60 !! Update VM 11/2004 externalized version
61 !-------------------------------------------------------------------------------
62 !
63 !* 0. DECLARATIONS
64 ! ------------
65 !
66 USE modd_csts,ONLY : xpi, xradius
67 !
68 !
69 USE yomhook ,ONLY : lhook, dr_hook
70 USE parkind1 ,ONLY : jprb
71 !
72 IMPLICIT NONE
73 !
74 !* 0.1 Declarations of arguments and results
75 !
76 REAL, INTENT(IN) :: plat0 ! Reference latitude
77 REAL, INTENT(IN) :: plon0 ! Reference longitude
78 REAL, INTENT(IN) :: prpk ! projection parameter
79 ! ! K=1 : stereographic north pole
80 ! ! 0<K<1 : Lambert, north hemisphere
81 ! ! K=0 : Mercator
82 ! !-1<K<0 : Lambert, south hemisphere
83 ! ! K=-1: stereographic south pole
84 REAL, INTENT(IN) :: pbeta ! angle between grid and reference longitude
85 REAL, INTENT(IN) :: plator ! Latitude of the origine point
86 REAL, INTENT(IN) :: plonor ! Longitude of the origine point
87 REAL, DIMENSION(NDIM), INTENT(IN) :: px,py
88  ! given conformal coordinates of the
89  ! processed points (meters);
90 REAL, DIMENSION(NDIM), INTENT(OUT):: plat,plon
91  ! returned geographic latitudes and
92  ! longitudes of the processed points
93  ! (degrees).
94 INTEGER, INTENT(IN) :: ndim
95 !
96 !* 0.2 Declarations of local variables
97 !
98 REAL, DIMENSION(NDIM) :: zy
99 REAL :: zrpk,zbeta,zlat0,zlon0,zlator,zlonor
100 REAL :: zrdsdg,zclat0,zslat0,zclator,zslator
101 REAL :: zxbm0,zybm0,zro0,zga0
102 REAL :: zxp,zyp,zepsi,zt1,zcgam,zsgam,zraclat0
103 !
104 REAL, DIMENSION(NDIM) :: zata,zro2,zt2,zxmi0,zymi0
105 REAL(KIND=JPRB) :: zhook_handle
106 !
107 !--------------------------------------------------------------------------------
108 !
109 !* 1. Preliminary calculations for all projections
110 ! --------------------------------------------
111 !
112 IF (lhook) CALL dr_hook('OI_LATLON_CONF_PROJ',0,zhook_handle)
113 zrdsdg = xpi/180. ! Degree to radian conversion factor
114 zepsi = 10.*epsilon(1.) ! A small number
115 !
116 ! By definition, (PLONOR,PLATOR) are the geographical
117 ! coordinates, and (ZXBM0,ZYBM0) the conformal cartesian
118 ! point of coordinates (x=0,y=0).
119 !
120 zxbm0 = 0.
121 zybm0 = 0.
122 !
123 !-------------------------------------------------------------------------------
124 !
125 !* 2. POLAR STEREOGRAPHIC AND LAMBERT CONFORMAL CASES
126 ! -----------------------------------------------
127 ! (PRPK=1 P-stereo, 0<PRPK<1 Lambert)
128 !
129 IF(prpk /= 0.) THEN
130 !
131  IF (prpk<0.) THEN ! projection from north pole
132  zrpk=-prpk
133  zbeta=-pbeta
134  zlat0=-plat0
135  zlon0=plon0+180.
136  zlator=-plator
137  zlonor=plonor+180.
138  zy(:)=-py(:)
139  zybm0=-zybm0
140  ELSE ! projection from south pole
141  zrpk=prpk
142  zbeta=pbeta
143  zlat0=plat0
144  zlon0=plon0
145  zlator=plator
146  zlonor=plonor
147  zy(:)=py(:)
148  ENDIF
149 !
150 !* 2.1 Preliminary calculations
151 !
152  zclat0 = cos(zrdsdg*zlat0)
153  zslat0 = sin(zrdsdg*zlat0)
154  zclator = cos(zrdsdg*zlator)
155  zslator = sin(zrdsdg*zlator)
156  zro0 = (xradius/zrpk)*(abs(zclat0))**(1.-zrpk) &
157  * ((1.+zslat0)*abs(zclator)/(1.+zslator))**zrpk
158  zga0 = (zrpk*(zlonor-zlon0)-zbeta)*zrdsdg
159  zxp = zxbm0-zro0*sin(zga0)
160  zyp = zybm0+zro0*cos(zga0)
161 !
162 !* 2.2 Longitude
163 !
164  WHERE (abs(zy(:)-zyp) < zepsi &
165  .AND.abs(px(:)-zxp) < zepsi)
166  zata(:) = 0.
167  ELSEWHERE
168  zata(:) = atan2(-(zxp-px(:)),(zyp-zy(:)))/zrdsdg
169  END WHERE
170  !
171  plon(:) = (zbeta+zata(:))/zrpk+zlon0
172 !
173 !* 2.3 Latitude
174 !
175  zro2(:) = (px(:)-zxp)**2+(zy(:)-zyp)**2
176  zt1 = (xradius*(abs(zclat0))**(1.-zrpk))**(2./zrpk) &
177  * (1+zslat0)**2
178  zt2(:) = (zrpk**2*zro2(:))**(1./zrpk)
179  !
180  plat(:) = (xpi/2.-acos((zt1-zt2(:))/(zt1+zt2(:))))/zrdsdg
181 !
182  IF (prpk<0.) THEN ! projection from north pole
183  plat(:)=-plat(:)
184  plon(:)=plon(:)+180.
185  ENDIF
186 !
187 !-------------------------------------------------------------------------------
188 !
189 !* 3. MERCATOR PROJECTION WITH ROTATION
190 ! ---------------------------------
191 ! (PRPK=0)
192 !
193 ELSE
194 !
195 !* 3.1 Preliminary calculations
196 !
197  zcgam = cos(-zrdsdg*pbeta)
198  zsgam = sin(-zrdsdg*pbeta)
199  zraclat0 = xradius*cos(zrdsdg*plat0)
200 !
201 !* 3.2 Longitude
202 !
203  zxmi0(:) = px(:)-zxbm0
204  zymi0(:) = py(:)-zybm0
205 !
206  plon(:) = (zxmi0(:)*zcgam+zymi0(:)*zsgam) &
207  / (zraclat0*zrdsdg)+plonor
208 !
209 !* 3.3 Latitude
210 !
211  zt1 = alog(tan(xpi/4.+plator*zrdsdg/2.))
212  zt2(:) = (-zxmi0(:)*zsgam+zymi0(:)*zcgam)/zraclat0
213  !
214  plat(:) = (-xpi/2.+2.*atan(exp(zt1+zt2(:))))/zrdsdg
215 !
216 !---------------------------------------------------------------------------------
217 !
218 !* 4. EXIT
219 ! ----
220 !
221 END IF
222 plon(:)=plon(:)+nint((plon0-plon(:))/360.)*360.
223 IF (lhook) CALL dr_hook('OI_LATLON_CONF_PROJ',1,zhook_handle)
224 !---------------------------------------------------------------------------------
225 END SUBROUTINE oi_latlon_conf_proj
subroutine oi_latlon_conf_proj(NDIM, PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, PX, PY, PLAT, PLON)