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/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90 @ 9467

Last change on this file since 9467 was 9467, checked in by acc, 6 years ago

Branch 2017/dev_merge_2017. Fix for out of bounds error with the extended form of lbcnfd. See ticket #2074

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