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

source: branches/DEV_r1879_FCM/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90 @ 2007

Last change on this file since 2007 was 2007, checked in by smasson, 14 years ago

update branches/DEV_r1879_FCM/NEMOGCM/NEMO with tags/nemo_v3_2_1/NEMO

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