Subversion Repositories lagranto.icon

Rev

Details | Last modification | View Log | RSS feed

Rev Author Line No. Line
3 michaesp 1
! ********************************************************************************
2
! * Transformation routines from gm2em                                           *
3
! ********************************************************************************
4
 
5
REAL FUNCTION LMSTOLM (PHIS, LAMS, POLPHI, POLLAM)
6
  !
7
  !**** LMSTOLM  -   FC:BERECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE FUER
8
  !****                 EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
9
  !****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
10
  !****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
11
  !**   AUFRUF   :   LAM = LMSTOLM (PHIS, LAMS, POLPHI, POLLAM)
12
  !**   ENTRIES  :   KEINE
13
  !**   ZWECK    :   BERECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE FUER
14
  !**                EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
15
  !**                IM ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
16
  !**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
17
  !**   VERSIONS-
18
  !**   DATUM    :   03.05.90
19
  !**
20
  !**   EXTERNALS:   KEINE
21
  !**   EINGABE-
22
  !**   PARAMETER:   PHIS     REAL   GEOGR. BREITE DES PUNKTES IM ROT.SYS.
23
  !**                LAMS     REAL   GEOGR. LAENGE DES PUNKTES IM ROT.SYS.
24
  !**                POLPHI   REAL   WAHRE GEOGR. BREITE DES NORDPOLS
25
  !**                POLLAM   REAL   WAHRE GEOGR. LAENGE DES NORDPOLS
26
  !**   AUSGABE-
27
  !**   PARAMETER:   WAHRE GEOGRAPHISCHE LAENGE ALS WERT DER FUNKTION
28
  !**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
29
  !**
30
  !**   COMMON-
31
  !**   BLOECKE  :   KEINE
32
  !**
33
  !**   FEHLERBE-
34
  !**   HANDLUNG :   KEINE
35
  !**   VERFASSER:   D.MAJEWSKI
36
 
37
  REAL :: LAMS,PHIS,POLPHI,POLLAM
38
 
39
  DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
40
 
41
  ZSINPOL = SIN(ZPIR18*POLPHI)
42
  ZCOSPOL = COS(ZPIR18*POLPHI)
43
  ZLAMPOL = ZPIR18*POLLAM
44
  ZPHIS   = ZPIR18*PHIS
45
  ZLAMS   = LAMS
46
  IF(ZLAMS.GT.180.0) ZLAMS = ZLAMS - 360.0
47
  ZLAMS   = ZPIR18*ZLAMS
48
 
49
  ZARG1   = SIN(ZLAMPOL)*(- ZSINPOL*COS(ZLAMS)*COS(ZPHIS)  + &
50
       ZCOSPOL*           SIN(ZPHIS)) - &
51
       COS(ZLAMPOL)*           SIN(ZLAMS)*COS(ZPHIS)
52
  ZARG2   = COS(ZLAMPOL)*(- ZSINPOL*COS(ZLAMS)*COS(ZPHIS)  + &
53
       ZCOSPOL*           SIN(ZPHIS)) + &
54
       SIN(ZLAMPOL)*           SIN(ZLAMS)*COS(ZPHIS)
55
  IF (ABS(ZARG2).LT.1.E-30) THEN
56
    IF (ABS(ZARG1).LT.1.E-30) THEN
57
      LMSTOLM =   0.0
58
    ELSEIF (ZARG1.GT.0.) THEN
59
          LMSTOLAM =  90.0
60
        ELSE
61
          LMSTOLAM = -90.0
62
        ENDIF
63
  ELSE
64
    LMSTOLM = ZRPI18*ATAN2(ZARG1,ZARG2)
65
  ENDIF
66
 
67
  RETURN
68
END FUNCTION LMSTOLM
69
 
70
 
71
REAL FUNCTION PHSTOPH (PHIS, LAMS, POLPHI, POLLAM)
72
  !
73
  !**** PHSTOPH  -   FC:BERECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE FUER
74
  !****                 EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
75
  !****                 ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
76
  !****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
77
  !**   AUFRUF   :   PHI = PHSTOPH (PHIS, LAMS, POLPHI, POLLAM)
78
  !**   ENTRIES  :   KEINE
79
  !**   ZWECK    :   BERECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE FUER
80
  !**                EINEN PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
81
  !**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
82
  !**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
83
  !**   VERSIONS-
84
  !**   DATUM    :   03.05.90
85
  !**
86
  !**   EXTERNALS:   KEINE
