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 @ 2168

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

Cosmetic changes on BDY branch

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