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.
bdyini.F90 in branches/DEV_r1986_BDY_updates/NEMO/OPA_SRC/BDY – NEMO

source: branches/DEV_r1986_BDY_updates/NEMO/OPA_SRC/BDY/bdyini.F90 @ 2093

Last change on this file since 2093 was 2093, checked in by davestorkey, 14 years ago

Main change set.

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 20.2 KB
Line 
1MODULE bdyini
2   !!======================================================================
3   !!                       ***  MODULE  bdyini  ***
4   !! Unstructured open boundaries : initialisation
5   !!======================================================================
6   !! History :  1.0  !  2005-01  (J. Chanut, A. Sellar)  Original code
7   !!             -   !  2007-01  (D. Storkey) Update to use IOM module
8   !!             -   !  2007-01  (D. Storkey) Tidal forcing
9   !!            3.0  !  2008-04  (NEMO team)  add in the reference version
10   !!            3.3  !  2010-09  (E.O'Dea) updates for Shelf configurations
11   !!            3.3  !  2010-09  (D.Storkey) add ice boundary conditions
12   !!----------------------------------------------------------------------
13#if defined key_bdy
14   !!----------------------------------------------------------------------
15   !!   'key_bdy'                     Unstructured Open Boundary Conditions
16   !!----------------------------------------------------------------------
17   !!   bdy_init       : Initialization of unstructured open boundaries
18   !!----------------------------------------------------------------------
19   USE oce             ! ocean dynamics and tracers variables
20   USE dom_oce         ! ocean space and time domain
21   USE bdy_oce         ! unstructured open boundary conditions
22   USE bdytides        ! tides at open boundaries initialization (tide_init routine)
23   USE in_out_manager  ! I/O units
24   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
25   USE lib_mpp         ! for mpp_sum 
26   USE iom             ! I/O
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   bdy_init   ! routine called by opa.F90
32
33   !!----------------------------------------------------------------------
34   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
35   !! $Id$
36   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
37   !!---------------------------------------------------------------------------------
38
39CONTAINS
40   
41   SUBROUTINE bdy_init
42      !!----------------------------------------------------------------------
43      !!                 ***  ROUTINE bdy_init  ***
44      !!         
45      !! ** Purpose :   Initialization of the dynamics and tracer fields with
46      !!      unstructured open boundaries.
47      !!
48      !! ** Method  :  Read initialization arrays (mask, indices) to identify
49      !!               an unstructured open boundary
50      !!
51      !! ** Input   :  bdy_init.nc, input file for unstructured open boundaries
52      !!
53      !!----------------------------------------------------------------------     
54      INTEGER ::   ii, ij, ik, igrd, ib, ir   ! dummy loop indices
55      INTEGER ::   icount, icountr
56      INTEGER ::   ib_len, ibr_max
57      INTEGER ::   iw, ie, is, in 
58      INTEGER ::   inum                 ! temporary logical unit
59      INTEGER ::   id_dummy             ! temporary integers
60      INTEGER ::   igrd_start, igrd_end ! start and end of loops on igrd
61      INTEGER, DIMENSION (2)             ::   kdimsz
62      INTEGER, DIMENSION(jpbdta, jpbgrd) ::   nbidta, nbjdta   ! Index arrays: i and j indices of bdy dta
63      INTEGER, DIMENSION(jpbdta, jpbgrd) ::   nbrdta           ! Discrete distance from rim points
64      REAL(wp) :: zefl, zwfl, znfl, zsfl                       ! temporary scalars
65      REAL(wp) , DIMENSION(jpidta,jpjdta) ::   zmask           ! global domain mask
66      REAL(wp) , DIMENSION(jpbdta,1)      ::   zdta            ! temporary array
67      CHARACTER(LEN=80),DIMENSION(6)      ::   clfile
68      !!
69      NAMELIST/nambdy/filbdy_mask, filbdy_data_T, filbdy_data_U, filbdy_data_V,          &
70         &            filbdy_data_bt_T, filbdy_data_bt_U, filbdy_data_bt_V,          &
71         &            ln_bdy_tides, ln_bdy_clim, ln_bdy_vol, ln_bdy_mask,                &
72         &            ln_bdy_dyn_fla, ln_bdy_dyn_frs, ln_bdy_tra_frs,ln_bdy_ice_frs,     &
73         &            nbdy_dta, nb_rimwidth, volbdy
74
75      !!----------------------------------------------------------------------
76
77      IF(lwp) WRITE(numout,*)
78      IF(lwp) WRITE(numout,*) 'bdy_init : initialization of unstructured open boundaries'
79      IF(lwp) WRITE(numout,*) '~~~~~~~~'
80      !
81      IF( jperio /= 0 ) CALL ctl_stop( 'Cyclic or symmetric,',   &
82           ' and unstructured open boundary condition are not compatible' )
83
84#if defined key_obc
85      CALL ctl_stop( 'Straight open boundaries,',   &
86           ' and unstructured open boundaries are not compatible' )
87#endif
88
89      ! Read namelist parameters
90      ! ---------------------------
91      REWIND( numnam )
92      READ  ( numnam, nambdy )
93
94      ! control prints
95      IF(lwp) WRITE(numout,*) '         nambdy'
96
97      ! Check nbdy_dta value
98      IF(lwp) WRITE(numout,*) 'nbdy_dta =', nbdy_dta     
99      IF(lwp) WRITE(numout,*) ' '
100      SELECT CASE( nbdy_dta )
101      CASE( 0 )
102        IF(lwp) WRITE(numout,*) '         initial state used for bdy data'       
103      CASE( 1 )
104        IF(lwp) WRITE(numout,*) '         boundary data taken from file'
105      CASE DEFAULT
106        CALL ctl_stop( 'nbdy_dta must be 0 or 1' )
107      END SELECT
108
109      IF(lwp) WRITE(numout,*) ' '
110      IF(lwp) WRITE(numout,*) 'Boundary rim width for the FRS nb_rimwidth = ', nb_rimwidth
111
112      IF(lwp) WRITE(numout,*) ' '
113      IF(lwp) WRITE(numout,*) '         volbdy = ', volbdy
114
115      IF (ln_bdy_vol) THEN
116        SELECT CASE ( volbdy ) ! Check volbdy value
117        CASE( 1 )
118          IF(lwp) WRITE(numout,*) '         The total volume will be constant'
119        CASE( 0 )
120          IF(lwp) WRITE(numout,*) '         The total volume will vary according'
121          IF(lwp) WRITE(numout,*) '         to the surface E-P flux'
122        CASE DEFAULT
123          CALL ctl_stop( 'volbdy must be 0 or 1' )
124        END SELECT
125      ELSE
126        IF(lwp) WRITE(numout,*) 'No volume correction with unstructured open boundaries'
127        IF(lwp) WRITE(numout,*) ' '
128      ENDIF
129
130      IF (ln_bdy_tides) THEN
131        IF(lwp) WRITE(numout,*) ' '
132        IF(lwp) WRITE(numout,*) 'Tidal harmonic forcing at unstructured open boundaries'
133        IF(lwp) WRITE(numout,*) ' '
134      ENDIF
135
136      IF (ln_bdy_dyn_fla) THEN
137        IF(lwp) WRITE(numout,*) ' '
138        IF(lwp) WRITE(numout,*) 'Flather condition on U, V at unstructured open boundaries'
139        IF(lwp) WRITE(numout,*) ' '
140      ENDIF
141
142      IF (ln_bdy_dyn_frs) THEN
143        IF(lwp) WRITE(numout,*) ' '
144        IF(lwp) WRITE(numout,*) 'FRS condition on U and V at unstructured open boundaries'
145        IF(lwp) WRITE(numout,*) ' '
146      ENDIF
147
148      IF (ln_bdy_tra_frs) THEN
149        IF(lwp) WRITE(numout,*) ' '
150        IF(lwp) WRITE(numout,*) 'FRS condition on T & S fields at unstructured open boundaries'
151        IF(lwp) WRITE(numout,*) ' '
152      ENDIF
153
154      IF (ln_bdy_ice_frs) THEN
155        IF(lwp) WRITE(numout,*) ' '
156        IF(lwp) WRITE(numout,*) 'FRS condition on ice fields at unstructured open boundaries'
157        IF(lwp) WRITE(numout,*) ' '
158      ENDIF
159
160      ! Read tides namelist
161      ! ------------------------
162      IF( ln_bdy_tides )   CALL tide_init
163
164      ! Read arrays defining unstructured open boundaries
165      ! -------------------------------------------------
166
167      ! Read global 2D mask at T-points: bdytmask
168      ! *****************************************
169      ! bdytmask = 1  on the computational domain AND on open boundaries
170      !          = 0  elsewhere   
171 
172      IF( cp_cfg == "eel" .AND. jp_cfg == 5 ) THEN
173         zmask(         :                ,:) = 0.e0
174         zmask(jpizoom+1:jpizoom+jpiglo-2,:) = 1.e0         
175      ELSE IF ( ln_bdy_mask ) THEN
176         CALL iom_open( filbdy_mask, inum )
177         CALL iom_get ( inum, jpdom_data, 'bdy_msk', zmask(:,:) )
178         CALL iom_close( inum )
179      ELSE
180         zmask(:,:) = 1.e0
181      ENDIF
182
183      ! Save mask over local domain     
184      DO ij = 1, nlcj
185         DO ii = 1, nlci
186            bdytmask(ii,ij) = zmask( mig(ii), mjg(ij) )
187         END DO
188      END DO
189
190      ! Derive mask on U and V grid from mask on T grid
191      bdyumask(:,:) = 0.e0
192      bdyvmask(:,:) = 0.e0
193      DO ij=1, jpjm1
194         DO ii=1, jpim1
195            bdyumask(ii,ij)=bdytmask(ii,ij)*bdytmask(ii+1, ij )
196            bdyvmask(ii,ij)=bdytmask(ii,ij)*bdytmask(ii  ,ij+1) 
197         END DO
198      END DO
199
200      ! Lateral boundary conditions
201      CALL lbc_lnk( bdyumask(:,:), 'U', 1. )
202      CALL lbc_lnk( bdyvmask(:,:), 'V', 1. )
203
204      ! Read discrete distance and mapping indices
205      ! ******************************************
206      nbidta(:,:) = 0.e0
207      nbjdta(:,:) = 0.e0
208      nbrdta(:,:) = 0.e0
209
210      IF( cp_cfg == "eel" .AND. jp_cfg == 5 ) THEN
211         icount = 0
212         ! Define west boundary (from ii=2 to ii=1+nb_rimwidth):
213         DO ir = 1, nb_rimwidth         
214            DO ij = 3, jpjglo-2
215               icount=icount+1
216               nbidta(icount,:) = ir + 1 + (jpizoom-1)
217               nbjdta(icount,:) = ij + (jpjzoom-1) 
218               nbrdta(icount,:) = ir
219            END DO
220         END DO
221
222         ! Define east boundary (from ii=jpiglo-1 to ii=jpiglo-nb_rimwidth):
223         DO ir=1,nb_rimwidth         
224            DO ij=3,jpjglo-2
225               icount=icount+1
226               nbidta(icount,:) = jpiglo-ir + (jpizoom-1)
227               nbidta(icount,2) = jpiglo-ir-1 + (jpizoom-1) ! special case for u points
228               nbjdta(icount,:) = ij + (jpjzoom-1)
229               nbrdta(icount,:) = ir
230            END DO
231         END DO
232           
233      ELSE            ! Read indices and distances in unstructured boundary data files
234
235         IF( ln_bdy_tides ) THEN 
236            ! Read tides input files for preference in case there are
237            ! no bdydata files.
238            clfile(4) = TRIM(filtide)//TRIM(tide_cpt(1))//'_grid_T.nc'
239            clfile(5) = TRIM(filtide)//TRIM(tide_cpt(1))//'_grid_U.nc'
240            clfile(6) = TRIM(filtide)//TRIM(tide_cpt(1))//'_grid_V.nc'
241         ENDIF
242         IF( ln_bdy_dyn_fla .and. .not. ln_bdy_tides ) THEN
243            clfile(4) = filbdy_data_bt_T
244            clfile(5) = filbdy_data_bt_U
245            clfile(6) = filbdy_data_bt_V
246         ENDIF
247
248         IF( ln_bdy_tra_frs ) THEN
249            clfile(1) = filbdy_data_T
250            IF( .not. ln_bdy_dyn_frs ) THEN
251               clfile(2) = filbdy_data_T  ! Dummy read re read T file for sake of 6 files
252               clfile(3) = filbdy_data_T  !
253            ENDIF
254         ENDIF         
255         IF( ln_bdy_dyn_frs ) THEN
256            IF( .not. ln_bdy_tra_frs ) THEN
257               clfile(1) = filbdy_data_U ! Dummy Read
258            ENDIF
259            clfile(2) = filbdy_data_U
260            clfile(3) = filbdy_data_V 
261         ENDIF
262
263         ! how many files are we to read in?
264         IF(ln_bdy_tides .or. ln_bdy_dyn_fla) then
265             igrd_start = 4
266         ENDIF
267
268         IF(ln_bdy_tra_frs) then
269             igrd_start = 1
270         ELSEIF(ln_bdy_dyn_frs) then
271             igrd_start = 2
272         ENDIF
273
274         IF( ln_bdy_tra_frs ) then
275             igrd_end = 1
276         ENDIF
277
278         IF(ln_bdy_dyn_fla .or. ln_bdy_tides) THEN
279             igrd_end = 6
280         ELSEIF( ln_bdy_dyn_frs) THEN
281             igrd_end = 3
282         ENDIF
283
284         DO igrd = igrd_start, igrd_end
285            CALL iom_open( clfile(igrd), inum )
286            id_dummy = iom_varid( inum, 'nbidta', kdimsz=kdimsz ) 
287            IF(lwp) WRITE(numout,*) 'kdimsz : ',kdimsz
288            ib_len = kdimsz(1)
289            IF( ib_len > jpbdta) CALL ctl_stop(          &
290                'Boundary data array in file too long.', &
291                'File :', TRIM(clfile(igrd)),            &
292                'increase parameter jpbdta.' )
293
294            CALL iom_get( inum, jpdom_unknown, 'nbidta', zdta(1:ib_len,:) )
295            DO ii = 1,ib_len
296               nbidta(ii,igrd) = INT( zdta(ii,1) )
297            END DO
298            CALL iom_get( inum, jpdom_unknown, 'nbjdta', zdta(1:ib_len,:) )
299            DO ii = 1,ib_len
300              nbjdta(ii,igrd) = INT( zdta(ii,1) )
301            END DO
302            CALL iom_get ( inum, jpdom_unknown, 'nbrdta', zdta(1:ib_len,:) )
303            DO ii = 1,ib_len
304              nbrdta(ii,igrd) = INT( zdta(ii,1) )
305            END DO
306            CALL iom_close( inum )
307
308            ! Check that rimwidth in file is big enough for Frs case(barotropic is one):
309            IF( igrd < 4) then
310                ibr_max = MAXVAL( nbrdta(:,igrd) )
311                IF(lwp) WRITE(numout,*)
312                IF(lwp) WRITE(numout,*) ' Maximum rimwidth in file is ', ibr_max
313                IF(lwp) WRITE(numout,*) ' nb_rimwidth from namelist is ', nb_rimwidth
314                IF (ibr_max < nb_rimwidth) CALL ctl_stop( &
315                    'nb_rimwidth is larger than maximum rimwidth in file' )
316            ENDIF !Check igrd < 4
317            !
318         END DO
319         !
320      ENDIF 
321
322      ! Dispatch mapping indices and discrete distances on each processor
323      ! *****************************************************************
324     
325      iw = mig(1) + 1            ! if monotasking and no zoom, iw=2
326      ie = mig(1) + nlci-1 - 1   ! if monotasking and no zoom, ie=jpim1
327      is = mjg(1) + 1            ! if monotasking and no zoom, is=2
328      in = mjg(1) + nlcj-1 - 1   ! if monotasking and no zoom, in=jpjm1
329
330      DO igrd = igrd_start, igrd_end
331        icount  = 0
332        icountr = 0
333        nblen(igrd) = 0
334        nblenrim(igrd) = 0
335        nblendta(igrd) = 0
336        DO ir=1, nb_rimwidth
337          DO ib = 1, jpbdta
338          ! check if point is in local domain and equals ir
339            IF(  nbidta(ib,igrd) >= iw .AND. nbidta(ib,igrd) <= ie .AND.   &
340               & nbjdta(ib,igrd) >= is .AND. nbjdta(ib,igrd) <= in .AND.   &
341               & nbrdta(ib,igrd) == ir  ) THEN
342               !
343               icount = icount  + 1
344               !
345               IF( ir == 1 )   icountr = icountr+1
346                  IF (icount > jpbdim) THEN
347                     IF(lwp) WRITE(numout,*) 'bdy_ini: jpbdim too small'
348                     nstop = nstop + 1
349                  ELSE
350                     nbi(icount, igrd)  = nbidta(ib,igrd)- mig(1)+1
351                     nbj(icount, igrd)  = nbjdta(ib,igrd)- mjg(1)+1
352                     nbr(icount, igrd)  = nbrdta(ib,igrd)
353                     nbmap(icount,igrd) = ib
354                  ENDIF           
355               ENDIF
356            END DO
357         END DO
358         nblenrim(igrd) = icountr !: length of rim boundary data on each proc
359         nblen   (igrd) = icount  !: length of boundary data on each proc       
360      END DO 
361
362      ! Compute rim weights
363      ! -------------------
364      DO igrd = igrd_start, igrd_end
365         DO ib = 1, nblen(igrd)
366            ! tanh formulation
367            nbw(ib,igrd) = 1.- TANH( FLOAT( nbr(ib,igrd) - 1 ) *0.5 )
368            ! quadratic
369!           nbw(ib,igrd) = (FLOAT(nb_rimwidth+1-nbr(ib,igrd))/FLOAT(nb_rimwidth))**2
370            ! linear
371!           nbw(ib,igrd) =  FLOAT(nb_rimwidth+1-nbr(ib,igrd))/FLOAT(nb_rimwidth)
372         END DO
373      END DO 
374   
375      ! Mask corrections
376      ! ----------------
377      DO ik = 1, jpkm1
378         DO ij = 1, jpj
379            DO ii = 1, jpi
380               tmask(ii,ij,ik) = tmask(ii,ij,ik) * bdytmask(ii,ij)
381               umask(ii,ij,ik) = umask(ii,ij,ik) * bdyumask(ii,ij)
382               vmask(ii,ij,ik) = vmask(ii,ij,ik) * bdyvmask(ii,ij)
383               bmask(ii,ij)    = bmask(ii,ij)    * bdytmask(ii,ij)
384            END DO     
385         END DO
386      END DO
387
388      DO ik = 1, jpkm1
389         DO ij = 2, jpjm1
390            DO ii = 2, jpim1
391               fmask(ii,ij,ik) = fmask(ii,ij,ik) * bdytmask(ii,ij  ) * bdytmask(ii+1,ij  )   &
392                  &                              * bdytmask(ii,ij+1) * bdytmask(ii+1,ij+1)
393            END DO     
394         END DO
395      END DO
396
397      tmask_i (:,:) = tmask(:,:,1) * tmask_i(:,:)             
398      bdytmask(:,:) = tmask(:,:,1)
399
400      ! bdy masks and bmask are now set to zero on boundary points:
401      igrd = 1       ! In the free surface case, bmask is at T-points
402      DO ib = 1, nblenrim(igrd)     
403        bmask(nbi(ib,igrd), nbj(ib,igrd)) = 0.e0
404      END DO
405      !
406      igrd = 1
407      DO ib = 1, nblenrim(igrd)     
408        bdytmask(nbi(ib,igrd), nbj(ib,igrd)) = 0.e0
409      END DO
410      !
411      igrd = 2
412      DO ib = 1, nblenrim(igrd)
413        bdyumask(nbi(ib,igrd), nbj(ib,igrd)) = 0.e0
414      END DO
415      !
416      igrd = 3
417      DO ib = 1, nblenrim(igrd)
418        bdyvmask(nbi(ib,igrd), nbj(ib,igrd)) = 0.e0
419      END DO
420
421      ! Lateral boundary conditions
422      CALL lbc_lnk( fmask        , 'F', 1. )
423      CALL lbc_lnk( bdytmask(:,:), 'T', 1. )
424      CALL lbc_lnk( bdyumask(:,:), 'U', 1. )
425      CALL lbc_lnk( bdyvmask(:,:), 'V', 1. )
426
427      IF( ln_bdy_vol .OR. ln_bdy_dyn_fla ) THEN      ! Indices and directions of rim velocity components
428         !
429         !flagu = -1 : u component is normal to the dynamical boundary but its direction is outward
430         !flagu =  0 : u is tangential
431         !flagu =  1 : u is normal to the boundary and is direction is inward
432         icount = 0 
433         flagu(:) = 0.e0
434 
435         igrd = 2      ! u-component
436         DO ib = 1, nblenrim(igrd) 
437            zefl=bdytmask(nbi(ib,igrd)  , nbj(ib,igrd))
438            zwfl=bdytmask(nbi(ib,igrd)+1, nbj(ib,igrd))
439            IF( zefl + zwfl ==2 ) THEN
440               icount = icount +1
441            ELSE
442               flagu(ib)=-zefl+zwfl
443            ENDIF
444         END DO
445
446         !flagv = -1 : u component is normal to the dynamical boundary but its direction is outward
447         !flagv =  0 : u is tangential
448         !flagv =  1 : u is normal to the boundary and is direction is inward
449         flagv(:) = 0.e0
450
451         igrd = 3      ! v-component
452         DO ib = 1, nblenrim(igrd) 
453            znfl = bdytmask(nbi(ib,igrd), nbj(ib,igrd))
454            zsfl = bdytmask(nbi(ib,igrd), nbj(ib,igrd)+1)
455            IF( znfl + zsfl ==2 ) THEN
456               icount = icount + 1
457            ELSE
458               flagv(ib) = -znfl + zsfl
459            END IF
460         END DO
461 
462         IF( icount /= 0 ) THEN
463            IF(lwp) WRITE(numout,*)
464            IF(lwp) WRITE(numout,*) ' E R R O R : Some data velocity points,',   &
465               ' are not boundary points. Check nbi, nbj, indices.'
466            IF(lwp) WRITE(numout,*) ' ========== '
467            IF(lwp) WRITE(numout,*)
468            nstop = nstop + 1
469         ENDIF
470   
471      ENDIF
472
473      ! Compute total lateral surface for volume correction:
474      ! ----------------------------------------------------
475 
476      bdysurftot = 0.e0 
477      IF( ln_bdy_vol ) THEN 
478         igrd = 2      ! Lateral surface at U-points
479         DO ib = 1, nblenrim(igrd)
480            bdysurftot = bdysurftot + hu     (nbi(ib,igrd)  ,nbj(ib,igrd))                      &
481               &                    * e2u    (nbi(ib,igrd)  ,nbj(ib,igrd)) * ABS( flagu(ib) )   &
482               &                    * tmask_i(nbi(ib,igrd)  ,nbj(ib,igrd))                      &
483               &                    * tmask_i(nbi(ib,igrd)+1,nbj(ib,igrd))                   
484         END DO
485
486         igrd=3 ! Add lateral surface at V-points
487         DO ib = 1, nblenrim(igrd)
488            bdysurftot = bdysurftot + hv     (nbi(ib,igrd),nbj(ib,igrd)  )                      &
489               &                    * e1v    (nbi(ib,igrd),nbj(ib,igrd)  ) * ABS( flagv(ib) )   &
490               &                    * tmask_i(nbi(ib,igrd),nbj(ib,igrd)  )                      &
491               &                    * tmask_i(nbi(ib,igrd),nbj(ib,igrd)+1)
492         END DO
493
494         IF( lk_mpp )   CALL mpp_sum( bdysurftot )      ! sum over the global domain
495      END IF   
496
497      ! Initialise bdy data arrays
498      ! --------------------------
499      tbdy(:,:) = 0.e0
500      sbdy(:,:) = 0.e0
501      ubdy(:,:) = 0.e0
502      vbdy(:,:) = 0.e0
503      sshbdy(:) = 0.e0
504      ubtbdy(:) = 0.e0
505      vbtbdy(:) = 0.e0
506#if defined key_lim2
507      frld_bdy(:) = 0.e0
508      hicif_bdy(:) = 0.e0
509      hsnif_bdy(:) = 0.e0
510#endif
511
512      ! Read in tidal constituents and adjust for model start time
513      ! ----------------------------------------------------------
514      IF( ln_bdy_tides )   CALL tide_data
515      !
516   END SUBROUTINE bdy_init
517
518#else
519   !!---------------------------------------------------------------------------------
520   !!   Dummy module                                   NO unstructured open boundaries
521   !!---------------------------------------------------------------------------------
522CONTAINS
523   SUBROUTINE bdy_init      ! Dummy routine
524   END SUBROUTINE bdy_init
525#endif
526
527   !!=================================================================================
528END MODULE bdyini
Note: See TracBrowser for help on using the repository browser.