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

source: trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90 @ 2715

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

First attempt to put dynamic allocation on the trunk

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