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.
domzgr.F90 in NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DOM – NEMO

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/DOM/domzgr.F90 @ 12340

Last change on this file since 12340 was 12340, checked in by acc, 4 years ago

Branch 2019/dev_r11943_MERGE_2019. This commit introduces basic do loop macro
substitution to the 2019 option 1, merge branch. These changes have been SETTE
tested. The only addition is the do_loop_substitute.h90 file in the OCE directory but
the macros defined therein are used throughout the code to replace identifiable, 2D-
and 3D- nested loop opening and closing statements with single-line alternatives. Code
indents are also adjusted accordingly.

The following explanation is taken from comments in the new header file:

This header file contains preprocessor definitions and macros used in the do-loop
substitutions introduced between version 4.0 and 4.2. The primary aim of these macros
is to assist in future applications of tiling to improve performance. This is expected
to be achieved by alternative versions of these macros in selected locations. The
initial introduction of these macros simply replaces all identifiable nested 2D- and
3D-loops with single line statements (and adjusts indenting accordingly). Do loops
are identifiable if they comform to either:

DO jk = ....

DO jj = .... DO jj = ...

DO ji = .... DO ji = ...
. OR .
. .

END DO END DO

END DO END DO

END DO

and white-space variants thereof.

Additionally, only loops with recognised jj and ji loops limits are treated; these are:
Lower limits of 1, 2 or fs_2
Upper limits of jpi, jpim1 or fs_jpim1 (for ji) or jpj, jpjm1 or fs_jpjm1 (for jj)

The macro naming convention takes the form: DO_2D_BT_LR where:

B is the Bottom offset from the PE's inner domain;
T is the Top offset from the PE's inner domain;
L is the Left offset from the PE's inner domain;
R is the Right offset from the PE's inner domain

So, given an inner domain of 2,jpim1 and 2,jpjm1, a typical example would replace:

DO jj = 2, jpj

DO ji = 1, jpim1
.
.

END DO

END DO

with:

DO_2D_01_10
.
.
END_2D

similar conventions apply to the 3D loops macros. jk loop limits are retained
through macro arguments and are not restricted. This includes the possibility of
strides for which an extra set of DO_3DS macros are defined.

In the example definition below the inner PE domain is defined by start indices of
(kIs, kJs) and end indices of (kIe, KJe)

#define DO_2D_00_00 DO jj = kJs, kJe ; DO ji = kIs, kIe
#define END_2D END DO ; END DO

TO DO:


Only conventional nested loops have been identified and replaced by this step. There are constructs such as:

DO jk = 2, jpkm1

z2d(:,:) = z2d(:,:) + e3w(:,:,jk,Kmm) * z3d(:,:,jk) * wmask(:,:,jk)

END DO

which may need to be considered.

  • Property svn:keywords set to Id
