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

source: branches/UKMO/dev_r8183_GC_couple_pkg/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90 @ 8734

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

Make repcmo routine available to other files.

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