87
  !**   EINGABE-
88
  !**   PARAMETER:   PHIS     REAL   GEOGR. BREITE DES PUNKTES IM ROT.SYS.
89
  !**                LAMS     REAL   GEOGR. LAENGE DES PUNKTES IM ROT.SYS.
90
  !**                POLPHI   REAL   WAHRE GEOGR. BREITE DES NORDPOLS
91
  !**                POLLAM   REAL   WAHRE GEOGR. LAENGE DES NORDPOLS
92
  !**   AUSGABE-
93
  !**   PARAMETER:   WAHRE GEOGRAPHISCHE BREITE ALS WERT DER FUNKTION
94
  !**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
95
  !**
96
  !**   COMMON-
97
  !**   BLOECKE  :   KEINE
98
  !**
99
  !**   FEHLERBE-
100
  !**   HANDLUNG :   KEINE
101
  !**   VERFASSER:   D.MAJEWSKI
102
 
103
  REAL :: LAMS,PHIS,POLPHI,POLLAM
104
 
105
  DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
106
 
107
  SINPOL = SIN(ZPIR18*POLPHI)
108
  COSPOL = COS(ZPIR18*POLPHI)
109
  ZPHIS  = ZPIR18*PHIS
110
  ZLAMS  = LAMS
111
  IF(ZLAMS.GT.180.0) ZLAMS = ZLAMS - 360.0
112
  ZLAMS  = ZPIR18*ZLAMS
113
  ARG     = COSPOL*COS(ZPHIS)*COS(ZLAMS) + SINPOL*SIN(ZPHIS)
114
 
115
  PHSTOPH = ZRPI18*ASIN(ARG)
116
 
117
  RETURN
118
END FUNCTION PHSTOPH
119
 
120
 
121
REAL FUNCTION LMTOLMS (PHI, LAM, POLPHI, POLLAM)
122
  !
123
  !%Z% Modul %M%, V%I% vom %G%, extrahiert am %H%
124
  !
125
  !**** LMTOLMS  -   FC:UMRECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE LAM
126
  !****                 AUF EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
127
  !****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
128
  !****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
129
  !**   AUFRUF   :   LAM = LMTOLMS (PHI, LAM, POLPHI, POLLAM)
130
  !**   ENTRIES  :   KEINE
131
  !**   ZWECK    :   UMRECHNUNG DER WAHREN GEOGRAPHISCHEN LAENGE LAM AUF
132
  !**                EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
133
  !**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
134
  !**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
135
  !**   VERSIONS-
136
  !**   DATUM    :   03.05.90
137
  !**
138
  !**   EXTERNALS:   KEINE
139
  !**   EINGABE-
140
  !**   PARAMETER:   PHI    REAL BREITE DES PUNKTES IM GEOGR. SYSTEM
141
  !**                LAM    REAL LAENGE DES PUNKTES IM GEOGR. SYSTEM
142
  !**                POLPHI REAL GEOGR.BREITE DES N-POLS DES ROT. SYSTEMS
143
  !**                POLLAM REAL GEOGR.LAENGE DES N-POLS DES ROT. SYSTEMS
144
  !**   AUSGABE-
145
  !**   PARAMETER:   WAHRE GEOGRAPHISCHE LAENGE ALS WERT DER FUNKTION
146
  !**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
147
  !**
148
  !**   COMMON-
149
  !**   BLOECKE  :   KEINE
150
  !**
151
  !**   FEHLERBE-
152
  !**   HANDLUNG :   KEINE
153
  !**   VERFASSER:   G. DE MORSIER
154
 
155
  REAL :: LAM,PHI,POLPHI,POLLAM
156
 
157
  DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
158
 
159
  ZSINPOL = SIN(ZPIR18*POLPHI)
160
  ZCOSPOL = COS(ZPIR18*POLPHI)
161
  ZLAMPOL =     ZPIR18*POLLAM
162
  ZPHI    =     ZPIR18*PHI
163
  ZLAM    = LAM
164
  IF(ZLAM.GT.180.0) ZLAM = ZLAM - 360.0
165
  ZLAM    = ZPIR18*ZLAM
166
 
167
  ZARG1   = - SIN(ZLAM-ZLAMPOL)*COS(ZPHI)
168
  ZARG2   = - ZSINPOL*COS(ZPHI)*COS(ZLAM-ZLAMPOL)+ZCOSPOL*SIN(ZPHI)
169
  IF (ABS(ZARG2).LT.1.E-30) THEN
