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.
obcdyn_tam.F90 in branches/2010_and_older/TAM_V3_2_2/NEMOTAM/OPATAM_SRC/OBC – NEMO

source: branches/2010_and_older/TAM_V3_2_2/NEMOTAM/OPATAM_SRC/OBC/obcdyn_tam.F90 @ 7797

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

first import of NEMOTAM 3.2.2

  • Property svn:executable set to *
File size: 21.1 KB
Line 
1MODULE obcdyn_tam
2#if defined key_obc
3   !!=================================================================================
4   !!                       ***  MODULE  obcdyn  ***
5   !! Ocean dynamics:   Radiation of velocities on each open boundary
6   !!=================================================================================
7
8   !!---------------------------------------------------------------------------------
9   !!   obc_dyn_tan        : call the subroutine for each open boundary
10   !!   obc_dyn_east_tan   :
11   !!   obc_dyn_west_tan   :
12   !!   obc_dyn_north_tan  :
13   !!   obc_dyn_south_tan  :
14   !!   obc_dyn_adj        : call the subroutine for each open boundary
15   !!   obc_dyn_east_adj   :
16   !!   obc_dyn_west_adj   :
17   !!   obc_dyn_north_adj  :
18   !!   obc_dyn_south_adj  :
19   !!----------------------------------------------------------------------------------
20
21   !!----------------------------------------------------------------------------------
22   !! * Modules used
23   USE oce_tam,        ONLY : ub_tl, vb_tl, ua_tl, va_tl, & ! ocean dynamics and tracers
24        &                     ub_ad, vb_ad, ua_ad, va_ad
25   USE obc_oce
26   USE dom_oce         ! ocean space and time domain
27   USE phycst          ! physical constants
28   USE obc_oce         ! ocean open boundary conditions
29   USE lbclnk          ! ???
30   USE lbclnk_tam,     ONLY : lbc_lnk_adj ! ocean lateral boundary conditions (or mpp link)
31   USE lib_mpp         ! ???
32   USE in_out_manager  ! I/O manager
33   USE prtctl
34   IMPLICIT NONE
35   PRIVATE
36
37   !! * Accessibility
38   PUBLIC obc_dyn_tan ! routine called in dynspg_flt
39   PUBLIC obc_dyn_adj ! routine called in dynspg_flt
40   PUBLIC obc_dyn_adj_tst
41
42   !! * Module variables
43   INTEGER ::   ji, jj, jk     ! dummy loop indices
44   LOGICAL ::   ll_fbc
45
46   !!---------------------------------------------------------------------------------
47
48CONTAINS
49
50   SUBROUTINE obc_dyn_tan ( kt )
51      !!------------------------------------------------------------------------------
52      !!                      SUBROUTINE obc_dyn
53      !!                     ********************
54      !! ** Purpose :
55      !!      Compute  dynamics (u,v) at the open boundaries.
56      !!      if defined key_dynspg_flt:
57      !!                 this routine is called by dynspg_flt and updates
58      !!                 ua, va which are the actual velocities (not trends)
59      !!
60      !!      The logical variable lp_obc_east, and/or lp_obc_west, and/or lp_obc_north,
61      !!      and/or lp_obc_south allow the user to determine which boundary is an
62      !!      open one (must be done in the param_obc.h90 file).
63      !!
64      !! ** Reference :
65      !!      Marchesiello P., 1995, these de l'universite J. Fourier, Grenoble, France.
66      !!
67      !! History :
68      !!        !  95-03 (J.-M. Molines) Original, SPEM
69      !!        !  97-07 (G. Madec, J.-M. Molines) addition
70      !!   8.5  !  02-10 (C. Talandier, A-M. Treguier) Free surface, F90
71      !!   9.0  !  05-11  (V. Garnier) Surface pressure gradient organization
72      !!----------------------------------------------------------------------
73      !! * Arguments
74      INTEGER, INTENT( in ) ::   kt
75
76      !!----------------------------------------------------------------------
77      !!  OPA 9.0 , LOCEAN-IPSL (2005)
78      !! $Header: /home/opalod/NEMOCVSROOT/NEMO/OPA_SRC/OBC/obcdyn.F90,v 1.5 2005/12/28 09:25:07 opalod Exp $
79      !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
80      !!----------------------------------------------------------------------
81
82      ! 0. Local constant initialization
83      ! --------------------------------
84
85#if defined key_pomme_r025
86      ! Warning : TAM is available only for fixed boundary conditions (FBC)
87      ll_fbc = .true.
88#else
89      Error, OBC not ready.
90#endif
91
92# if defined key_dynspg_rl 
93      Error, this option is obsolete (suppressed after nemo_v3_2)
94# endif
95
96      IF( lp_obc_east  )   CALL obc_dyn_east_tan
97      IF( lp_obc_west  )   CALL obc_dyn_west_tan
98      IF( lp_obc_north )   CALL obc_dyn_north_tan
99      IF( lp_obc_south )   CALL obc_dyn_south_tan
100
101      IF( lk_mpp ) THEN
102         CALL lbc_lnk( ub_tl, 'U', -1. )
103         CALL lbc_lnk( vb_tl, 'V', -1. )
104         CALL lbc_lnk( ua_tl, 'U', -1. )
105         CALL lbc_lnk( va_tl, 'V', -1. )
106      ENDIF
107
108   END SUBROUTINE obc_dyn_tan
109
110   SUBROUTINE obc_dyn_adj ( kt )
111      !!------------------------------------------------------------------------------
112      !!                  ***  SUBROUTINE obc_dyn_adj  ***
113      !!             
114      !! ** Purpose :
115      !!
116      !!  History :
117      !!         !
118      !!------------------------------------------------------------------------------
119      !! * Arguments
120      INTEGER, INTENT( in ) ::   kt
121      !! * Local declaration
122      !!------------------------------------------------------------------------------
123
124#if defined key_pomme_r025
125      ! Warning : TAM is available only for fixed boundary conditions (FBC)
126      ll_fbc = .true.
127#else
128      Error, OBC not ready.
129#endif
130
131      IF( lk_mpp ) THEN
132         CALL lbc_lnk_adj( va_ad, 'V', -1. )
133         CALL lbc_lnk_adj( ua_ad, 'U', -1. )
134         CALL lbc_lnk_adj( vb_ad, 'V', -1. )
135         CALL lbc_lnk_adj( ub_ad, 'U', -1. )
136      ENDIF
137
138      IF( lp_obc_south )   CALL obc_dyn_south_adj
139      IF( lp_obc_north )   CALL obc_dyn_north_adj
140      IF( lp_obc_west  )   CALL obc_dyn_west_adj
141      IF( lp_obc_east  )   CALL obc_dyn_east_adj
142
143   END SUBROUTINE obc_dyn_adj
144
145   SUBROUTINE obc_dyn_east_tan
146      !!------------------------------------------------------------------------------
147      !!                  ***  SUBROUTINE obc_dyn_east  ***
148      !!             
149      !! ** Purpose :
150      !!      Apply the radiation algorithm on east OBC velocities ua, va using the
151      !!      phase velocities calculated in obc_rad_east subroutine in obcrad.F90 module
152      !!      If the logical lfbceast is .TRUE., there is no radiation but only fixed OBC
153      !!
154      !!  History :
155      !!         ! 95-03 (J.-M. Molines) Original from SPEM
156      !!         ! 97-07 (G. Madec, J.-M. Molines) additions
157      !!         ! 97-12 (M. Imbard) Mpp adaptation
158      !!         ! 00-06 (J.-M. Molines)
159      !!    8.5  ! 02-10 (C. Talandier, A-M. Treguier) Free surface, F90
160      !!    9.0  ! 05-11  (V. Garnier) Surface pressure gradient organization
161      !!------------------------------------------------------------------------------
162
163      ! 1. First three time steps and more if lfbceast is .TRUE.
164      !    In that case open boundary conditions are FIXED.
165      ! --------------------------------------------------------
166
167      WRITE(numout,*) 'verif passage dans obc_dyn_east_tan'
168      IF ( ll_fbc .OR. lfbceast ) THEN
169
170         ! 1.1 U zonal velocity   
171         ! --------------------
172         DO ji = nie0, nie1
173            DO jk = 1, jpkm1
174               DO jj = 1, jpj
175                  ua_tl(ji,jj,jk) = ua_tl(ji,jj,jk) * ( 1. - uemsk(jj,jk) )
176               END DO
177            END DO
178         END DO
179
180         ! 1.2 V meridional velocity
181         ! -------------------------
182         DO ji = nie0+1, nie1+1
183            DO jk = 1, jpkm1
184               DO jj = 1, jpj
185                  va_tl(ji,jj,jk) = va_tl(ji,jj,jk) * ( 1. - vemsk(jj,jk) ) 
186               END DO
187            END DO
188         END DO
189
190      ELSE
191
192         CALL ctl_stop( 'Error in obcdyn_tam : TAM is available only for fixed boundary conditions' )
193
194      END IF
195
196   END SUBROUTINE obc_dyn_east_tan
197
198   SUBROUTINE obc_dyn_east_adj
199      !!------------------------------------------------------------------------------
200      !!                  ***  SUBROUTINE obc_dyn_east_adj  ***
201      !!             
202      !! ** Purpose :
203      !!
204      !!  History :
205      !!         !
206      !!------------------------------------------------------------------------------
207      !! * Arguments
208      !! * Local declaration
209      !!------------------------------------------------------------------------------
210      WRITE(numout,*) 'verif passage dans obc_dyn_east_adj'
211
212      IF ( ll_fbc .OR. lfbceast ) THEN
213
214         ! 1.2 V meridional velocity
215         ! -------------------------
216         DO ji = nie0+1, nie1+1
217            DO jk = 1, jpkm1
218               DO jj = 1, jpj
219                  va_ad(ji,jj,jk) = va_ad(ji,jj,jk) * ( 1. - vemsk(jj,jk) ) 
220               END DO
221            END DO
222         END DO
223
224         ! 1.1 U zonal velocity   
225         ! --------------------
226         DO ji = nie0, nie1
227            DO jk = 1, jpkm1
228               DO jj = 1, jpj
229                  ua_ad(ji,jj,jk) = ua_ad(ji,jj,jk) * ( 1. - uemsk(jj,jk) )
230               END DO
231            END DO
232         END DO
233
234      ELSE
235
236         CALL ctl_stop( 'Error in obcdyn_tam : TAM is available only for fixed boundary conditions' )
237
238      END IF
239
240   END SUBROUTINE obc_dyn_east_adj
241
242   SUBROUTINE obc_dyn_west_tan
243      !!------------------------------------------------------------------------------
244      !!                  ***  SUBROUTINE obc_dyn_west  ***
245      !!                 
246      !! ** Purpose :
247      !!      Apply the radiation algorithm on west OBC velocities ua, va using the
248      !!      phase velocities calculated in obc_rad_west subroutine in obcrad.F90 module
249      !!      If the logical lfbcwest is .TRUE., there is no radiation but only fixed OBC
250      !!
251      !!  History :
252      !!         ! 95-03 (J.-M. Molines) Original from SPEM
253      !!         ! 97-07 (G. Madec, J.-M. Molines) additions
254      !!         ! 97-12 (M. Imbard) Mpp adaptation
255      !!         ! 00-06 (J.-M. Molines)
256      !!    8.5  ! 02-10 (C. Talandier, A-M. Treguier) Free surface, F90
257      !!    9.0  ! 05-11  (V. Garnier) Surface pressure gradient organization
258      !!------------------------------------------------------------------------------
259
260      ! 1. First three time steps and more if lfbcwest is .TRUE.
261      !    In that case open boundary conditions are FIXED.
262      ! --------------------------------------------------------
263
264      IF ( ll_fbc .OR. lfbcwest ) THEN
265
266         ! 1.1 U zonal velocity
267         ! ---------------------
268         DO ji = niw0, niw1
269            DO jk = 1, jpkm1
270               DO jj = 1, jpj
271                  ua_tl(ji,jj,jk) = ua_tl(ji,jj,jk) * ( 1. - uwmsk(jj,jk) ) 
272               END DO
273            END DO
274         END DO
275
276         ! 1.2 V meridional velocity
277         ! -------------------------
278         DO ji = niw0, niw1
279            DO jk = 1, jpkm1
280               DO jj = 1, jpj
281                  va_tl(ji,jj,jk) = va_tl(ji,jj,jk) * ( 1. - vwmsk(jj,jk) )
282               END DO
283            END DO
284         END DO
285
286      ELSE
287
288         CALL ctl_stop( 'Error in obcdyn_tam : TAM is available only for fixed boundary conditions' )
289
290      END IF
291
292   END SUBROUTINE obc_dyn_west_tan
293
294   SUBROUTINE obc_dyn_west_adj
295      !!------------------------------------------------------------------------------
296      !!                  ***  SUBROUTINE obc_dyn_west_adj  ***
297      !!             
298      !! ** Purpose :
299      !!
300      !!  History :
301      !!         !
302      !!------------------------------------------------------------------------------
303      !! * Arguments
304      !! * Local declaration
305      !!------------------------------------------------------------------------------
306      IF ( ll_fbc .OR. lfbcwest ) THEN
307
308         ! 1.2 V meridional velocity
309         ! -------------------------
310         DO ji = niw0, niw1
311            DO jk = 1, jpkm1
312               DO jj = 1, jpj
313                  va_ad(ji,jj,jk) = va_ad(ji,jj,jk) * ( 1. - vwmsk(jj,jk) )
314               END DO
315            END DO
316         END DO
317         ! 1.1 U zonal velocity
318         ! ---------------------
319         DO ji = niw0, niw1
320            DO jk = 1, jpkm1
321               DO jj = 1, jpj
322                  ua_ad(ji,jj,jk) = ua_ad(ji,jj,jk) * ( 1. - uwmsk(jj,jk) ) 
323               END DO
324            END DO
325         END DO
326
327      ELSE
328
329         CALL ctl_stop( 'Error in obcdyn_tam : TAM is available only for fixed boundary conditions' )
330
331      END IF
332
333   END SUBROUTINE obc_dyn_west_adj
334
335   SUBROUTINE obc_dyn_north_tan
336      !!------------------------------------------------------------------------------
337      !!                     SUBROUTINE obc_dyn_north
338      !!                    *************************
339      !! ** Purpose :
340      !!      Apply the radiation algorithm on north OBC velocities ua, va using the
341      !!      phase velocities calculated in obc_rad_north subroutine in obcrad.F90 module
342      !!      If the logical lfbcnorth is .TRUE., there is no radiation but only fixed OBC
343      !!
344      !!  History :
345      !!         ! 95-03 (J.-M. Molines) Original from SPEM
346      !!         ! 97-07 (G. Madec, J.-M. Molines) additions
347      !!         ! 97-12 (M. Imbard) Mpp adaptation
348      !!         ! 00-06 (J.-M. Molines)
349      !!    8.5  ! 02-10 (C. Talandier, A-M. Treguier) Free surface, F90
350      !!    9.0  ! 05-11  (V. Garnier) Surface pressure gradient organization
351      !!------------------------------------------------------------------------------
352
353      ! 1. First three time steps and more if lfbcnorth is .TRUE.
354      !    In that case open boundary conditions are FIXED.
355      ! ---------------------------------------------------------
356 
357        IF ( ll_fbc .OR. lfbcnorth ) THEN
358   
359         ! 1.1 U zonal velocity
360         ! --------------------
361         DO jj = njn0+1, njn1+1
362            DO jk = 1, jpkm1
363               DO ji = 1, jpi
364                  ua_tl(ji,jj,jk) = ua_tl(ji,jj,jk) * ( 1. - unmsk(ji,jk) )
365               END DO
366            END DO
367         END DO
368
369         ! 1.2 V meridional velocity
370         ! -------------------------
371         DO jj = njn0, njn1
372            DO jk = 1, jpkm1
373               DO ji = 1, jpi
374                  va_tl(ji,jj,jk)= va_tl(ji,jj,jk) * ( 1. - vnmsk(ji,jk) )
375               END DO
376            END DO
377         END DO
378
379      ELSE
380
381         CALL ctl_stop( 'Error in obcdyn_tam : TAM is available only for fixed boundary conditions' )
382
383      END IF
384
385   END SUBROUTINE obc_dyn_north_tan
386
387   SUBROUTINE obc_dyn_north_adj
388      !!------------------------------------------------------------------------------
389      !!                  ***  SUBROUTINE obc_dyn_north_adj  ***
390      !!             
391      !! ** Purpose :
392      !!
393      !!  History :
394      !!         !
395      !!------------------------------------------------------------------------------
396      !! * Arguments
397      !! * Local declaration
398      !!------------------------------------------------------------------------------
399        IF ( ll_fbc .OR. lfbcnorth ) THEN
400   
401         ! 1.2 V meridional velocity
402         ! -------------------------
403         DO jj = njn0, njn1
404            DO jk = 1, jpkm1
405               DO ji = 1, jpi
406                  va_ad(ji,jj,jk)= va_ad(ji,jj,jk) * ( 1. - vnmsk(ji,jk) )
407               END DO
408            END DO
409         END DO
410
411         ! 1.1 U zonal velocity
412         ! --------------------
413         DO jj = njn0+1, njn1+1
414            DO jk = 1, jpkm1
415               DO ji = 1, jpi
416                  ua_ad(ji,jj,jk) = ua_ad(ji,jj,jk) * ( 1. - unmsk(ji,jk) )
417               END DO
418            END DO
419         END DO
420
421      ELSE
422
423         CALL ctl_stop( 'Error in obcdyn_tam : TAM is available only for fixed boundary conditions' )
424
425      END IF
426
427   END SUBROUTINE obc_dyn_north_adj
428
429   SUBROUTINE obc_dyn_south_tan
430      !!------------------------------------------------------------------------------
431      !!                     SUBROUTINE obc_dyn_south
432      !!                    *************************
433      !! ** Purpose :
434      !!      Apply the radiation algorithm on south OBC velocities ua, va using the
435      !!      phase velocities calculated in obc_rad_south subroutine in obcrad.F90 module
436      !!      If the logical lfbcsouth is .TRUE., there is no radiation but only fixed OBC
437      !!
438      !!  History :
439      !!         ! 95-03 (J.-M. Molines) Original from SPEM
440      !!         ! 97-07 (G. Madec, J.-M. Molines) additions
441      !!         ! 97-12 (M. Imbard) Mpp adaptation
442      !!         ! 00-06 (J.-M. Molines)
443      !!    8.5  ! 02-10 (C. Talandier, A-M. Treguier) Free surface, F90
444      !!    9.0  ! 05-11  (V. Garnier) Surface pressure gradient organization
445      !!------------------------------------------------------------------------------
446
447      ! 1. First three time steps and more if lfbcsouth is .TRUE.
448      !    In that case open boundary conditions are FIXED.
449      ! ---------------------------------------------------------
450
451      IF ( ll_fbc .OR. lfbcsouth ) THEN
452     
453         ! 1.1 U zonal velocity
454         ! --------------------
455         DO jj = njs0, njs1
456            DO jk = 1, jpkm1
457               DO ji = 1, jpi
458                  ua_tl(ji,jj,jk) = ua_tl(ji,jj,jk) * ( 1. - usmsk(ji,jk) )
459               END DO
460            END DO
461         END DO
462
463         ! 1.2 V meridional velocity
464         ! -------------------------
465         DO jj = njs0, njs1
466            DO jk = 1, jpkm1
467               DO ji = 1, jpi
468                  va_tl(ji,jj,jk) = va_tl(ji,jj,jk) * ( 1. - vsmsk(ji,jk) )
469               END DO
470            END DO
471         END DO
472
473      ELSE
474
475         CALL ctl_stop( 'Error in obcdyn_tam : TAM is available only for fixed boundary conditions' )
476
477      END IF
478
479   END SUBROUTINE obc_dyn_south_tan
480
481   SUBROUTINE obc_dyn_south_adj
482      !!------------------------------------------------------------------------------
483      !!                  ***  SUBROUTINE obc_dyn_south_adj  ***
484      !!             
485      !! ** Purpose :
486      !!
487      !!  History :
488      !!         !
489      !!------------------------------------------------------------------------------
490      !! * Arguments
491      !! * Local declaration
492      !!------------------------------------------------------------------------------
493      IF ( ll_fbc .OR. lfbcsouth ) THEN
494     
495         ! 1.2 V meridional velocity
496         ! -------------------------
497         DO jj = njs0, njs1
498            DO jk = 1, jpkm1
499               DO ji = 1, jpi
500                  va_ad(ji,jj,jk) = va_ad(ji,jj,jk) * ( 1. - vsmsk(ji,jk) )
501               END DO
502            END DO
503         END DO
504
505         ! 1.1 U zonal velocity
506         ! --------------------
507         DO jj = njs0, njs1
508            DO jk = 1, jpkm1
509               DO ji = 1, jpi
510                  ua_ad(ji,jj,jk) = ua_ad(ji,jj,jk) * ( 1. - usmsk(ji,jk) )
511               END DO
512            END DO
513         END DO
514
515      ELSE
516
517         CALL ctl_stop( 'Error in obcdyn_tam : TAM is available only for fixed boundary conditions' )
518
519      END IF
520
521   END SUBROUTINE obc_dyn_south_adj
522
523
524   SUBROUTINE obc_dyn_adj_tst( kumadt )
525
526     USE gridrandom, ONLY : grid_rd_sd
527     USE tstool_tam, ONLY : prntst_adj, stdu, stdv
528     USE dotprodfld, ONLY : dot_product  ! Computes dot product for 3D and 2D fields
529
530     INTEGER, INTENT(IN) ::  kumadt        ! Output unit
531     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  &
532          zua_tlin,  zva_tlin,  zua_adin,  zva_adin, z3r
533     REAL(wp) ::  zspdx, zspdy
534     CHARACTER (LEN=14) ::  cl_name
535
536     ! ... Allocate memory
537     ALLOCATE(  zua_tlin (jpi,jpj,jpk), zva_tlin(jpi,jpj,jpk), &
538                zua_adin (jpi,jpj,jpk), zva_adin(jpi,jpj,jpk), &
539                z3r(jpi,jpj,jpk)  ) 
540     
541     ! ... Initialisations
542     zua_tlin(:,:,:) = 0.e0  ;   zua_adin(:,:,:) = 0.e0
543     zva_tlin(:,:,:) = 0.e0  ;   zva_adin(:,:,:) = 0.e0
544
545     ! ... Define random working arrays
546     CALL grid_rd_sd( 456953, z3r,  'U', 0.0_wp, stdu)
547     DO jk = 1, jpk ; DO jj = nldj, nlej ; DO ji = nldi, nlei
548        zua_tlin(ji,jj,jk) = z3r(ji,jj,jk)
549     END DO ; END DO ; END DO
550     
551     CALL grid_rd_sd( 3434334, z3r, 'V', 0.0_wp, stdv)
552     DO jk = 1, jpk ; DO jj = nldj, nlej ; DO ji = nldi, nlei
553        zva_tlin(ji,jj,jk) = z3r(ji,jj,jk)
554     END DO ; END DO ; END DO
555
556     ! ... Initialize the tangent variables
557     ua_tl(:,:,:) = zua_tlin(:,:,:)   ;   ub_tl(:,:,:) = 0.e0
558     va_tl(:,:,:) = zva_tlin(:,:,:)   ;   vb_tl(:,:,:) = 0.e0
559
560     ! ... Call the tangent routine
561     CALL obc_dyn_tan( nit000 )
562 
563     ! ... Initialize the adjoint variables
564     zua_adin(:,:,:) = 1. * ua_tl(:,:,:)
565     zva_adin(:,:,:) = 1. * va_tl(:,:,:)
566
567     ! ... Calculate the scalar product for the output
568     zspdy = DOT_PRODUCT( ua_tl, zua_adin ) &
569           + DOT_PRODUCT( va_tl, zva_adin ) 
570
571     ! ... Call the adjoint routine
572     ua_ad(:,:,:) = zua_adin(:,:,:)   ;   ub_ad(:,:,:) = 0.e0
573     va_ad(:,:,:) = zva_adin(:,:,:)   ;   vb_ad(:,:,:) = 0.e0
574
575     CALL obc_dyn_adj( nit000 )
576
577     ! ... Calculate the scalar product for the input
578     zspdx = DOT_PRODUCT( zua_tlin, ua_ad ) &
579           + DOT_PRODUCT( zva_tlin, va_ad ) 
580
581     ! ... Diagnostic write
582     !    14 char:'12345678901234'
583     cl_name =    'obcdyn_tam    '
584     CALL prntst_adj( cl_name, kumadt, zspdx, zspdy )
585
586   END SUBROUTINE obc_dyn_adj_tst
587#else
588   !!=================================================================================
589   !!                       ***  MODULE  obcdyn  ***
590   !! Ocean dynamics:   Radiation of velocities on each open boundary
591   !!=================================================================================
592CONTAINS
593   SUBROUTINE obc_dyn_tan                              ! No open boundaries ==> empty routine
594   END SUBROUTINE obc_dyn_tan
595   SUBROUTINE obc_dyn_adj                              ! No open boundaries ==> empty routine
596   END SUBROUTINE obc_dyn_adj
597   SUBROUTINE obc_dyn_adj_tst
598   END SUBROUTINE obc_dyn_adj_tst
599#endif
600
601END MODULE obcdyn_tam
Note: See TracBrowser for help on using the repository browser.