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

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90 @ 2631

Last change on this file since 2631 was 2631, checked in by trackstand2, 13 years ago

geo2ocean - bug fix - missing ALLOCATABLE attribute and .NOT. on check on allocated status

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