170
    IF (ABS(ZARG1).LT.1.E-30) THEN
171
      LMTOLMS =   0.0
172
    ELSEIF (ZARG1.GT.0.) THEN
173
          LMTOLMS =  90.0
174
        ELSE
175
          LMTOLMS = -90.0
176
        ENDIF
177
  ELSE
178
    LMTOLMS = ZRPI18*ATAN2(ZARG1,ZARG2)
179
  ENDIF
180
 
181
  RETURN
182
END FUNCTION LMTOLMS
183
 
184
 
185
REAL FUNCTION PHTOPHS (PHI, LAM, POLPHI, POLLAM)
186
  !
187
  !%Z% Modul %M%, V%I% vom %G%, extrahiert am %H%
188
  !
189
  !**** PHTOPHS  -   FC:UMRECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE PHI
190
  !****                 AUF EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS)
191
  !****                 IM ROTIERTEN SYSTEM. DER NORDPOL DES SYSTEMS HAT
192
  !****                 DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
193
  !**   AUFRUF   :   PHI = PHTOPHS (PHI, LAM, POLPHI, POLLAM)
194
  !**   ENTRIES  :   KEINE
195
  !**   ZWECK    :   UMRECHNUNG DER WAHREN GEOGRAPHISCHEN BREITE PHI AUF
196
  !**                EINEM PUNKT MIT DEN KOORDINATEN (PHIS, LAMS) IM
197
  !**                ROTIERTEN SYSTEM. DER NORDPOL DIESES SYSTEMS HAT
198
  !**                DIE WAHREN KOORDINATEN (POLPHI, POLLAM)
199
  !**   VERSIONS-
200
  !**   DATUM    :   03.05.90
201
  !**
202
  !**   EXTERNALS:   KEINE
203
  !**   EINGABE-
204
  !**   PARAMETER:   PHI    REAL BREITE DES PUNKTES IM GEOGR. SYSTEM
205
  !**                LAM    REAL LAENGE DES PUNKTES IM GEOGR. SYSTEM
206
  !**                POLPHI REAL GEOGR.BREITE DES N-POLS DES ROT. SYSTEMS
207
  !**                POLLAM REAL GEOGR.LAENGE DES N-POLS DES ROT. SYSTEMS
208
  !**   AUSGABE-
209
  !**   PARAMETER:   ROTIERTE BREITE PHIS ALS WERT DER FUNKTION
210
  !**                ALLE WINKEL IN GRAD (NORDEN>0, OSTEN>0)
211
  !**
212
  !**   COMMON-
213
  !**   BLOECKE  :   KEINE
214
  !**
215
  !**   FEHLERBE-
216
  !**   HANDLUNG :   KEINE
217
  !**   VERFASSER:   G. DE MORSIER
218
 
219
  REAL :: LAM,PHI,POLPHI,POLLAM
220
 
221
  DATA        ZRPI18 , ZPIR18  / 57.2957795 , 0.0174532925 /
222
 
223
  ZSINPOL = SIN(ZPIR18*POLPHI)
224
  ZCOSPOL = COS(ZPIR18*POLPHI)
225
  ZLAMPOL = ZPIR18*POLLAM
226
  ZPHI    = ZPIR18*PHI
227
  ZLAM    = LAM
228
  IF(ZLAM.GT.180.0) ZLAM = ZLAM - 360.0
229
  ZLAM    = ZPIR18*ZLAM
230
  ZARG    = ZCOSPOL*COS(ZPHI)*COS(ZLAM-ZLAMPOL) + ZSINPOL*SIN(ZPHI)
231
 
232
  PHTOPHS = ZRPI18*ASIN(ZARG)
233
 
234
  RETURN
235
END FUNCTION PHTOPHS
236
 
237
 
238
SUBROUTINE uv2uvrot(u, v, rlat, rlon, pollat, pollon, urot, vrot)
239
 
240
  ! Description:
241
  ! This routine converts the wind components u and v from the real
242
  ! geographical system to the rotated system.
243
  !
244
  ! Method:
245
  ! Transformation formulas for converting between these two systems.
246
 
247
  real :: u, v
248
  real :: rlat, rlon
249
  real :: pollat, pollon
250
  real :: urot, vrot
251
  real :: zsinpol, zcospol, zlonp, zlat, zarg1, zarg2, znorm
252
  real      :: zrpi18 = 57.2957795
253
  real      :: zpir18 = 0.0174532925
254
 
255
  zsinpol = SIN(pollat * zpir18)
