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

source: trunk/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90 @ 2528

Last change on this file since 2528 was 2528, checked in by rblod, 13 years ago

Update NEMOGCM from branch nemo_v3_3_beta

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