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

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90 @ 4434

Last change on this file since 4434 was 4419, checked in by trackstand2, 10 years ago

Explicit zeroing of bdytmask array

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