New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
geo2ocean.F90 in branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90 @ 13726

Last change on this file since 13726 was 9679, checked in by dancopsey, 6 years ago

Merge in r8183 version of this branch (dev_r8183_GC_couple_pkg [8730:8734])

File size: 24.1 KB
Line 
1MODULE geo2ocean
2   !!======================================================================
3   !!                     ***  MODULE  geo2ocean  ***
4   !! Ocean mesh    :  ???
5   !!======================================================================
6   !! History :  OPA  !  07-1996  (O. Marti)  Original code
7   !!   NEMO     1.0  !  06-2006  (G. Madec )  Free form, F90 + opt.
8   !!                 !  04-2007  (S. Masson)  angle: Add T, F points and bugfix in cos lateral boundary
9   !!            3.0  !  07-2008  (G. Madec)  geo2oce suppress lon/lat agruments
10   !!            3.7  !  11-2015  (G. Madec)  remove the unused repere and repcmo routines
11   !!----------------------------------------------------------------------
12#if defined key_agrif
13!clem: these lines do not seem necessary anymore
14!!DIR$ OPTIMIZE (-O 1)  ! cray formulation
15# if defined __INTEL_COMPILER
16!acc: still breaks on at least one Ivybridge cluster with ifort 17.0.4 without this directive
17!DIR$ OPTIMIZE:1        ! intel formulation
18# endif
19#endif
20   !!----------------------------------------------------------------------
21   !!   rot_rep       : Rotate the Repere: geographic grid <==> stretched coordinates grid
22   !!   angle         :
23   !!   geo2oce       :
24   !!   oce2geo       :
25   !!----------------------------------------------------------------------
26   USE dom_oce        ! mesh and scale factors
27   USE phycst         ! physical constants
28   !
29   USE in_out_manager ! I/O manager
30   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
31   USE lib_mpp        ! MPP library
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   repcmo    ! called in sbccpl
37   PUBLIC   rot_rep   ! called in sbccpl, fldread, and cyclone
38   PUBLIC   geo2oce   ! called in sbccpl
39   PUBLIC   oce2geo   ! called in sbccpl
40   PUBLIC   obs_rot   ! called in obs_rot_vel and obs_write
41
42   !                                         ! cos/sin between model grid lines and NP direction
43   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   gsint, gcost   ! at T point
44   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   gsinu, gcosu   ! at U point
45   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   gsinv, gcosv   ! at V point
46   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   gsinf, gcosf   ! at F point
47
48   LOGICAL ,              SAVE, DIMENSION(4)     ::   linit = .FALSE.
49   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gsinlon, gcoslon, gsinlat, gcoslat
50
51   LOGICAL ::   lmust_init = .TRUE.        !: used to initialize the cos/sin variables (see above)
52
53   !! * Substitutions
54#  include "vectopt_loop_substitute.h90"
55   !!----------------------------------------------------------------------
56   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
57   !! $Id$
58   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
59   !!----------------------------------------------------------------------
60CONTAINS
61
62   SUBROUTINE repcmo ( pxu1, pyu1, pxv1, pyv1,   &
63                       px2 , py2 , kchoix  )
64      !!----------------------------------------------------------------------
65      !!                  ***  ROUTINE repcmo  ***
66      !!
67      !! ** Purpose :   Change vector componantes from a geographic grid to a
68      !!      stretched coordinates grid.
69      !!
70      !! ** Method  :   Initialization of arrays at the first call.
71      !!
72      !! ** Action  : - px2 : first  componante (defined at u point)
73      !!              - py2 : second componante (defined at v point)
74      !!----------------------------------------------------------------------
75      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj) ::   pxu1, pyu1   ! geographic vector componantes at u-point
76      REAL(wp), INTENT(in   ), DIMENSION(jpi,jpj) ::   pxv1, pyv1   ! geographic vector componantes at v-point
77      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj) ::   px2          ! i-componante (defined at u-point)
78      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj) ::   py2          ! j-componante (defined at v-point)
79      !!----------------------------------------------------------------------
80      INTEGER, INTENT( IN ) ::   &
81         kchoix   ! type of transformation
82                  ! = 1 change from geographic to model grid.
83                  ! =-1 change from model to geographic grid
84      !!----------------------------------------------------------------------
85 
86      SELECT CASE (kchoix)
87      CASE ( 1)
88        ! Change from geographic to stretched coordinate
89        ! ----------------------------------------------
90     
91        CALL rot_rep( pxu1, pyu1, 'U', 'en->i',px2 )
92        CALL rot_rep( pxv1, pyv1, 'V', 'en->j',py2 )
93      CASE (-1)
94       ! Change from stretched to geographic coordinate
95       ! ----------------------------------------------
96     
97       CALL rot_rep( pxu1, pyu1, 'U', 'ij->e',px2 )
98       CALL rot_rep( pxv1, pyv1, 'V', 'ij->n',py2 )
99     END SELECT
100     
101   END SUBROUTINE repcmo
102
103   SUBROUTINE rot_rep ( pxin, pyin, cd_type, cdtodo, prot )
104      !!----------------------------------------------------------------------
105      !!                  ***  ROUTINE rot_rep  ***
106      !!
107      !! ** Purpose :   Rotate the Repere: Change vector componantes between
108      !!                geographic grid <--> stretched coordinates grid.
109      !!----------------------------------------------------------------------
110      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   pxin, pyin   ! vector componantes
111      CHARACTER(len=1),             INTENT(in   ) ::   cd_type      ! define the nature of pt2d array grid-points
112      CHARACTER(len=5),             INTENT(in   ) ::   cdtodo       ! type of transpormation:
113      !                                                             ! 'en->i' = east-north to i-component
114      !                                                             ! 'en->j' = east-north to j-component
115      !                                                             ! 'ij->e' = (i,j) components to east
116      !                                                             ! 'ij->n' = (i,j) components to north
117      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) ::   prot     
118      !!----------------------------------------------------------------------
119      !
120      IF( lmust_init ) THEN      ! at 1st call only: set  gsin. & gcos.
121         IF(lwp) WRITE(numout,*)
122         IF(lwp) WRITE(numout,*) ' rot_rep: coordinate transformation : geographic <==> model (i,j)-components'
123         IF(lwp) WRITE(numout,*) ' ~~~~~~~~    '
124         !
125         CALL angle       ! initialization of the transformation
126         lmust_init = .FALSE.
127      ENDIF
128      !
129      SELECT CASE( cdtodo )      ! type of rotation
130      !
131      CASE( 'en->i' )                  ! east-north to i-component
132         SELECT CASE (cd_type)
133         CASE ('T')   ;   prot(:,:) = pxin(:,:) * gcost(:,:) + pyin(:,:) * gsint(:,:)
134         CASE ('U')   ;   prot(:,:) = pxin(:,:) * gcosu(:,:) + pyin(:,:) * gsinu(:,:)
135         CASE ('V')   ;   prot(:,:) = pxin(:,:) * gcosv(:,:) + pyin(:,:) * gsinv(:,:)
136         CASE ('F')   ;   prot(:,:) = pxin(:,:) * gcosf(:,:) + pyin(:,:) * gsinf(:,:)
137         CASE DEFAULT   ;   CALL ctl_stop( 'Only T, U, V and F grid points are coded' )
138         END SELECT
139      CASE ('en->j')                   ! east-north to j-component
140         SELECT CASE (cd_type)
141         CASE ('T')   ;   prot(:,:) = pyin(:,:) * gcost(:,:) - pxin(:,:) * gsint(:,:)
142         CASE ('U')   ;   prot(:,:) = pyin(:,:) * gcosu(:,:) - pxin(:,:) * gsinu(:,:)
143         CASE ('V')   ;   prot(:,:) = pyin(:,:) * gcosv(:,:) - pxin(:,:) * gsinv(:,:)   
144         CASE ('F')   ;   prot(:,:) = pyin(:,:) * gcosf(:,:) - pxin(:,:) * gsinf(:,:)   
145         CASE DEFAULT   ;   CALL ctl_stop( 'Only T, U, V and F grid points are coded' )
146         END SELECT
147      CASE ('ij->e')                   ! (i,j)-components to east
148         SELECT CASE (cd_type)
149         CASE ('T')   ;   prot(:,:) = pxin(:,:) * gcost(:,:) - pyin(:,:) * gsint(:,:)
150         CASE ('U')   ;   prot(:,:) = pxin(:,:) * gcosu(:,:) - pyin(:,:) * gsinu(:,:)
151         CASE ('V')   ;   prot(:,:) = pxin(:,:) * gcosv(:,:) - pyin(:,:) * gsinv(:,:)
152         CASE ('F')   ;   prot(:,:) = pxin(:,:) * gcosf(:,:) - pyin(:,:) * gsinf(:,:)
153         CASE DEFAULT   ;   CALL ctl_stop( 'Only T, U, V and F grid points are coded' )
154         END SELECT
155      CASE ('ij->n')                   ! (i,j)-components to north
156         SELECT CASE (cd_type)
157         CASE ('T')   ;   prot(:,:) = pyin(:,:) * gcost(:,:) + pxin(:,:) * gsint(:,:)
158         CASE ('U')   ;   prot(:,:) = pyin(:,:) * gcosu(:,:) + pxin(:,:) * gsinu(:,:)
159         CASE ('V')   ;   prot(:,:) = pyin(:,:) * gcosv(:,:) + pxin(:,:) * gsinv(:,:)
160         CASE ('F')   ;   prot(:,:) = pyin(:,:) * gcosf(:,:) + pxin(:,:) * gsinf(:,:)
161         CASE DEFAULT   ;   CALL ctl_stop( 'Only T, U, V and F grid points are coded' )
162         END SELECT
163      CASE DEFAULT   ;   CALL ctl_stop( 'rot_rep: Syntax Error in the definition of cdtodo' )
164      !
165      END SELECT
166      !
167   END SUBROUTINE rot_rep
168
169
170   SUBROUTINE angle
171      !!----------------------------------------------------------------------
172      !!                  ***  ROUTINE angle  ***
173      !!
174      !! ** Purpose :   Compute angles between model grid lines and the North direction
175      !!
176      !! ** Method  :   sinus and cosinus of the angle between the north-south axe
177      !!              and the j-direction at t, u, v and f-points
178      !!                dot and cross products are used to obtain cos and sin, resp.
179      !!
180      !! ** Action  : - gsint, gcost, gsinu, gcosu, gsinv, gcosv, gsinf, gcosf
181      !!----------------------------------------------------------------------
182      INTEGER  ::   ji, jj   ! dummy loop indices
183      INTEGER  ::   ierr     ! local integer
184      REAL(wp) ::   zlam, zphi            ! local scalars
185      REAL(wp) ::   zlan, zphh            !   -      -
186      REAL(wp) ::   zxnpt, zynpt, znnpt   ! x,y components and norm of the vector: T point to North Pole
187      REAL(wp) ::   zxnpu, zynpu, znnpu   ! x,y components and norm of the vector: U point to North Pole
188      REAL(wp) ::   zxnpv, zynpv, znnpv   ! x,y components and norm of the vector: V point to North Pole
189      REAL(wp) ::   zxnpf, zynpf, znnpf   ! x,y components and norm of the vector: F point to North Pole
190      REAL(wp) ::   zxvvt, zyvvt, znvvt   ! x,y components and norm of the vector: between V points below and above a T point
191      REAL(wp) ::   zxffu, zyffu, znffu   ! x,y components and norm of the vector: between F points below and above a U point
192      REAL(wp) ::   zxffv, zyffv, znffv   ! x,y components and norm of the vector: between F points left  and right a V point
193      REAL(wp) ::   zxuuf, zyuuf, znuuf   ! x,y components and norm of the vector: between U points below and above a F point
194      !!----------------------------------------------------------------------
195      !
196      ALLOCATE( gsint(jpi,jpj), gcost(jpi,jpj),   & 
197         &      gsinu(jpi,jpj), gcosu(jpi,jpj),   & 
198         &      gsinv(jpi,jpj), gcosv(jpi,jpj),   & 
199         &      gsinf(jpi,jpj), gcosf(jpi,jpj), STAT=ierr )
200      IF(lk_mpp)   CALL mpp_sum( ierr )
201      IF( ierr /= 0 )   CALL ctl_stop( 'angle: unable to allocate arrays' )
202      !
203      ! ============================= !
204      ! Compute the cosinus and sinus !
205      ! ============================= !
206      ! (computation done on the north stereographic polar plane)
207      !
208      DO jj = 2, jpjm1
209         DO ji = fs_2, jpi   ! vector opt.
210            !                 
211            zlam = glamt(ji,jj)     ! north pole direction & modulous (at t-point)
212            zphi = gphit(ji,jj)
213            zxnpt = 0. - 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )
214            zynpt = 0. - 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )
215            znnpt = zxnpt*zxnpt + zynpt*zynpt
216            !
217            zlam = glamu(ji,jj)     ! north pole direction & modulous (at u-point)
218            zphi = gphiu(ji,jj)
219            zxnpu = 0. - 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )
220            zynpu = 0. - 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )
221            znnpu = zxnpu*zxnpu + zynpu*zynpu
222            !
223            zlam = glamv(ji,jj)     ! north pole direction & modulous (at v-point)
224            zphi = gphiv(ji,jj)
225            zxnpv = 0. - 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )
226            zynpv = 0. - 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )
227            znnpv = zxnpv*zxnpv + zynpv*zynpv
228            !
229            zlam = glamf(ji,jj)     ! north pole direction & modulous (at f-point)
230            zphi = gphif(ji,jj)
231            zxnpf = 0. - 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )
232            zynpf = 0. - 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )
233            znnpf = zxnpf*zxnpf + zynpf*zynpf
234            !
235            zlam = glamv(ji,jj  )   ! j-direction: v-point segment direction (around t-point)
236            zphi = gphiv(ji,jj  )
237            zlan = glamv(ji,jj-1)
238            zphh = gphiv(ji,jj-1)
239            zxvvt =  2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )   &
240               &  -  2. * COS( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. )
241            zyvvt =  2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )   &
242               &  -  2. * SIN( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. )
243            znvvt = SQRT( znnpt * ( zxvvt*zxvvt + zyvvt*zyvvt )  )
244            znvvt = MAX( znvvt, 1.e-14 )
245            !
246            zlam = glamf(ji,jj  )   ! j-direction: f-point segment direction (around u-point)
247            zphi = gphif(ji,jj  )
248            zlan = glamf(ji,jj-1)
249            zphh = gphif(ji,jj-1)
250            zxffu =  2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )   &
251               &  -  2. * COS( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. )
252            zyffu =  2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )   &
253               &  -  2. * SIN( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. )
254            znffu = SQRT( znnpu * ( zxffu*zxffu + zyffu*zyffu )  )
255            znffu = MAX( znffu, 1.e-14 )
256            !
257            zlam = glamf(ji  ,jj)   ! i-direction: f-point segment direction (around v-point)
258            zphi = gphif(ji  ,jj)
259            zlan = glamf(ji-1,jj)
260            zphh = gphif(ji-1,jj)
261            zxffv =  2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )   &
262               &  -  2. * COS( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. )
263            zyffv =  2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )   &
264               &  -  2. * SIN( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. )
265            znffv = SQRT( znnpv * ( zxffv*zxffv + zyffv*zyffv )  )
266            znffv = MAX( znffv, 1.e-14 )
267            !
268            zlam = glamu(ji,jj+1)   ! j-direction: u-point segment direction (around f-point)
269            zphi = gphiu(ji,jj+1)
270            zlan = glamu(ji,jj  )
271            zphh = gphiu(ji,jj  )
272            zxuuf =  2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )   &
273               &  -  2. * COS( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. )
274            zyuuf =  2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. )   &
275               &  -  2. * SIN( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. )
276            znuuf = SQRT( znnpf * ( zxuuf*zxuuf + zyuuf*zyuuf )  )
277            znuuf = MAX( znuuf, 1.e-14 )
278            !
279            !                       ! cosinus and sinus using dot and cross products
280            gsint(ji,jj) = ( zxnpt*zyvvt - zynpt*zxvvt ) / znvvt
281            gcost(ji,jj) = ( zxnpt*zxvvt + zynpt*zyvvt ) / znvvt
282            !
283            gsinu(ji,jj) = ( zxnpu*zyffu - zynpu*zxffu ) / znffu
284            gcosu(ji,jj) = ( zxnpu*zxffu + zynpu*zyffu ) / znffu
285            !
286            gsinf(ji,jj) = ( zxnpf*zyuuf - zynpf*zxuuf ) / znuuf
287            gcosf(ji,jj) = ( zxnpf*zxuuf + zynpf*zyuuf ) / znuuf
288            !
289            gsinv(ji,jj) = ( zxnpv*zxffv + zynpv*zyffv ) / znffv
290            gcosv(ji,jj) =-( zxnpv*zyffv - zynpv*zxffv ) / znffv     ! (caution, rotation of 90 degres)
291            !
292         END DO
293      END DO
294
295      ! =============== !
296      ! Geographic mesh !
297      ! =============== !
298
299      DO jj = 2, jpjm1
300         DO ji = fs_2, jpi   ! vector opt.
301            IF( MOD( ABS( glamv(ji,jj) - glamv(ji,jj-1) ), 360. ) < 1.e-8 ) THEN
302               gsint(ji,jj) = 0.
303               gcost(ji,jj) = 1.
304            ENDIF
305            IF( MOD( ABS( glamf(ji,jj) - glamf(ji,jj-1) ), 360. ) < 1.e-8 ) THEN
306               gsinu(ji,jj) = 0.
307               gcosu(ji,jj) = 1.
308            ENDIF
309            IF(      ABS( gphif(ji,jj) - gphif(ji-1,jj) )         < 1.e-8 ) THEN
310               gsinv(ji,jj) = 0.
311               gcosv(ji,jj) = 1.
312            ENDIF
313            IF( MOD( ABS( glamu(ji,jj) - glamu(ji,jj+1) ), 360. ) < 1.e-8 ) THEN
314               gsinf(ji,jj) = 0.
315               gcosf(ji,jj) = 1.
316            ENDIF
317         END DO
318      END DO
319
320      ! =========================== !
321      ! Lateral boundary conditions !
322      ! =========================== !
323      !           ! lateral boundary cond.: T-, U-, V-, F-pts, sgn
324      CALL lbc_lnk_multi( gcost, 'T', -1., gsint, 'T', -1., gcosu, 'U', -1., gsinu, 'U', -1., & 
325                      &   gcosv, 'V', -1., gsinv, 'V', -1., gcosf, 'F', -1., gsinf, 'F', -1.  )
326      !
327   END SUBROUTINE angle
328
329
330   SUBROUTINE geo2oce ( pxx, pyy, pzz, cgrid, pte, ptn )
331      !!----------------------------------------------------------------------
332      !!                    ***  ROUTINE geo2oce  ***
333      !!     
334      !! ** Purpose :
335      !!
336      !! ** Method  :   Change a vector from geocentric to east/north
337      !!
338      !!----------------------------------------------------------------------
339      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::  pxx, pyy, pzz
340      CHARACTER(len=1)            , INTENT(in   ) ::  cgrid
341      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) ::  pte, ptn
342      !
343      REAL(wp), PARAMETER :: rpi = 3.141592653e0
344      REAL(wp), PARAMETER :: rad = rpi / 180.e0
345      INTEGER ::   ig     !
346      INTEGER ::   ierr   ! local integer
347      !!----------------------------------------------------------------------
348      !
349      IF( .NOT. ALLOCATED( gsinlon ) ) THEN
350         ALLOCATE( gsinlon(jpi,jpj,4) , gcoslon(jpi,jpj,4) ,   &
351            &      gsinlat(jpi,jpj,4) , gcoslat(jpi,jpj,4) , STAT=ierr )
352         IF( lk_mpp    )   CALL mpp_sum( ierr )
353         IF( ierr /= 0 )   CALL ctl_stop('geo2oce: unable to allocate arrays' )
354      ENDIF
355      !
356      SELECT CASE( cgrid)
357      CASE ( 'T' )   
358         ig = 1
359         IF( .NOT. linit(ig) ) THEN
360            gsinlon(:,:,ig) = SIN( rad * glamt(:,:) )
361            gcoslon(:,:,ig) = COS( rad * glamt(:,:) )
362            gsinlat(:,:,ig) = SIN( rad * gphit(:,:) )
363            gcoslat(:,:,ig) = COS( rad * gphit(:,:) )
364            linit(ig) = .TRUE.
365         ENDIF
366      CASE ( 'U' )   
367         ig = 2
368         IF( .NOT. linit(ig) ) THEN
369            gsinlon(:,:,ig) = SIN( rad * glamu(:,:) )
370            gcoslon(:,:,ig) = COS( rad * glamu(:,:) )
371            gsinlat(:,:,ig) = SIN( rad * gphiu(:,:) )
372            gcoslat(:,:,ig) = COS( rad * gphiu(:,:) )
373            linit(ig) = .TRUE.
374         ENDIF
375      CASE ( 'V' )   
376         ig = 3
377         IF( .NOT. linit(ig) ) THEN
378            gsinlon(:,:,ig) = SIN( rad * glamv(:,:) )
379            gcoslon(:,:,ig) = COS( rad * glamv(:,:) )
380            gsinlat(:,:,ig) = SIN( rad * gphiv(:,:) )
381            gcoslat(:,:,ig) = COS( rad * gphiv(:,:) )
382            linit(ig) = .TRUE.
383         ENDIF
384      CASE ( 'F' )   
385         ig = 4
386         IF( .NOT. linit(ig) ) THEN
387            gsinlon(:,:,ig) = SIN( rad * glamf(:,:) )
388            gcoslon(:,:,ig) = COS( rad * glamf(:,:) )
389            gsinlat(:,:,ig) = SIN( rad * gphif(:,:) )
390            gcoslat(:,:,ig) = COS( rad * gphif(:,:) )
391            linit(ig) = .TRUE.
392         ENDIF
393      CASE default   
394         WRITE(ctmp1,*) 'geo2oce : bad grid argument : ', cgrid
395         CALL ctl_stop( ctmp1 )
396      END SELECT
397      !
398      pte = - gsinlon(:,:,ig) * pxx + gcoslon(:,:,ig) * pyy
399      ptn = - gcoslon(:,:,ig) * gsinlat(:,:,ig) * pxx    &
400         &  - gsinlon(:,:,ig) * gsinlat(:,:,ig) * pyy    &
401         &  + gcoslat(:,:,ig) * pzz
402      !
403   END SUBROUTINE geo2oce
404
405
406   SUBROUTINE oce2geo ( pte, ptn, cgrid, pxx , pyy , pzz )
407      !!----------------------------------------------------------------------
408      !!                    ***  ROUTINE oce2geo  ***
409      !!     
410      !! ** Purpose :
411      !!
412      !! ** Method  :   Change vector from east/north to geocentric
413      !!
414      !! History :     ! (A. Caubel)  oce2geo - Original code
415      !!----------------------------------------------------------------------
416      REAL(wp), DIMENSION(jpi,jpj), INTENT( IN    ) ::  pte, ptn
417      CHARACTER(len=1)            , INTENT( IN    ) ::  cgrid
418      REAL(wp), DIMENSION(jpi,jpj), INTENT(   OUT ) ::  pxx , pyy , pzz
419      !!
420      REAL(wp), PARAMETER :: rpi = 3.141592653E0
421      REAL(wp), PARAMETER :: rad = rpi / 180.e0
422      INTEGER ::   ig     !
423      INTEGER ::   ierr   ! local integer
424      !!----------------------------------------------------------------------
425
426      IF( .NOT. ALLOCATED( gsinlon ) ) THEN
427         ALLOCATE( gsinlon(jpi,jpj,4) , gcoslon(jpi,jpj,4) ,   &
428            &      gsinlat(jpi,jpj,4) , gcoslat(jpi,jpj,4) , STAT=ierr )
429         IF( lk_mpp    )   CALL mpp_sum( ierr )
430         IF( ierr /= 0 )   CALL ctl_stop('oce2geo: unable to allocate arrays' )
431      ENDIF
432
433      SELECT CASE( cgrid)
434         CASE ( 'T' )   
435            ig = 1
436            IF( .NOT. linit(ig) ) THEN
437               gsinlon(:,:,ig) = SIN( rad * glamt(:,:) )
438               gcoslon(:,:,ig) = COS( rad * glamt(:,:) )
439               gsinlat(:,:,ig) = SIN( rad * gphit(:,:) )
440               gcoslat(:,:,ig) = COS( rad * gphit(:,:) )
441               linit(ig) = .TRUE.
442            ENDIF
443         CASE ( 'U' )   
444            ig = 2
445            IF( .NOT. linit(ig) ) THEN
446               gsinlon(:,:,ig) = SIN( rad * glamu(:,:) )
447               gcoslon(:,:,ig) = COS( rad * glamu(:,:) )
448               gsinlat(:,:,ig) = SIN( rad * gphiu(:,:) )
449               gcoslat(:,:,ig) = COS( rad * gphiu(:,:) )
450               linit(ig) = .TRUE.
451            ENDIF
452         CASE ( 'V' )   
453            ig = 3
454            IF( .NOT. linit(ig) ) THEN
455               gsinlon(:,:,ig) = SIN( rad * glamv(:,:) )
456               gcoslon(:,:,ig) = COS( rad * glamv(:,:) )
457               gsinlat(:,:,ig) = SIN( rad * gphiv(:,:) )
458               gcoslat(:,:,ig) = COS( rad * gphiv(:,:) )
459               linit(ig) = .TRUE.
460            ENDIF
461         CASE ( 'F' )   
462            ig = 4
463            IF( .NOT. linit(ig) ) THEN
464               gsinlon(:,:,ig) = SIN( rad * glamf(:,:) )
465               gcoslon(:,:,ig) = COS( rad * glamf(:,:) )
466               gsinlat(:,:,ig) = SIN( rad * gphif(:,:) )
467               gcoslat(:,:,ig) = COS( rad * gphif(:,:) )
468               linit(ig) = .TRUE.
469            ENDIF
470         CASE default   
471            WRITE(ctmp1,*) 'geo2oce : bad grid argument : ', cgrid
472            CALL ctl_stop( ctmp1 )
473      END SELECT
474      !
475      pxx = - gsinlon(:,:,ig) * pte - gcoslon(:,:,ig) * gsinlat(:,:,ig) * ptn 
476      pyy =   gcoslon(:,:,ig) * pte - gsinlon(:,:,ig) * gsinlat(:,:,ig) * ptn
477      pzz =   gcoslat(:,:,ig) * ptn
478      !
479   END SUBROUTINE oce2geo
480
481
482   SUBROUTINE obs_rot( psinu, pcosu, psinv, pcosv )
483      !!----------------------------------------------------------------------
484      !!                  ***  ROUTINE obs_rot  ***
485      !!
486      !! ** Purpose :   Copy gsinu, gcosu, gsinv and gsinv
487      !!                to input data for rotations of
488      !!                current at observation points
489      !!
490      !! History :  9.2  !  09-02  (K. Mogensen)
491      !!----------------------------------------------------------------------
492      REAL(wp), DIMENSION(jpi,jpj), INTENT( OUT )::   psinu, pcosu, psinv, pcosv   ! copy of data
493      !!----------------------------------------------------------------------
494      !
495      ! Initialization of gsin* and gcos* at first call
496      ! -----------------------------------------------
497      IF( lmust_init ) THEN
498         IF(lwp) WRITE(numout,*)
499         IF(lwp) WRITE(numout,*) ' obs_rot : geographic <--> stretched'
500         IF(lwp) WRITE(numout,*) ' ~~~~~~~   coordinate transformation'
501         CALL angle       ! initialization of the transformation
502         lmust_init = .FALSE.
503      ENDIF
504      !
505      psinu(:,:) = gsinu(:,:)
506      pcosu(:,:) = gcosu(:,:)
507      psinv(:,:) = gsinv(:,:)
508      pcosv(:,:) = gcosv(:,:)
509      !
510   END SUBROUTINE obs_rot
511
512  !!======================================================================
513END MODULE geo2ocean
Note: See TracBrowser for help on using the repository browser.