256
  zcospol = COS(pollat * zpir18)
257
  zlonp   = (pollon-rlon) * zpir18
258
  zlat    =         rlat  * zpir18
259
  zarg1   = zcospol*SIN(zlonp)
260
  zarg2   = zsinpol*COS(zlat) - zcospol*SIN(zlat)*COS(zlonp)
261
  znorm   = 1./SQRT( zarg1**2 + zarg2**2 )
262
  urot   =  u*zarg2*znorm - v*zarg1*znorm
263
  vrot   =  u*zarg1*znorm + v*zarg2*znorm
264
 
265
END SUBROUTINE uv2uvrot
266
 
267
 
268
SUBROUTINE uvrot2uv (urot, vrot, rlat, rlon, pollat, pollon, u, v)
269
 
270
  ! Description:
271
  ! This routine converts the wind components u and v from the rotated system
272
  ! to the real geographical system.
273
  !
274
  ! Method:
275
  ! Transformation formulas for converting between these two systems.
276
 
277
  integer :: n
278
  real :: u, v
279
  real :: rlat, rlon
280
  real :: pollat, pollon
281
  real :: urot, vrot
282
  real :: zsinpol, zcospol, zlonp, zlat, zarg1, zarg2, znorm
283
  integer :: i
284
  real      :: zrpi18 = 57.2957795
285
  real      :: zpir18 = 0.0174532925
286
 
287
  zsinpol = SIN(pollat * zpir18)
288
  zcospol = COS(pollat * zpir18)
289
  zlonp   = (pollon-rlon) * zpir18
290
  zlat    =         rlat  * zpir18
291
  zarg1   = zcospol*SIN(zlonp)
292
  zarg2   = zsinpol*COS(zlat) - zcospol*SIN(zlat)*COS(zlonp)
293
  znorm   = 1./SQRT(zarg1**2 + zarg2**2)
294
  u       =   urot*zarg2*znorm + vrot*zarg1*znorm
295
  v       = - urot*zarg1*znorm + vrot*zarg2*znorm
296
 
297
END SUBROUTINE uvrot2uv
298
 
299
! ********************************************************************************
300
! * Transformation routines from <utilities.f90>                                 *
301
! ********************************************************************************
302
 
303
FUNCTION  phirot2phi ( phirot, rlarot, polphi, pollam, polgam )
304
 
305
!------------------------------------------------------------------------------
306
!
307
! Description:
308
!   This function converts phi from one rotated system to phi in another
309
!   system. If the optional argument polgam is present, the other system
310
!   can also be a rotated one, where polgam is the angle between the two
311
!   north poles.
312
!   If polgam is not present, the other system is the real geographical
313
!   system.
314
!
315
! Method:
316
!   Transformation formulas for converting between these two systems.
317
!
318
!------------------------------------------------------------------------------
319
 
320
!------------------------------------------------------------------------------
321
!
322
! Declarations:
323
!
324
!------------------------------------------------------------------------------
325
 
326
! Parameter list:
327
REAL, INTENT (IN)      ::        &
328
  polphi,   & ! latitude of the rotated north pole
329
  pollam,   & ! longitude of the rotated north pole
330
  phirot,   & ! latitude in the rotated system
331
  rlarot      ! longitude in the rotated system
332
 
333
REAL, INTENT (IN)      ::        &
334
  polgam      ! angle between the north poles of the systems
335
 
336
REAL                   ::        &
337
  phirot2phi  ! latitude in the geographical system
338
 
339
! Local variables
340
REAL                   ::        &
341
  zsinpol, zcospol, zphis, zrlas, zarg, zgam
342
 
343
REAL, PARAMETER        ::        &
344
  zrpi18 = 57.2957795,                  &
345
  zpir18 = 0.0174532925
346
 
347
!------------------------------------------------------------------------------
348
 
349
! Begin function phirot2phi
350
 
351
  zsinpol     = SIN (zpir18 * polphi)
352
  zcospol     = COS (zpir18 * polphi)
353
 
354
  zphis       = zpir18 * phirot
355
  IF (rlarot > 180.0) THEN
356
    zrlas = rlarot - 360.0
357
  ELSE
358
    zrlas = rlarot
359
  ENDIF
360
  zrlas       = zpir18 * zrlas
361
 
362
  IF (polgam /= 0.0) THEN
363
    zgam  = zpir18 * polgam
364
    zarg  = zsinpol*SIN (zphis) +                                           &
