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

source: trunk/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90 @ 7698

Last change on this file since 7698 was 7698, checked in by mocavero, 7 years ago

update trunk with OpenMP parallelization

  • Property svn:keywords set to Id
File size: 20.5 KB
RevLine 
[3]1MODULE domzgr
2   !!==============================================================================
3   !!                       ***  MODULE domzgr   ***
[6140]4   !! Ocean domain : definition of the vertical coordinate system
[3]5   !!==============================================================================
[1566]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)
[2528]9   !!            8.5  ! 2002-09  (A. Bozec, G. Madec)  F90: Free form and module
10   !!             -   ! 2002-09  (A. de Miranda)  rigid-lid + islands
[1566]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
[2528]16   !!            3.3  ! 2010-11  (G. Madec) add mbk. arrays associated to the deepest ocean level
[3680]17   !!            3.4  ! 2012-08  (J. Siddorn) added Siddorn and Furner stretching function
[3764]18   !!            3.4  ! 2012-12  (R. Bourdalle-Badie and G. Reffray)  modify C1D case 
[5120]19   !!            3.6  ! 2014-11  (P. Mathiot and C. Harris) add ice shelf capabilitye 
[6152]20   !!            3.?  ! 2015-11  (H. Liu) Modifications for Wetting/Drying
[1099]21   !!----------------------------------------------------------------------
[3]22
23   !!----------------------------------------------------------------------
[7646]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
[3]27   !!---------------------------------------------------------------------
[7646]28   USE oce            ! ocean variables
29   USE dom_oce        ! ocean domain
30   USE usrdef_zgr     ! user defined vertical coordinate system
31   USE depth_e3       ! depth <=> e3
32   USE wet_dry, ONLY: ln_wd, ht_wd
[6140]33   !
[7646]34   USE in_out_manager ! I/O manager
35   USE iom            ! I/O library
36   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
37   USE lib_mpp        ! distributed memory computing library
38   USE wrk_nemo       ! Memory allocation
39   USE timing         ! Timing
[3]40
41   IMPLICIT NONE
42   PRIVATE
43
[2715]44   PUBLIC   dom_zgr        ! called by dom_init.F90
[3]45
[2715]46  !! * Substitutions
[3]47#  include "vectopt_loop_substitute.h90"
48   !!----------------------------------------------------------------------
[2715]49   !! NEMO/OPA 3.3.1 , NEMO Consortium (2011)
[1146]50   !! $Id$
[2528]51   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[3]52   !!----------------------------------------------------------------------
53CONTAINS       
54
[7646]55   SUBROUTINE dom_zgr( k_top, k_bot )
[3]56      !!----------------------------------------------------------------------
57      !!                ***  ROUTINE dom_zgr  ***
58      !!                   
[3764]59      !! ** Purpose :   set the depth of model levels and the resulting
60      !!              vertical scale factors.
[3]61      !!
[4292]62      !! ** Method  : - reference 1D vertical coordinate (gdep._1d, e3._1d)
[1099]63      !!              - read/set ocean depth and ocean levels (bathy, mbathy)
64      !!              - vertical coordinate (gdep., e3.) depending on the
65      !!                coordinate chosen :
[2528]66      !!                   ln_zco=T   z-coordinate   
[1099]67      !!                   ln_zps=T   z-coordinate with partial steps
68      !!                   ln_zco=T   s-coordinate
[3]69      !!
[1099]70      !! ** Action  :   define gdep., e3., mbathy and bathy
71      !!----------------------------------------------------------------------
[7646]72      INTEGER, DIMENSION(:,:), INTENT(out) ::   k_top, k_bot   ! ocean first and last level indices
[2528]73      !
[7698]74      INTEGER  ::   ji, jj, jk                  ! dummy loop index
[7646]75      INTEGER  ::   ioptio, ibat, ios   ! local integer
76      REAL(wp) ::   zrefdep             ! depth of the reference level (~10m)
[3]77      !!----------------------------------------------------------------------
[3294]78      !
[3764]79      IF( nn_timing == 1 )   CALL timing_start('dom_zgr')
[3294]80      !
[7646]81      IF(lwp) THEN                     ! Control print
82         WRITE(numout,*)
83         WRITE(numout,*) 'dom_zgr : vertical coordinate'
84         WRITE(numout,*) '~~~~~~~'
85      ENDIF
[454]86
[7646]87      IF( ln_linssh .AND. lwp) WRITE(numout,*) '   linear free surface: the vertical mesh does not change in time'
[4147]88
[7646]89
90      IF( ln_read_cfg ) THEN        !==  read in mesh_mask.nc file  ==!
91         IF(lwp) WRITE(numout,*)
92         IF(lwp) WRITE(numout,*) '          Read vertical mesh in ', TRIM( cn_domcfg ), ' file'
93         !
94         CALL zgr_read   ( ln_zco  , ln_zps  , ln_sco, ln_isfcav,   & 
95            &              gdept_1d, gdepw_1d, e3t_1d, e3w_1d   ,   &    ! 1D gridpoints depth
96            &              gdept_0 , gdepw_0                    ,   &    ! gridpoints depth
97            &              e3t_0   , e3u_0   , e3v_0 , e3f_0    ,   &    ! vertical scale factors
98            &              e3w_0   , e3uw_0  , e3vw_0           ,   &    ! vertical scale factors
99            &              k_top   , k_bot            )                  ! 1st & last ocean level
100         !
101      ELSE                          !==  User defined configuration  ==!
102         IF(lwp) WRITE(numout,*)
103         IF(lwp) WRITE(numout,*) '          User defined vertical mesh (usr_def_zgr)'
104         !
105         CALL usr_def_zgr( ln_zco  , ln_zps  , ln_sco, ln_isfcav,   & 
106            &              gdept_1d, gdepw_1d, e3t_1d, e3w_1d   ,   &    ! 1D gridpoints depth
107            &              gdept_0 , gdepw_0                    ,   &    ! gridpoints depth
108            &              e3t_0   , e3u_0   , e3v_0 , e3f_0    ,   &    ! vertical scale factors
109            &              e3w_0   , e3uw_0  , e3vw_0           ,   &    ! vertical scale factors
110            &              k_top   , k_bot            )                  ! 1st & last ocean level
111         !
112      ENDIF
113      !
114!!gm to be remove when removing the OLD definition of e3 scale factors so that gde3w disappears
115      ! Compute gde3w_0 (vertical sum of e3w)
[7698]116!$OMP PARALLEL
117!$OMP DO schedule(static) private(jj, ji)
118      DO jj = 1, jpj
119         DO ji = 1, jpi
120            gde3w_0(ji,jj,1) = 0.5_wp * e3w_0(ji,jj,1)
121         END DO
122      END DO
[7646]123      DO jk = 2, jpk
[7698]124!$OMP DO schedule(static) private(jj, ji)
125         DO jj = 1, jpj
126            DO ji = 1, jpi
127               gde3w_0(ji,jj,jk) = gde3w_0(ji,jj,jk-1) + e3w_0(ji,jj,jk)
128            END DO
129         END DO
[7646]130      END DO
[7698]131!$OMP END PARALLEL
[7646]132      !
[1099]133      IF(lwp) THEN                     ! Control print
[454]134         WRITE(numout,*)
[7646]135         WRITE(numout,*) '   Type of vertical coordinate (read in ', TRIM( cn_domcfg ), ' file or set in userdef_nam) :'
[6140]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
[454]140      ENDIF
141
[1099]142      ioptio = 0                       ! Check Vertical coordinate options
[3764]143      IF( ln_zco      )   ioptio = ioptio + 1
144      IF( ln_zps      )   ioptio = ioptio + 1
145      IF( ln_sco      )   ioptio = ioptio + 1
[2528]146      IF( ioptio /= 1 )   CALL ctl_stop( ' none or several vertical coordinate options used' )
[7646]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
153      !                                ! deepest/shallowest W level Above/Below ~10m
154!!gm BUG in s-coordinate this does not work!
155      zrefdep = 10._wp - 0.1_wp * MINVAL( e3w_1d )                   ! ref. depth with tolerance (10% of minimum layer thickness)
156      nlb10 = MINLOC( gdepw_1d, mask = gdepw_1d > zrefdep, dim = 1 ) ! shallowest W level Below ~10m
157      nla10 = nlb10 - 1                                              ! deepest    W level Above ~10m
158!!gm end bug
[2528]159      !
[1348]160      IF( nprint == 1 .AND. lwp )   THEN
[7646]161         WRITE(numout,*) ' MIN val k_top   ', MINVAL(   k_top(:,:) ), ' MAX ', MAXVAL( k_top(:,:) )
162         WRITE(numout,*) ' MIN val k_bot   ', MINVAL(   k_bot(:,:) ), ' MAX ', MAXVAL( k_bot(:,:) )
[4292]163         WRITE(numout,*) ' MIN val depth t ', MINVAL( gdept_0(:,:,:) ),   &
[6140]164            &                          ' w ', MINVAL( gdepw_0(:,:,:) ), '3w ', MINVAL( gde3w_0(:,:,:) )
165         WRITE(numout,*) ' MIN val e3    t ', MINVAL(   e3t_0(:,:,:) ), ' f ', MINVAL(   e3f_0(:,:,:) ),  &
166            &                          ' u ', MINVAL(   e3u_0(:,:,:) ), ' u ', MINVAL(   e3v_0(:,:,:) ),  &
167            &                          ' uw', MINVAL(  e3uw_0(:,:,:) ), ' vw', MINVAL(  e3vw_0(:,:,:)),   &
168            &                          ' w ', MINVAL(   e3w_0(:,:,:) )
[1348]169
[4292]170         WRITE(numout,*) ' MAX val depth t ', MAXVAL( gdept_0(:,:,:) ),   &
[6140]171            &                          ' w ', MAXVAL( gdepw_0(:,:,:) ), '3w ', MAXVAL( gde3w_0(:,:,:) )
172         WRITE(numout,*) ' MAX val e3    t ', MAXVAL(   e3t_0(:,:,:) ), ' f ', MAXVAL(   e3f_0(:,:,:) ),  &
173            &                          ' u ', MAXVAL(   e3u_0(:,:,:) ), ' u ', MAXVAL(   e3v_0(:,:,:) ),  &
174            &                          ' uw', MAXVAL(  e3uw_0(:,:,:) ), ' vw', MAXVAL(  e3vw_0(:,:,:) ),  &
175            &                          ' w ', MAXVAL(   e3w_0(:,:,:) )
[1348]176      ENDIF
[2528]177      !
[3294]178      IF( nn_timing == 1 )  CALL timing_stop('dom_zgr')
179      !
[3]180   END SUBROUTINE dom_zgr
181
182
[7646]183   SUBROUTINE zgr_read( ld_zco  , ld_zps  , ld_sco  , ld_isfcav,   &   ! type of vertical coordinate
184      &                 pdept_1d, pdepw_1d, pe3t_1d , pe3w_1d  ,   &   ! 1D reference vertical coordinate
185      &                 pdept , pdepw ,                            &   ! 3D t & w-points depth
186      &                 pe3t  , pe3u  , pe3v   , pe3f ,            &   ! vertical scale factors
187      &                 pe3w  , pe3uw , pe3vw         ,            &   !     -      -      -
188      &                 k_top  , k_bot    )                            ! top & bottom ocean level
189      !!---------------------------------------------------------------------
190      !!              ***  ROUTINE zgr_read  ***
[3]191      !!
[7646]192      !! ** Purpose :   Read the vertical information in the domain configuration file
[3]193      !!
194      !!----------------------------------------------------------------------
[7646]195      LOGICAL                   , INTENT(out) ::   ld_zco, ld_zps, ld_sco      ! vertical coordinate flags
196      LOGICAL                   , INTENT(out) ::   ld_isfcav                   ! under iceshelf cavity flag
197      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pdept_1d, pdepw_1d          ! 1D grid-point depth       [m]
198      REAL(wp), DIMENSION(:)    , INTENT(out) ::   pe3t_1d , pe3w_1d           ! 1D vertical scale factors [m]
199      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pdept, pdepw                ! grid-point depth          [m]
200      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3t , pe3u , pe3v , pe3f   ! vertical scale factors    [m]
201      REAL(wp), DIMENSION(:,:,:), INTENT(out) ::   pe3w , pe3uw, pe3vw         !    -       -      -
202      INTEGER , DIMENSION(:,:)  , INTENT(out) ::   k_top , k_bot               ! first & last ocean level
203      !
[7698]204      INTEGER  ::   jk, jj, ji   ! dummy loop index
[7646]205      INTEGER  ::   inum   ! local logical unit
206      REAL(WP) ::   z_zco, z_zps, z_sco, z_cav
207      REAL(wp), DIMENSION(jpi,jpj) ::   z2d   ! 2D workspace
[3]208      !!----------------------------------------------------------------------
[3294]209      !
[7646]210      IF(lwp) THEN
[3]211         WRITE(numout,*)
[7646]212         WRITE(numout,*) '   zgr_read : read the vertical coordinates in ', TRIM( cn_domcfg ), ' file'
213         WRITE(numout,*) '   ~~~~~~~~'
[3]214      ENDIF
[1099]215      !
[7646]216      CALL iom_open( cn_domcfg, inum )
[3294]217      !
[7646]218      !                          !* type of vertical coordinate
219      CALL iom_get( inum, 'ln_zco'   , z_zco )
220      CALL iom_get( inum, 'ln_zps'   , z_zps )
221      CALL iom_get( inum, 'ln_sco'   , z_sco )
222      IF( z_zco == 0._wp ) THEN   ;   ld_zco = .false.   ;   ELSE   ;   ld_zco = .true.   ;   ENDIF
223      IF( z_zps == 0._wp ) THEN   ;   ld_zps = .false.   ;   ELSE   ;   ld_zps = .true.   ;   ENDIF
224      IF( z_sco == 0._wp ) THEN   ;   ld_sco = .false.   ;   ELSE   ;   ld_sco = .true.   ;   ENDIF
[3294]225      !
[7646]226      !                          !* ocean cavities under iceshelves
227      CALL iom_get( inum, 'ln_isfcav', z_cav )
228      IF( z_cav == 0._wp ) THEN   ;   ld_isfcav = .false.   ;   ELSE   ;   ld_isfcav = .true.   ;   ENDIF
[3294]229      !
[7646]230      !                          !* vertical scale factors
231      CALL iom_get( inum, jpdom_unknown, 'e3t_1d'  , pe3t_1d  )                     ! 1D reference coordinate
232      CALL iom_get( inum, jpdom_unknown, 'e3w_1d'  , pe3w_1d  )
[1099]233      !
[7646]234      CALL iom_get( inum, jpdom_data, 'e3t_0'  , pe3t  , lrowattr=ln_use_jattr )    ! 3D coordinate
235      CALL iom_get( inum, jpdom_data, 'e3u_0'  , pe3u  , lrowattr=ln_use_jattr )
236      CALL iom_get( inum, jpdom_data, 'e3v_0'  , pe3v  , lrowattr=ln_use_jattr )
237      CALL iom_get( inum, jpdom_data, 'e3f_0'  , pe3f  , lrowattr=ln_use_jattr )
238      CALL iom_get( inum, jpdom_data, 'e3w_0'  , pe3w  , lrowattr=ln_use_jattr )
239      CALL iom_get( inum, jpdom_data, 'e3uw_0' , pe3uw , lrowattr=ln_use_jattr )
240      CALL iom_get( inum, jpdom_data, 'e3vw_0' , pe3vw , lrowattr=ln_use_jattr )
[2528]241      !
[7646]242      !                          !* depths
243      !                                   !- old depth definition (obsolescent feature)
244      IF(  iom_varid( inum, 'gdept_1d', ldstop = .FALSE. ) > 0  .AND.  &
245         & iom_varid( inum, 'gdepw_1d', ldstop = .FALSE. ) > 0  .AND.  &
246         & iom_varid( inum, 'gdept_0' , ldstop = .FALSE. ) > 0  .AND.  &
247         & iom_varid( inum, 'gdepw_0' , ldstop = .FALSE. ) > 0    ) THEN
248         CALL ctl_warn( 'zgr_read : old definition of depths and scale factors used ', & 
249            &           '           depths at t- and w-points read in the domain configuration file')
250         CALL iom_get( inum, jpdom_unknown, 'gdept_1d', pdept_1d )   
251         CALL iom_get( inum, jpdom_unknown, 'gdepw_1d', pdepw_1d )
252         CALL iom_get( inum, jpdom_data   , 'gdept_0' , pdept , lrowattr=ln_use_jattr )
253         CALL iom_get( inum, jpdom_data   , 'gdepw_0' , pdepw , lrowattr=ln_use_jattr )
[3]254         !
[7646]255      ELSE                                !- depths computed from e3. scale factors
256         CALL e3_to_depth( pe3t_1d, pe3w_1d, pdept_1d, pdepw_1d )    ! 1D reference depth
257         CALL e3_to_depth( pe3t   , pe3w   , pdept   , pdepw    )    ! 3D depths
258         IF(lwp) THEN
259            WRITE(numout,*)
260            WRITE(numout,*) '              Reference 1D z-coordinate depth and scale factors:'
261            WRITE(numout, "(9x,' level  gdept_1d  gdepw_1d  e3t_1d   e3w_1d  ')" )
262            WRITE(numout, "(10x, i4, 4f9.2)" ) ( jk, pdept_1d(jk), pdepw_1d(jk), pe3t_1d(jk), pe3w_1d(jk), jk = 1, jpk )
263         ENDIF
[3]264      ENDIF
[1099]265      !
[7646]266      !                          !* ocean top and bottom level
267      CALL iom_get( inum, jpdom_data, 'top_level'    , z2d  , lrowattr=ln_use_jattr )   ! 1st wet T-points (ISF)
[7698]268!$OMP PARALLEL DO schedule(static) private(jj, ji)
269      DO jj = 1, jpj
270         DO ji = 1, jpi
271            k_top(ji,jj) = INT( z2d(ji,jj) )
272         END DO
273      END DO
[7646]274      CALL iom_get( inum, jpdom_data, 'bottom_level' , z2d  , lrowattr=ln_use_jattr )   ! last wet T-points
[7698]275!$OMP PARALLEL DO schedule(static) private(jj, ji)
276      DO jj = 1, jpj
277         DO ji = 1, jpi
278            k_bot(ji,jj) = INT( z2d(ji,jj) )
279         END DO
280      END DO
[3294]281      !
[7646]282      ! bathymetry with orography (wetting and drying only)
283      IF( ln_wd )  CALL iom_get( inum, jpdom_data, 'ht_wd' , ht_wd  , lrowattr=ln_use_jattr )
[3294]284      !
[7646]285      CALL iom_close( inum )
[3294]286      !
[7646]287   END SUBROUTINE zgr_read
[3]288
289
[7646]290   SUBROUTINE zgr_top_bot( k_top, k_bot )
[2528]291      !!----------------------------------------------------------------------
[7646]292      !!                    ***  ROUTINE zgr_top_bot  ***
[2528]293      !!
294      !! ** Purpose :   defines the vertical index of ocean bottom (mbk. arrays)
295      !!
[7646]296      !! ** Method  :   computes from k_top and k_bot with a minimum value of 1 over land
[2528]297      !!
[7646]298      !! ** Action  :   mikt, miku, mikv :   vertical indices of the shallowest
299      !!                                     ocean level at t-, u- & v-points
300      !!                                     (min value = 1)
[2528]301      !! ** Action  :   mbkt, mbku, mbkv :   vertical indices of the deeptest
302      !!                                     ocean level at t-, u- & v-points
303      !!                                     (min value = 1 over land)
304      !!----------------------------------------------------------------------
[7646]305      INTEGER , DIMENSION(:,:), INTENT(in) ::   k_top, k_bot   ! top & bottom ocean level indices
306      !
[2528]307      INTEGER ::   ji, jj   ! dummy loop indices
[7646]308      REAL(wp), POINTER, DIMENSION(:,:) ::  zk
[2528]309      !!----------------------------------------------------------------------
310      !
[7646]311      IF( nn_timing == 1 )  CALL timing_start('zgr_top_bot')
[2715]312      !
[7646]313      CALL wrk_alloc( jpi,jpj,   zk )
[3294]314      !
[2528]315      IF(lwp) WRITE(numout,*)
[7646]316      IF(lwp) WRITE(numout,*) '    zgr_top_bot : ocean top and bottom k-index of T-, U-, V- and W-levels '
317      IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~'
[2528]318      !
[7698]319!$OMP PARALLEL
320!$OMP DO schedule(static) private(jj, ji)
321      DO jj = 1, jpj
322         DO ji = 1, jpi
323            mikt(ji,jj) = MAX( k_top(ji,jj) , 1 )    ! top    ocean k-index of T-level (=1 over land)
324            !
325            mbkt(ji,jj) = MAX( k_bot(ji,jj) , 1 )    ! bottom ocean k-index of T-level (=1 over land)
326         END DO
327      END DO
[7646]328      !                                    ! N.B.  top     k-index of W-level = mikt
329      !                                    !       bottom  k-index of W-level = mbkt+1
[7698]330!$OMP DO schedule(static) private(jj, ji)
[7646]331      DO jj = 1, jpjm1
[2528]332         DO ji = 1, jpim1
[4990]333            miku(ji,jj) = MAX(  mikt(ji+1,jj  ) , mikt(ji,jj)  )
334            mikv(ji,jj) = MAX(  mikt(ji  ,jj+1) , mikt(ji,jj)  )
335            mikf(ji,jj) = MAX(  mikt(ji  ,jj+1) , mikt(ji,jj), mikt(ji+1,jj  ), mikt(ji+1,jj+1)  )
[7646]336            !
337            mbku(ji,jj) = MIN(  mbkt(ji+1,jj  ) , mbkt(ji,jj)  )
338            mbkv(ji,jj) = MIN(  mbkt(ji  ,jj+1) , mbkt(ji,jj)  )
[4990]339         END DO
340      END DO
341      ! converte into REAL to use lbc_lnk ; impose a min value of 1 as a zero can be set in lbclnk
[7698]342!$OMP DO schedule(static) private(jj, ji)
343      DO jj = 1, jpj
344         DO ji = 1, jpi
345            zk(ji,jj) = REAL( miku(ji,jj), wp )
346         END DO
347      END DO
348!$OMP END PARALLEL
349      CALL lbc_lnk( zk, 'U', 1. )
350!$OMP PARALLEL
351!$OMP DO schedule(static) private(jj, ji)
352      DO jj = 1, jpj
353         DO ji = 1, jpi
354            miku(ji,jj) = MAX( INT( zk(ji,jj) ), 1 )
355         END DO
356      END DO
357!$OMP DO schedule(static) private(jj, ji)
358      DO jj = 1, jpj
359         DO ji = 1, jpi
360            zk(ji,jj) = REAL( mikv(ji,jj), wp )
361         END DO
362      END DO
363!$OMP END PARALLEL
364      CALL lbc_lnk( zk, 'V', 1. )
365!$OMP PARALLEL
366!$OMP DO schedule(static) private(jj, ji)
367      DO jj = 1, jpj
368         DO ji = 1, jpi
369            mikv(ji,jj) = MAX( INT( zk(ji,jj) ), 1 )
370         END DO
371      END DO
372!$OMP DO schedule(static) private(jj, ji)
373      DO jj = 1, jpj
374         DO ji = 1, jpi
375            zk(ji,jj) = REAL( mikf(ji,jj), wp )
376         END DO
377      END DO
378!$OMP END PARALLEL
379      CALL lbc_lnk( zk, 'F', 1. )
380!$OMP PARALLEL
381!$OMP DO schedule(static) private(jj, ji)
382      DO jj = 1, jpj
383         DO ji = 1, jpi
384            mikf(ji,jj) = MAX( INT( zk(ji,jj) ), 1 )
385         END DO
386      END DO
[4990]387      !
[7698]388!$OMP DO schedule(static) private(jj, ji)
389      DO jj = 1, jpj
390         DO ji = 1, jpi
391            zk(ji,jj) = REAL( mbku(ji,jj), wp )
392         END DO
393      END DO
394!$OMP END PARALLEL
395      CALL lbc_lnk( zk, 'U', 1. )
396!$OMP PARALLEL
397!$OMP DO schedule(static) private(jj, ji)
398      DO jj = 1, jpj
399         DO ji = 1, jpi
400            mbku(ji,jj) = MAX( INT( zk(ji,jj) ), 1 )
401         END DO
402      END DO
403!$OMP DO schedule(static) private(jj, ji)
404      DO jj = 1, jpj
405         DO ji = 1, jpi
406            zk(ji,jj) = REAL( mbkv(ji,jj), wp )
407         END DO
408      END DO
409!$OMP END PARALLEL
410      CALL lbc_lnk( zk, 'V', 1. )
411!$OMP PARALLEL DO schedule(static) private(jj, ji)
412      DO jj = 1, jpj
413         DO ji = 1, jpi
414            mbkv(ji,jj) = MAX( INT( zk(ji,jj) ), 1 )
415         END DO
416      END DO
[4990]417      !
[7646]418      CALL wrk_dealloc( jpi,jpj,   zk )
[4990]419      !
[7646]420      IF( nn_timing == 1 )  CALL timing_stop('zgr_top_bot')
[1099]421      !
[7646]422   END SUBROUTINE zgr_top_bot
[454]423
[3]424   !!======================================================================
425END MODULE domzgr
Note: See TracBrowser for help on using the repository browser.