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 trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/geo2ocean.F90 @ 941

Last change on this file since 941 was 719, checked in by ctlod, 16 years ago

get back to the nemo_v2_3 version for trunk

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