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/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90 @ 5883

Last change on this file since 5883 was 5883, checked in by gm, 8 years ago

#1613: vvl by default: TRA/TRC remove optimization associated with linear free surface

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