365
        zcospol*COS(zphis) * ( COS(zrlas)*COS(zgam) - SIN(zgam)*SIN(zrlas) )
366
  ELSE
367
    zarg  = zcospol * COS (zphis) * COS (zrlas) + zsinpol * SIN (zphis)
368
  ENDIF
369
 
370
  phirot2phi  = zrpi18 * ASIN (zarg)
371
 
372
END FUNCTION phirot2phi
373
 
374
 
375
FUNCTION  phi2phirot ( phi, rla, polphi, pollam )
376
 
377
!------------------------------------------------------------------------------
378
! Description:
379
!   This routine converts phi from the real geographical system to phi
380
!   in the rotated system.
381
!
382
! Method:
383
!   Transformation formulas for converting between these two systems.
384
!
385
!------------------------------------------------------------------------------
386
! Parameter list:
387
REAL, INTENT (IN)      ::        &
388
  polphi,  & ! latitude of the rotated north pole
389
  pollam,  & ! longitude of the rotated north pole
390
  phi,     & ! latitude in the geographical system
391
  rla        ! longitude in the geographical system
392
 
393
REAL                   ::        &
394
  phi2phirot ! longitude in the rotated system
395
 
396
! Local variables
397
REAL                       ::    &
398
  zsinpol, zcospol, zlampol, zphi, zrla, zarg1, zarg2, zrla1
399
 
400
REAL, PARAMETER            ::    &
401
  zrpi18 = 57.2957795,                  & !
402
  zpir18 = 0.0174532925
403
 
404
!------------------------------------------------------------------------------
405
 
406
! Begin function phi2phirot
407
 
408
  zsinpol  = SIN (zpir18 * polphi)
409
  zcospol  = COS (zpir18 * polphi)
410
  zlampol  =      zpir18 * pollam
411
  zphi     =      zpir18 * phi
412
  IF (rla > 180.0) THEN
413
    zrla1  = rla - 360.0
414
  ELSE
415
    zrla1  = rla
416
  ENDIF
417
  zrla     = zpir18 * zrla1
418
 
419
  zarg1    = SIN (zphi) * zsinpol
420
  zarg2    = COS (zphi) * zcospol * COS (zrla - zlampol)
421
 
422
  phi2phirot = zrpi18 * ASIN (zarg1 + zarg2)
423
 
424
END FUNCTION phi2phirot
425
 
426
!==============================================================================
427
!==============================================================================
428
 
429
!------------------------------------------------------------------------------
430
 
431
FUNCTION  rlarot2rla (phirot, rlarot, polphi, pollam, polgam)
432
 
433
!------------------------------------------------------------------------------
434
!
435
! Description:
436
!   This function converts lambda from one rotated system to lambda in another
437
!   system. If the optional argument polgam is present, the other system
438
!   can also be a rotated one, where polgam is the angle between the two
439
!   north poles.
440
!   If polgam is not present, the other system is the real geographical
441
!   system.
442
!
443
! Method:
444
!   Transformation formulas for converting between these two systems.
445
!
446
! Modules used:    NONE
447
!
448
!------------------------------------------------------------------------------
449
 
450
!------------------------------------------------------------------------------
451
!
452
! Declarations:
453
!
454
!------------------------------------------------------------------------------
455
 
456
! Parameter list:
457
REAL, INTENT (IN)      ::        &
458
  polphi,   & ! latitude of the rotated north pole
459
  pollam,   & ! longitude of the rotated north pole
460
  phirot,   & ! latitude in the rotated system
461
  rlarot      ! longitude in the rotated system
462
 
463
REAL, INTENT (IN)      ::        &
464
  polgam      ! angle between the north poles of the systems
465
 
466
REAL                   ::        &
467
  rlarot2rla  ! latitude in the geographical system
468
 
469
! Local variables
470
REAL                   ::        &
471
  zsinpol, zcospol, zlampol, zphis, zrlas, zarg1, zarg2, zgam
472
 
473
REAL, PARAMETER        ::        &
474
  zrpi18 = 57.2957795,                  & !
475
  zpir18 = 0.0174532925
476
 
477
!------------------------------------------------------------------------------
478
 
479
! Begin function rlarot2rla
480
 
481
  zsinpol = SIN (zpir18 * polphi)
482
  zcospol = COS (zpir18 * polphi)
483
 
484
  zlampol = zpir18 * pollam
485
  zphis   = zpir18 * phirot
486
  IF (rlarot > 180.0) THEN