File size: 18.9 KB
Line 
1MODULE domzgr
2   !!==============================================================================
3   !!                       ***  MODULE domzgr   ***
4   !! Ocean domain : definition of the vertical coordinate system
5   !!==============================================================================
6   !! History :  OPA  ! 1995-12  (G. Madec)  Original code : s vertical coordinate
7   !!                 ! 1997-07  (G. Madec)  lbc_lnk call
8   !!                 ! 1997-04  (J.-O. Beismann)
9   !!            8.5  ! 2002-09  (A. Bozec, G. Madec)  F90: Free form and module
10   !!             -   ! 2002-09  (A. de Miranda)  rigid-lid + islands
11   !!  NEMO      1.0  ! 2003-08  (G. Madec)  F90: Free form and module
12   !!             -   ! 2005-10  (A. Beckmann)  modifications for hybrid s-ccordinates & new stretching function
13   !!            2.0  ! 2006-04  (R. Benshila, G. Madec)  add zgr_zco
14   !!            3.0  ! 2008-06  (G. Madec)  insertion of domzgr_zps.h90 & conding style
15   !!            3.2  ! 2009-07  (R. Benshila) Suppression of rigid-lid option
16   !!            3.3  ! 2010-11  (G. Madec) add mbk. arrays associated to the deepest ocean level
17   !!            3.4  ! 2012-08  (J. Siddorn) added Siddorn and Furner stretching function
18   !!            3.4  ! 2012-12  (R. Bourdalle-Badie and G. Reffray)  modify C1D case 
19   !!            3.6  ! 2014-11  (P. Mathiot and C. Harris) add ice shelf capabilitye 
20   !!            3.?  ! 2015-11  (H. Liu) Modifications for Wetting/Drying
21   !!----------------------------------------------------------------------
22
23   !!----------------------------------------------------------------------
24   !!   dom_zgr       : read or set the ocean vertical coordinate system
25   !!   zgr_read      : read the vertical information in the domain configuration file
26   !!   zgr_top_bot   : ocean top and bottom level for t-, u, and v-points with 1 as minimum value
27   !!---------------------------------------------------------------------
28   USE oce            ! ocean variables
29   USE dom_oce        ! ocean domain
30   USE usrdef_zgr     ! user defined vertical coordinate system
31   USE closea         ! closed seas
32   USE depth_e3       ! depth <=> e3
33   USE wet_dry,   ONLY: ll_wd, ssh_ref  ! Wetting and drying
34   !
35   USE in_out_manager ! I/O manager
36   USE iom            ! I/O library
37   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
38   USE lib_mpp        ! distributed memory computing library
39
40   IMPLICIT NONE
41   PRIVATE
42
43   PUBLIC   dom_zgr        ! called by dom_init.F90
44
45  !! * Substitutions
46#  include "vectopt_loop_substitute.h90"
47#  include "do_loop_substitute.h90"
48   !!----------------------------------------------------------------------
49   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
50   !! $Id$
51   !! Software governed by the CeCILL license (see ./LICENSE)
52   !!----------------------------------------------------------------------
53CONTAINS       
54
55   SUBROUTINE dom_zgr( k_top, k_bot )
56      !!----------------------------------------------------------------------
57      !!                ***  ROUTINE dom_zgr  ***
58      !!                   
59      !! ** Purpose :   set the depth of model levels and the resulting
60      !!              vertical scale factors.
61      !!
62      !! ** Method  : - reference 1D vertical coordinate (gdep._1d, e3._1d)
63      !!              - read/set ocean depth and ocean levels (bathy, mbathy)
64      !!              - vertical coordinate (gdep., e3.) depending on the
65      !!                coordinate chosen :
66      !!                   ln_zco=T   z-coordinate   
67      !!                   ln_zps=T   z-coordinate with partial steps
68      !!                   ln_zco=T   s-coordinate
69      !!
70      !! ** Action  :   define gdep., e3., mbathy and bathy
71      !!----------------------------------------------------------------------
72      INTEGER, DIMENSION(:,:), INTENT(out) ::   k_top, k_bot   ! ocean first and last level indices
73      !
74      INTEGER  ::   ji,jj,jk            ! dummy loop index
75      INTEGER  ::   ikt, ikb            ! top/bot index
76      INTEGER  ::   ioptio, ibat, ios   ! local integer
77      REAL(wp) ::   zrefdep             ! depth of the reference level (~10m)
78      !!----------------------------------------------------------------------
79      !
80      IF(lwp) THEN                     ! Control print
81         WRITE(numout,*)
82         WRITE(numout,*) 'dom_zgr : vertical coordinate'
83         WRITE(numout,*) '~~~~~~~'
84      ENDIF
85
86      IF( ln_linssh .AND. lwp) WRITE(numout,*) '   linear free surface: the vertical mesh does not change in time'
87
88
89      IF( ln_read_cfg ) THEN        !==  read in mesh_mask.nc file  ==!
90         IF(lwp) WRITE(numout,*)
91         IF(lwp) WRITE(numout,*) '   ==>>>   Read vertical mesh in ', TRIM( cn_domcfg ), ' file'
92         !
93         CALL zgr_read   ( ln_zco  , ln_zps  , ln_sco, ln_isfcav,   & 
94            &              gdept_1d, gdepw_1d, e3t_1d, e3w_1d   ,   &    ! 1D gridpoints depth
95            &              gdept_0 , gdepw_0                    ,   &    ! gridpoints depth
96            &              e3t_0   , e3u_0   , e3v_0 , e3f_0    ,   &    ! vertical scale factors
97            &              e3w_0   , e3uw_0  , e3vw_0           ,   &    ! vertical scale factors
98            &              k_top   , k_bot            )                  ! 1st & last ocean level
99            !
100      ELSE                          !==  User defined configuration  ==!
101         IF(lwp) WRITE(numout,*)
102         IF(lwp) WRITE(numout,*) '          User defined vertical mesh (usr_def_zgr)'
103         !
104         CALL usr_def_zgr( ln_zco  , ln_zps  , ln_sco, ln_isfcav,   & 
105            &              gdept_1d, gdepw_1d, e3t_1d, e3w_1d   ,   &    ! 1D gridpoints depth
106            &              gdept_0 , gdepw_0                    ,   &    ! gridpoints depth
107            &              e3t_0   , e3u_0   , e3v_0 , e3f_0    ,   &    ! vertical scale factors
108            &              e3w_0   , e3uw_0  , e3vw_0           ,   &    ! vertical scale factors
109            &              k_top   , k_bot            )                  ! 1st & last ocean level
110         !
111      ENDIF
112      !
113!!gm to be remove when removing the OLD definition of e3 scale factors so that gde3w disappears
114      ! Compute gde3w_0 (vertical sum of e3w)
115      gde3w_0(:,:,1) = 0.5_wp * e3w_0(:,:,1)
116      DO jk = 2, jpk
117         gde3w_0(:,:,jk) = gde3w_0(:,:,jk-1) + e3w_0(:,:,jk)
118      END DO
119      !
120      ! Any closed seas (defined by closea_mask > 0 in domain_cfg file) to be filled
121      ! in at runtime if ln_closea=.false.
122      IF( ln_closea ) THEN
123         IF ( ln_maskcs ) THEN
124            ! mask all the closed sea
125            CALL clo_msk( k_top, k_bot, mask_opnsea, 'mask_opensea' )
126         ELSE IF ( ln_mask_csundef ) THEN
127            ! defined closed sea are kept
128            ! mask all the undefined closed sea
129            CALL clo_msk( k_top, k_bot, mask_csundef, 'mask_csundef' )
130         END IF
131      END IF
132      !
133      IF(lwp) THEN                     ! Control print
134         WRITE(numout,*)
135         WRITE(numout,*) '   Type of vertical coordinate (read in ', TRIM( cn_domcfg ), ' file or set in userdef_nam) :'
136         WRITE(numout,*) '      z-coordinate - full steps      ln_zco    = ', ln_zco
137         WRITE(numout,*) '      z-coordinate - partial steps   ln_zps    = ', ln_zps
138         WRITE(numout,*) '      s- or hybrid z-s-coordinate    ln_sco    = ', ln_sco
139         WRITE(numout,*) '      ice shelf cavities             ln_isfcav = ', ln_isfcav
140      ENDIF
141
142      ioptio = 0                       ! Check Vertical coordinate options
143      IF( ln_zco      )   ioptio = ioptio + 1
144      IF( ln_zps      )   ioptio = ioptio + 1
145      IF( ln_sco      )   ioptio = ioptio + 1
146      IF( ioptio /= 1 )   CALL ctl_stop( ' none or several vertical coordinate options used' )
147
148
149      !                                ! top/bottom ocean level indices for t-, u- and v-points (f-point also for top)
150      CALL zgr_top_bot( k_top, k_bot )      ! with a minimum value set to 1
151      !
152      !                                ! ice shelf draft and bathymetry
153      DO_2D_11_11
154         ikt = mikt(ji,jj)
155         ikb = mbkt(ji,jj)
156         bathy  (ji,jj) = gdepw_0(ji,jj,ikb+1)
157         risfdep(ji,jj) = gdepw_0(ji,jj,ikt  )
158      END_2D
159      !
160      !                                ! deepest/shallowest W level Above/Below ~10m
161!!gm BUG in s-coordinate this does not work!
162      zrefdep = 10._wp - 0.1_wp * MINVAL( e3w_1d )                   ! ref. depth with tolerance (10% of minimum layer thickness)
163      nlb10 = MINLOC( gdepw_1d, mask = gdepw_1d > zrefdep, dim = 1 ) ! shallowest W level Below ~10m
164      nla10 = nlb10 - 1                                              ! deepest    W level Above ~10m
165!!gm end bug
166      !
167      IF( nprint == 1 .AND. lwp )   THEN
168         WRITE(numout,*) ' MIN val k_top   ', MINVAL(   k_top(:,:) ), ' MAX ', MAXVAL( k_top(:,:) )
169         WRITE(numout,*) ' MIN val k_bot   ', MINVAL(   k_bot(:,:) ), ' MAX ', MAXVAL( k_bot(:,:) )
170         WRITE(numout,*) ' MIN val depth t ', MINVAL( gdept_0(:,:,:) ),   &
171            &                          ' w ', MINVAL( gdepw_0(:,:,:) ), '3w ', MINVAL( gde3w_0(:,:,:) )
172         WRITE(numout,*) ' MIN val e3    t ', MINVAL(   e3t_0(:,:,:) ), ' f ', MINVAL(   e3f_0(:,:,:) ),  &
173            &                          ' u ', MINVAL(   e3u_0(:,:,:) ), ' u ', MINVAL(   e3v_0(:,:,:) ),  &
174            &                          ' uw', MINVAL(  e3uw_0(:,:,:) ), ' vw', MINVAL(  e3vw_0(:,:,:)),   &
175            &                          ' w ', MINVAL(   e3w_0(:,:,:) )
176
177         WRITE(numout,*) ' MAX val depth t ', MAXVAL( gdept_0(:,:,:) ),   &
178            &                          ' w ', MAXVAL( gdepw_0(:,:,:) ), '3w ', MAXVAL( gde3w_0(:,:,:) )
179         WRITE(numout,*) ' MAX val e3    t ', MAXVAL(   e3t_0(:,:,:) ), ' f ', MAXVAL(   e3f_0(:,:,:) ),  &
180            &                          ' u ', MAXVAL(   e3u_0(:,:,:) ), ' u ', MAXVAL(   e3v_0(:,:,:) ),  &
181            &                          ' uw', MAXVAL(  e3uw_0(:,:,:) ), ' vw', MAXVAL(  e3vw_0(:,:,:) ),  &
182            &                          ' w ', MAXVAL(   e3w_0(:,:,:) )
183      ENDIF
184      !
185   END SUBROUTINE dom_zgr
186
187
188   SUBROUTINE zgr_read( ld_zco  , ld_zps  , ld_sco  , ld_isfcav,   &   ! type of vertical coordinate
189      &                 pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d  ,   &   ! 1D reference vertical coordinate
190      &                 pdept , pdepw ,                            &   ! 3D t & w-points depth
191      &                 pe3t  , pe3u  , pe3v   , pe3f ,            &   ! vertical scale factors
192      &                 pe3w  , pe3uw , pe3vw         ,            &   !     -      -      -
193      &                 k_top  , k_bot    )                            ! top & bottom ocean level
194      !!---------------------------------------------------------------------
195      !!              ***  ROUTINE zgr_read  ***
196      !!
197      !! ** Purpose :   Read the vertical information in the domain configuration file
198      !!
199      !!----------------------------------------------------------------------
200      LOGICAL                   , INTENT(out) ::   ld_zco, ld_zps, ld_sco      ! vertical coordinate flags
201      LOGICAL                   , INTENT(out) ::   ld_isfcav                   ! under iceshelf cavity flag
202      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth       [m]
203      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pe3t_1d , pe3w_1d           ! 1D vertical scale factors [m]
204      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pdept, pdepw                ! grid-point depth          [m]
205      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors    [m]
206      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3w , pe3uw, pe3vw         !    -       -      -
207      INTEGER , DIMENSION(:,:)  , INTENT(out) ::   k_top , k_bot               ! first & last ocean level
208      !
209      INTEGER  ::   jk     ! dummy loop index
210      INTEGER  ::   inum   ! local logical unit
211      REAL(WP) ::   z_zco, z_zps, z_sco, z_cav
212      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D workspace
213      !!----------------------------------------------------------------------
214      !
215      IF(lwp) THEN
216         WRITE(numout,*)
217         WRITE(numout,*) '   zgr_read : read the vertical coordinates in ', TRIM( cn_domcfg ), ' file'
218         WRITE(numout,*) '   ~~~~~~~~'
219      ENDIF
220      !
221      CALL iom_open( cn_domcfg, inum )
222      !
223      !                          !* type of vertical coordinate
224      CALL iom_get( inum, 'ln_zco'   , z_zco )
225      CALL iom_get( inum, 'ln_zps'   , z_zps )
226      CALL iom_get( inum, 'ln_sco'   , z_sco )
227      IF( z_zco == 0._wp ) THEN   ;   ld_zco = .false.   ;   ELSE   ;   ld_zco = .true.   ;   ENDIF
228      IF( z_zps == 0._wp ) THEN   ;   ld_zps = .false.   ;   ELSE   ;   ld_zps = .true.   ;   ENDIF
229      IF( z_sco == 0._wp ) THEN   ;   ld_sco = .false.   ;   ELSE   ;   ld_sco = .true.   ;   ENDIF
230      !
231      !                          !* ocean cavities under iceshelves
232      CALL iom_get( inum, 'ln_isfcav', z_cav )
233      IF( z_cav == 0._wp ) THEN   ;   ld_isfcav = .false.   ;   ELSE   ;   ld_isfcav = .true.   ;   ENDIF
234      !
235      !                          !* vertical scale factors
236      CALL iom_get( inum, jpdom_unknown, 'e3t_1d'  , pe3t_1d  )                     ! 1D reference coordinate
237      CALL iom_get( inum, jpdom_unknown, 'e3w_1d'  , pe3w_1d  )
238      !
239      CALL iom_get( inum, jpdom_data, 'e3t_0'  , pe3t  , lrowattr=ln_use_jattr )    ! 3D coordinate
240      CALL iom_get( inum, jpdom_data, 'e3u_0'  , pe3u  , lrowattr=ln_use_jattr )
241      CALL iom_get( inum, jpdom_data, 'e3v_0'  , pe3v  , lrowattr=ln_use_jattr )
242      CALL iom_get( inum, jpdom_data, 'e3f_0'  , pe3f  , lrowattr=ln_use_jattr )
243      CALL iom_get( inum, jpdom_data, 'e3w_0'  , pe3w  , lrowattr=ln_use_jattr )
244      CALL iom_get( inum, jpdom_data, 'e3uw_0' , pe3uw , lrowattr=ln_use_jattr )
245      CALL iom_get( inum, jpdom_data, 'e3vw_0' , pe3vw , lrowattr=ln_use_jattr )
246      !
247      !                          !* depths
248      !                                   !- old depth definition (obsolescent feature)
249      IF(  iom_varid( inum, 'gdept_1d', ldstop = .FALSE. ) > 0  .AND.  &
250         & iom_varid( inum, 'gdepw_1d', ldstop = .FALSE. ) > 0  .AND.  &
251         & iom_varid( inum, 'gdept_0' , ldstop = .FALSE. ) > 0  .AND.  &
252         & iom_varid( inum, 'gdepw_0' , ldstop = .FALSE. ) > 0    ) THEN
253         CALL ctl_warn( 'zgr_read : old definition of depths and scale factors used ', & 
254            &           '           depths at t- and w-points read in the domain configuration file')
255         CALL iom_get( inum, jpdom_unknown, 'gdept_1d', pdept_1d )   
256         CALL iom_get( inum, jpdom_unknown, 'gdepw_1d', pdepw_1d )
257         CALL iom_get( inum, jpdom_data   , 'gdept_0' , pdept , lrowattr=ln_use_jattr )
258         CALL iom_get( inum, jpdom_data   , 'gdepw_0' , pdepw , lrowattr=ln_use_jattr )
259         !
260      ELSE                                !- depths computed from e3. scale factors
261         CALL e3_to_depth( pe3t_1d, pe3w_1d, pdept_1d, pdepw_1d )    ! 1D reference depth
262         CALL e3_to_depth( pe3t   , pe3w   , pdept   , pdepw    )    ! 3D depths
263         IF(lwp) THEN
264            WRITE(numout,*)
265            WRITE(numout,*) '              Reference 1D z-coordinate depth and scale factors:'
266            WRITE(numout, "(9x,' level  gdept_1d  gdepw_1d  e3t_1d   e3w_1d  ')" )
267            WRITE(numout, "(10x, i4, 4f9.2)" ) ( jk, pdept_1d(jk), pdepw_1d(jk), pe3t_1d(jk), pe3w_1d(jk), jk = 1, jpk )
268         ENDIF
269      ENDIF
270      !
271      !                          !* ocean top and bottom level
272      CALL iom_get( inum, jpdom_data, 'top_level'    , z2d  , lrowattr=ln_use_jattr )   ! 1st wet T-points (ISF)
273      k_top(:,:) = NINT( z2d(:,:) )
274      CALL iom_get( inum, jpdom_data, 'bottom_level' , z2d  , lrowattr=ln_use_jattr )   ! last wet T-points
275      k_bot(:,:) = NINT( z2d(:,:) )
276      !
277      ! reference depth for negative bathy (wetting and drying only)
278      IF( ll_wd )  CALL iom_get( inum,  'rn_wd_ref_depth' , ssh_ref   )
279      !
280      CALL iom_close( inum )
281      !
282   END SUBROUTINE zgr_read
283
284
285   SUBROUTINE zgr_top_bot( k_top, k_bot )
286      !!----------------------------------------------------------------------
287      !!                    ***  ROUTINE zgr_top_bot  ***
288      !!
289      !! ** Purpose :   defines the vertical index of ocean bottom (mbk. arrays)
290      !!
291      !! ** Method  :   computes from k_top and k_bot with a minimum value of 1 over land
292      !!
293      !! ** Action  :   mikt, miku, mikv :   vertical indices of the shallowest
294      !!                                     ocean level at t-, u- & v-points
295      !!                                     (min value = 1)
296      !! ** Action  :   mbkt, mbku, mbkv :   vertical indices of the deeptest
297      !!                                     ocean level at t-, u- & v-points
298      !!                                     (min value = 1 over land)
299      !!----------------------------------------------------------------------
300      INTEGER , DIMENSION(:,:), INTENT(in) ::   k_top, k_bot   ! top & bottom ocean level indices
301      !
302      INTEGER ::   ji, jj   ! dummy loop indices
303      REAL(wp), DIMENSION(jpi,jpj) ::   zk   ! workspace
304      !!----------------------------------------------------------------------
305      !
306      IF(lwp) WRITE(numout,*)
307      IF(lwp) WRITE(numout,*) '    zgr_top_bot : ocean top and bottom k-index of T-, U-, V- and W-levels '
308      IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~'
309      !
310      mikt(:,:) = MAX( k_top(:,:) , 1 )    ! top    ocean k-index of T-level (=1 over land)
311      !
312      mbkt(:,:) = MAX( k_bot(:,:) , 1 )    ! bottom ocean k-index of T-level (=1 over land)
313 
314      !                                    ! N.B.  top     k-index of W-level = mikt
315      !                                    !       bottom  k-index of W-level = mbkt+1
316      DO_2D_10_10
317         miku(ji,jj) = MAX(  mikt(ji+1,jj  ) , mikt(ji,jj)  )
318         mikv(ji,jj) = MAX(  mikt(ji  ,jj+1) , mikt(ji,jj)  )
319         mikf(ji,jj) = MAX(  mikt(ji  ,jj+1) , mikt(ji,jj), mikt(ji+1,jj  ), mikt(ji+1,jj+1)  )
320         !
321         mbku(ji,jj) = MIN(  mbkt(ji+1,jj  ) , mbkt(ji,jj)  )
322         mbkv(ji,jj) = MIN(  mbkt(ji  ,jj+1) , mbkt(ji,jj)  )
323      END_2D
324      ! converte into REAL to use lbc_lnk ; impose a min value of 1 as a zero can be set in lbclnk
325      zk(:,:) = REAL( miku(:,:), wp )   ;   CALL lbc_lnk( 'domzgr', zk, 'U', 1. )   ;   miku(:,:) = MAX( NINT( zk(:,:) ), 1 )
326      zk(:,:) = REAL( mikv(:,:), wp )   ;   CALL lbc_lnk( 'domzgr', zk, 'V', 1. )   ;   mikv(:,:) = MAX( NINT( zk(:,:) ), 1 )
327      zk(:,:) = REAL( mikf(:,:), wp )   ;   CALL lbc_lnk( 'domzgr', zk, 'F', 1. )   ;   mikf(:,:) = MAX( NINT( zk(:,:) ), 1 )
328      !
329      zk(:,:) = REAL( mbku(:,:), wp )   ;   CALL lbc_lnk( 'domzgr', zk, 'U', 1. )   ;   mbku(:,:) = MAX( NINT( zk(:,:) ), 1 )
330      zk(:,:) = REAL( mbkv(:,:), wp )   ;   CALL lbc_lnk( 'domzgr', zk, 'V', 1. )   ;   mbkv(:,:) = MAX( NINT( zk(:,:) ), 1 )
331      !
332   END SUBROUTINE zgr_top_bot
333
334   !!======================================================================
335END MODULE domzgr
Note: See TracBrowser for help on using the repository browser.