487
    zrlas = rlarot - 360.0
488
  ELSE
489
    zrlas = rlarot
490
  ENDIF
491
  zrlas   = zpir18 * zrlas
492
 
493
  IF (polgam /= 0.0) THEN
494
    zgam    = zpir18 * polgam
495
    zarg1   = SIN (zlampol) *                                                &
496
      (- zsinpol*COS(zphis) * (COS(zrlas)*COS(zgam) - SIN(zrlas)*SIN(zgam))  &
497
       + zcospol * SIN(zphis))                                               &
498
    - COS (zlampol)*COS(zphis) * (SIN(zrlas)*COS(zgam) + COS(zrlas)*SIN(zgam))
499
 
500
    zarg2   = COS (zlampol) *                                                &
501
      (- zsinpol*COS(zphis) * (COS(zrlas)*COS(zgam) - SIN(zrlas)*SIN(zgam))  &
502
       + zcospol * SIN(zphis))                                               &
503
    + SIN (zlampol)*COS(zphis) * (SIN(zrlas)*COS(zgam) + COS(zrlas)*SIN(zgam))
504
  ELSE
505
    zarg1   = SIN (zlampol) * (-zsinpol * COS(zrlas) * COS(zphis)  +    &
506
                                zcospol *              SIN(zphis)) -    &
507
              COS (zlampol) *             SIN(zrlas) * COS(zphis)
508
    zarg2   = COS (zlampol) * (-zsinpol * COS(zrlas) * COS(zphis)  +    &
509
                                zcospol *              SIN(zphis)) +   &
510
              SIN (zlampol) *             SIN(zrlas) * COS(zphis)
511
  ENDIF
512
 
513
  IF (zarg2 == 0.0) zarg2 = 1.0E-20
514
 
515
  rlarot2rla = zrpi18 * ATAN2(zarg1,zarg2)
516
 
517
END FUNCTION rlarot2rla
518
 
519
!==============================================================================
520
!==============================================================================
521
 
522
!------------------------------------------------------------------------------
523
 
524
FUNCTION  rla2rlarot ( phi, rla, polphi, pollam, polgam )
525
 
526
!------------------------------------------------------------------------------
527
!
528
! Description:
529
!   This routine converts lambda from the real geographical system to lambda
530
!   in the rotated system.
531
!
532
! Method:
533
!   Transformation formulas for converting between these two systems.
534
!
535
!------------------------------------------------------------------------------
536
!
537
! Parameter list:
538
REAL, INTENT (IN)      ::        &
539
  polphi,  & ! latitude of the rotated north pole
540
  pollam,  & ! longitude of the rotated north pole
541
  phi,     & ! latitude in geographical system
542
  rla        ! longitude in geographical system
543
 
544
REAL, INTENT (IN)      ::        &
545
  polgam      ! angle between the north poles of the systems
546
 
547
REAL                   ::        &
548
  rla2rlarot ! latitude in the the rotated system
549
 
550
! Local variables
551
REAL                       ::    &
552
  zsinpol, zcospol, zlampol, zphi, zrla, zarg1, zarg2, zrla1
553
 
554
REAL, PARAMETER            ::    &
555
  zrpi18 = 57.2957795,                  & !
556
  zpir18 = 0.0174532925
557
 
558
!------------------------------------------------------------------------------
559
 
560
! Begin function rla2rlarot
561
 
562
  zsinpol  = SIN (zpir18 * polphi)
563
  zcospol  = COS (zpir18 * polphi)
564
  zlampol  =      zpir18 * pollam
565
  zphi     =      zpir18 * phi
566
  IF (rla > 180.0) THEN
567
    zrla1  = rla - 360.0
568
  ELSE
569
    zrla1  = rla
570
  ENDIF
571
  zrla     = zpir18 * zrla1
572
 
573
  zarg1    = - SIN (zrla-zlampol) * COS(zphi)
574
  zarg2    = - zsinpol * COS(zphi) * COS(zrla-zlampol) + zcospol * SIN(zphi)
575
 
576
  IF (zarg2 == 0.0) zarg2 = 1.0E-20
577
 
578
  rla2rlarot = zrpi18 * ATAN2 (zarg1,zarg2)
579
 
580
  IF (polgam /= 0.0 ) THEN
581
    rla2rlarot = polgam + rla2rlarot
582
    IF (rla2rlarot > 180.) rla2rlarot = rla2rlarot -360.
583
  ENDIF
584
 
585
END FUNCTION rla2rlarot
586