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.
Changeset 2443 for branches/nemo_v3_3_beta – NEMO

Ignore:
Timestamp:
2010-11-29T08:52:36+01:00 (13 years ago)
Author:
gm
Message:

v3.3beta: #766 share the deepest ocean level indices (mbkt, mbku & mbkv)

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r2392 r2443  
    66   !!====================================================================== 
    77   !! History :  1.0  ! 2005-10  (A. Beckmann, G. Madec)  reactivate s-coordinate  
    8    !!---------------------------------------------------------------------- 
    9    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    10    !! $Id$  
    11    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     8   !!            3.3  ! 2010-11  (G. Madec) add mbk. arrays associated to the deepest ocean level 
    129   !!---------------------------------------------------------------------- 
    1310   USE par_oce      ! ocean parameters 
     
    172169   !! masks, bathymetry 
    173170   !! --------------------------------------------------------------------- 
    174    INTEGER , PUBLIC, DIMENSION(jpi,jpj) ::   mbathy    !: number of ocean level (=0, 1, ... , jpk-1) 
    175    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   bathy     !: ocean depth (meters) 
    176    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   tmask_i   !: interior domain T-point mask 
    177    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   bmask     !: land/ocean mask of barotropic stream function 
    178  
    179    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   tmask, umask, vmask, fmask   !: land/ocean mask at T-, U-, V- and F-points 
    180  
    181    REAL(wp), PUBLIC, DIMENSION(jpiglo) ::   tpol, fpol          !: north fold mask (nperio= 3 or 4) 
     171   INTEGER , PUBLIC, DIMENSION(jpi,jpj) ::   mbathy       !: number of ocean level (=0, 1, ... , jpk-1) 
     172   INTEGER , PUBLIC, DIMENSION(jpi,jpj) ::   mbkt         !: vertical index of the bottom last T- ocean level 
     173   INTEGER , PUBLIC, DIMENSION(jpi,jpj) ::   mbku, mbkv   !: vertical index of the bottom last U- and W- ocean level 
     174   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   bathy        !: ocean depth (meters) 
     175   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   tmask_i      !: interior domain T-point mask 
     176   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   bmask        !: land/ocean mask of barotropic stream function 
     177 
     178   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   tmask, umask, vmask, fmask   !: land/ocean mask at T-, U-, V- and F-pts 
     179 
     180   REAL(wp), PUBLIC, DIMENSION(jpiglo) ::   tpol, fpol          !: north fold mask (jperio= 3 or 4) 
    182181 
    183182#if defined key_noslip_accurate 
     
    233232   END FUNCTION Agrif_CFixed 
    234233#endif 
     234   !!---------------------------------------------------------------------- 
     235   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     236   !! $Id$  
     237   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    235238   !!====================================================================== 
    236239END MODULE dom_oce 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r2436 r2443  
    1414   !!            3.0  ! 2008-06  (G. Madec)  insertion of domzgr_zps.h90 & conding style 
    1515   !!            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 
    1617   !!---------------------------------------------------------------------- 
    1718 
     
    497498      IF( .NOT.lk_c1d )   CALL zgr_bat_ctl            !   Bathymetry check  ! 
    498499      !                                               ! =================== ! 
     500      ! 
     501      !                                               ! ========================= ! 
     502                          CALL zgr_bot_level          !   level of ocean bottom   ! 
     503      !                                               ! ========================= ! 
    499504   END SUBROUTINE zgr_bat 
    500505 
     
    682687      ! 
    683688   END SUBROUTINE zgr_bat_ctl 
     689 
     690 
     691   SUBROUTINE zgr_bot_level 
     692      !!---------------------------------------------------------------------- 
     693      !!                    ***  ROUTINE zgr_bot_level  *** 
     694      !! 
     695      !! ** Purpose :   defines the vertical index of ocean bottom (mbk. arrays) 
     696      !! 
     697      !! ** Method  :   computes from mbathy with a minimum value of 1 over land 
     698      !! 
     699      !! ** Action  :   mbkt, mbku, mbkv :   vertical indices of the deeptest  
     700      !!                                     ocean level at t-, u- & v-points 
     701      !!                                     (min value = 1 over land) 
     702      !!---------------------------------------------------------------------- 
     703      INTEGER ::   ji, jj   ! dummy loop indices 
     704      REAL(wp), DIMENSION(jpi,jpj) ::   zmbk   ! 2D workspace  
     705      !!---------------------------------------------------------------------- 
     706      ! 
     707      IF(lwp) WRITE(numout,*) 
     708      IF(lwp) WRITE(numout,*) '    zgr_bot_level : ocean bottom k-index of T-, U-, V- and W-levels ' 
     709      IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~' 
     710      ! 
     711      mbkt(:,:) = MAX( mbathy(:,:) , 1 )    ! bottom k-index of T-level (=1 over land) 
     712      !                                     ! bottom k-index of W-level = mbkt+1 
     713      DO jj = 1, jpjm1                      ! bottom k-index of u- (v-) level 
     714         DO ji = 1, jpim1 
     715            mbku(ji,jj) = MIN(  mbkt(ji+1,jj  ) , mbkt(ji,jj)  ) 
     716            mbkv(ji,jj) = MIN(  mbkt(ji  ,jj+1) , mbkt(ji,jj)  ) 
     717         END DO 
     718      END DO 
     719      ! converte into REAL to use lbc_lnk ; impose a min value of 1 as a zero can be set in lbclnk  
     720      zmbk(:,:) = REAL( mbku(:,:), wp )   ;   CALL lbc_lnk(zmbk,'U',1.)   ;   mbku  (:,:) = MAX( INT( zmbk(:,:) ), 1 ) 
     721      zmbk(:,:) = REAL( mbkv(:,:), wp )   ;   CALL lbc_lnk(zmbk,'V',1.)   ;   mbkv  (:,:) = MAX( INT( zmbk(:,:) ), 1 ) 
     722      ! 
     723   END SUBROUTINE zgr_bot_level 
    684724 
    685725 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA/trabbc.F90

    r2337 r2443  
    88   !!             -   ! 2002-11 (A. Bozec)  tra_bbc_init: original code 
    99   !!            3.3  ! 2010-10 (G. Madec)  dynamical allocation + suppression of key_trabbc 
     10   !!             -   ! 2010-11 (G. Madec)  use mbkt array (deepest ocean t-level) 
    1011   !!---------------------------------------------------------------------- 
    1112 
     13   !!---------------------------------------------------------------------- 
    1214   !!   tra_bbc      : update the tracer trend at ocean bottom  
    1315   !!   tra_bbc_init : initialization of geothermal heat flux trend 
    1416   !!---------------------------------------------------------------------- 
    15    USE oce             ! ocean dynamics and active tracers 
    16    USE dom_oce         ! ocean space and time domain 
     17   USE oce             ! ocean variables 
     18   USE dom_oce         ! domain: ocean 
    1719   USE phycst          ! physical constants 
    18    USE trdmod_oce      ! ocean trends  
    19    USE trdtra      ! ocean trends  
     20   USE trdmod_oce      ! trends: ocean variables  
     21   USE trdtra          ! trends: active tracers  
    2022   USE in_out_manager  ! I/O manager 
    2123   USE prtctl          ! Print control 
     
    3234   REAL(wp)        ::   rn_geoflx_cst = 86.4e-3_wp   !  Constant value of geothermal heat flux 
    3335 
    34    INTEGER , DIMENSION(:,:), ALLOCATABLE ::   nbotlevt   ! ocean bottom level index at T-pt 
    3536   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   qgh_trd0   ! geothermal heating trend 
    3637  
     
    5758      !!       ocean bottom can be computed once and is added to the temperature 
    5859      !!       trend juste above the bottom at each time step: 
    59       !!            ta = ta + Qsf / (rau0 rcp e3T) for k= mbathy -1 
     60      !!            ta = ta + Qsf / (rau0 rcp e3T) for k= mbkt 
    6061      !!       Where Qsf is the geothermal heat flux. 
    6162      !! 
     
    6667      !!              Emile-Geay and Madec, 2009, Ocean Science. 
    6768      !!---------------------------------------------------------------------- 
    68       !! 
    6969      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    7070      !! 
    7171      INTEGER  ::   ji, jj, ik    ! dummy loop indices 
    72       REAL(wp) ::   zqgh_trd  ! geothermal heat flux trend 
     72      REAL(wp) ::   zqgh_trd      ! geothermal heat flux trend 
    7373      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ztrdt 
    7474      !!---------------------------------------------------------------------- 
    75  
     75      ! 
    7676      IF( l_trdtra )   THEN         ! Save ta and sa trends 
    7777         ALLOCATE( ztrdt(jpi,jpj,jpk) )     ;   ztrdt(:,:,:) = tsa(:,:,:,jp_tem) 
    7878      ENDIF 
    79  
     79      ! 
    8080      !                             !  Add the geothermal heat flux trend on temperature 
    8181#if defined key_vectopt_loop 
     
    8686         DO ji = 2, jpim1 
    8787#endif 
    88             ik = nbotlevt(ji,jj) 
     88            ik = mbkt(ji,jj) 
    8989            zqgh_trd = qgh_trd0(ji,jj) / fse3t(ji,jj,ik) 
    9090            tsa(ji,jj,ik,jp_tem) = tsa(ji,jj,ik,jp_tem) + zqgh_trd 
    9191         END DO 
    9292      END DO 
    93  
     93      ! 
    9494      IF( l_trdtra ) THEN        ! Save the geothermal heat flux trend for diagnostics 
    9595         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:) 
     
    117117      !! 
    118118      !! ** Action  : - read/fix the geothermal heat qgh_trd0 
    119       !!              - compute the bottom ocean level nbotlevt 
    120119      !!---------------------------------------------------------------------- 
    121120      USE iom 
     
    127126      !!---------------------------------------------------------------------- 
    128127 
    129       REWIND ( numnam )              ! Read Namelist nambbc : bottom momentum boundary condition 
    130       READ   ( numnam, nambbc ) 
     128      REWIND( numnam )                 ! Read Namelist nambbc : bottom momentum boundary condition 
     129      READ  ( numnam, nambbc ) 
    131130 
    132131      IF(lwp) THEN                     ! Control print 
     
    143142      IF( ln_trabbc ) THEN             !==  geothermal heating  ==! 
    144143         ! 
    145          ALLOCATE( nbotlevt(jpi,jpj) )    ! allocation 
    146          ALLOCATE( qgh_trd0(jpi,jpj) )      
    147          !              
    148          DO jj = 1, jpj                   ! level of the ocean bottom at T-point 
    149             DO ji = 1, jpi 
    150                nbotlevt(ji,jj) = MAX( mbathy(ji,jj)-1, 1 ) 
    151             END DO 
    152          END DO 
     144         ALLOCATE( qgh_trd0(jpi,jpj) )    ! allocation 
    153145         ! 
    154146         SELECT CASE ( nn_geoflx )        ! geothermal heat flux / (rauO * Cp) 
     
    172164         ! 
    173165      ELSE 
    174             IF(lwp) WRITE(numout,*) '      *** no geothermal heat flux' 
     166         IF(lwp) WRITE(numout,*) '      *** no geothermal heat flux' 
    175167      ENDIF 
    176168      ! 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA/trabbl.F90

    r2287 r2443  
    44   !! Ocean physics :  advective and/or diffusive bottom boundary layer scheme 
    55   !!============================================================================== 
    6    !! History :  OPA  !  1996-06  (L. Mortier)  Original code 
    7    !!            8.0  !  1997-11  (G. Madec)    Optimization 
    8    !!   NEMO     1.0  !  2002-08  (G. Madec)  free form + modules 
    9    !!             -   !  2004-01  (A. de Miranda, G. Madec, J.M. Molines ) add advective bbl 
    10    !!            3.3  !  2009-11  (G. Madec)  merge trabbl and trabbl_adv + style + optimization  
    11    !!             -   !  2010-04  (G. Madec)  Campin & Goosse advective bbl  
    12    !!             -   !  2010-06  (C. Ethe, G. Madec)  merge TRA-TRC 
     6   !! History :  OPA  ! 1996-06  (L. Mortier)  Original code 
     7   !!            8.0  ! 1997-11  (G. Madec)    Optimization 
     8   !!   NEMO     1.0  ! 2002-08  (G. Madec)  free form + modules 
     9   !!             -   ! 2004-01  (A. de Miranda, G. Madec, J.M. Molines ) add advective bbl 
     10   !!            3.3  ! 2009-11  (G. Madec)  merge trabbl and trabbl_adv + style + optimization  
     11   !!             -   ! 2010-04  (G. Madec)  Campin & Goosse advective bbl  
     12   !!             -   ! 2010-06  (C. Ethe, G. Madec)  merge TRA-TRC 
     13   !!             -   ! 2010-11  (G. Madec) add mbk. arrays associated to the deepest ocean level 
    1314   !!---------------------------------------------------------------------- 
    1415#if   defined key_trabbl   ||   defined key_esopa 
     
    2425   USE oce            ! ocean dynamics and active tracers 
    2526   USE dom_oce        ! ocean space and time domain 
    26    USE phycst         !  
     27   USE phycst         ! physical constant 
    2728   USE eosbn2         ! equation of state 
    28    USE trdmod_oce     ! ocean space and time domain 
    29    USE trdtra         ! ocean active tracers trends 
     29   USE trdmod_oce     ! trends: ocean variables 
     30   USE trdtra         ! trends: active tracers 
    3031   USE iom            ! IOM server                
    3132   USE in_out_manager ! I/O manager 
     
    3839   PUBLIC   tra_bbl       !  routine called by step.F90 
    3940   PUBLIC   tra_bbl_init  !  routine called by opa.F90 
    40    PUBLIC   tra_bbl_dif   !  routine called by tra_bbl and trc_bbl 
     41   PUBLIC   tra_bbl_dif   !  routine called by trcbbl.F90 
    4142   PUBLIC   tra_bbl_adv   !  -          -          -              - 
    42    PUBLIC   bbl           !  -          -          -              - 
     43   PUBLIC   bbl           !  routine called by trcbbl.F90 and dtadyn.F90 
    4344 
    4445# if defined key_trabbl 
     
    4849# endif 
    4950 
    50    !                                         !!* Namelist nambbl *  
    51    INTEGER , PUBLIC ::   nn_bbl_ldf = 0       !: =1   : diffusive bbl or not (=0) 
    52    INTEGER , PUBLIC ::   nn_bbl_adv = 0       !: =1/2 : advective bbl or not (=0) 
    53    !                                          !  =1 : advective bbl using the bottom ocean velocity 
    54    !                                          !  =2 :     -      -  using utr_bbl proportional to grad(rho) 
    55    REAL(wp), PUBLIC ::   rn_ahtbbl  = 1.e+3   !: along slope bbl diffusive coefficient [m2/s] 
    56    REAL(wp), PUBLIC ::   rn_gambbl  = 10.e0   !: lateral coeff. for bottom boundary layer scheme [s] 
     51   !                                           !!* Namelist nambbl *  
     52   INTEGER , PUBLIC ::   nn_bbl_ldf = 0         !: =1   : diffusive bbl or not (=0) 
     53   INTEGER , PUBLIC ::   nn_bbl_adv = 0         !: =1/2 : advective bbl or not (=0) 
     54   !                                            !  =1 : advective bbl using the bottom ocean velocity 
     55   !                                            !  =2 :     -      -  using utr_bbl proportional to grad(rho) 
     56   REAL(wp), PUBLIC ::   rn_ahtbbl  = 1.e3_wp   !: along slope bbl diffusive coefficient [m2/s] 
     57   REAL(wp), PUBLIC ::   rn_gambbl  = 10.0_wp   !: lateral coeff. for bottom boundary layer scheme [s] 
    5758 
    5859   REAL(wp), DIMENSION(jpi,jpj), PUBLIC ::   utr_bbl  , vtr_bbl   ! u- (v-) transport in the bottom boundary layer 
    5960 
    60    INTEGER , DIMENSION(jpi,jpj) ::   mbkt                   ! vertical index of the bottom ocean T-level 
    61    INTEGER , DIMENSION(jpi,jpj) ::   mbku     , mbkv        ! vertical index of the (upper) bottom ocean U/V-level 
    6261   INTEGER , DIMENSION(jpi,jpj) ::   mbku_d   , mbkv_d      ! vertical index of the "lower" bottom ocean U/V-level 
    6362   INTEGER , DIMENSION(jpi,jpj) ::   mgrhu    , mgrhv       ! = +/-1, sign of grad(H) in u-(v-)direction 
     
    7473   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    7574   !! $Id$ 
    76    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    77    !!---------------------------------------------------------------------- 
    78  
     75   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     76   !!---------------------------------------------------------------------- 
    7977CONTAINS 
    80  
    8178 
    8279   SUBROUTINE tra_bbl( kt ) 
     
    8582      !!                    
    8683      !! ** Purpose :   Compute the before tracer (t & s) trend associated  
    87       !!     with the bottom boundary layer and add it to the general trend 
    88       !!     of tracer equations. 
     84      !!              with the bottom boundary layer and add it to the general 
     85      !!              trend of tracer equations. 
    8986      !! 
    9087      !! ** Method  :   Depending on namtra_bbl namelist parameters the bbl 
     
    218215      !!                       transport proportional to the along-slope density gradient                    
    219216      !! 
    220       !! 
    221217      !! References : Beckmann, A., and R. Doscher, 1997, J. Phys.Oceanogr., 581-591. 
    222218      !!              Campin, J.-M., and H. Goosse, 1999, Tellus, 412-430. 
    223       !! 
    224219      !!----------------------------------------------------------------------   
    225220      INTEGER                              , INTENT(in   ) ::   kjpt    ! number of tracers 
     
    233228      REAL(wp) ::   zu_bbl, zv_bbl           !   -      - 
    234229      !!---------------------------------------------------------------------- 
    235  
     230      ! 
    236231      !                                                          ! =========== 
    237232      DO jn = 1, kjpt                                            ! tracer loop 
     
    547542      e1e2t_r(:,:) = 1.0 / ( e1t(:,:) * e2t(:,:) ) 
    548543       
    549       !                             !* vertical index of bottom t-, u- and v-points 
    550       DO jj = 1, jpj                      ! bottom k-index of T-level 
    551          DO ji = 1, jpi 
    552             mbkt(ji,jj) = MAX( mbathy(ji,jj) - 1, 1 ) 
     544      !                             !* vertical index of  "deep" bottom u- and v-points 
     545      DO jj = 1, jpjm1                    ! (the "shelf" bottom k-indices are mbku and mbkv) 
     546         DO ji = 1, jpim1 
     547            mbku_d(ji,jj) = MAX(  mbkt(ji+1,jj  ) , mbkt(ji,jj)  )   ! >= 1 as mbkt=1 over land 
     548            mbkv_d(ji,jj) = MAX(  mbkt(ji  ,jj+1) , mbkt(ji,jj)  ) 
    553549         END DO 
    554550      END DO 
    555       DO jj = 1, jpjm1                    ! bottom k-index of u- (v-) level (shelf and deep) 
    556          DO ji = 1, jpim1 
    557             mbku  (ji,jj) = MAX( MIN( mbathy(ji+1,jj  ), mbathy(ji,jj) ) - 1, 1 )   ! "shelf" 
    558             mbkv  (ji,jj) = MAX( MIN( mbathy(ji  ,jj+1), mbathy(ji,jj) ) - 1, 1 ) 
    559             mbku_d(ji,jj) = MAX( MAX( mbathy(ji+1,jj  ), mbathy(ji,jj) ) - 1, 1 )   ! "deep" 
    560             mbkv_d(ji,jj) = MAX( MAX( mbathy(ji  ,jj+1), mbathy(ji,jj) ) - 1, 1 ) 
    561          END DO 
    562       END DO 
    563       zmbk(:,:) = FLOAT( mbku  (:,:) )   ;   CALL lbc_lnk(zmbk,'U',1.)   ;   mbku  (:,:) = MAX( INT( zmbk(:,:) ), 1 ) 
    564       zmbk(:,:) = FLOAT( mbkv  (:,:) )   ;   CALL lbc_lnk(zmbk,'V',1.)   ;   mbkv  (:,:) = MAX( INT( zmbk(:,:) ), 1 ) 
    565       zmbk(:,:) = FLOAT( mbku_d(:,:) )   ;   CALL lbc_lnk(zmbk,'U',1.)   ;   mbku_d(:,:) = MAX( INT( zmbk(:,:) ), 1 ) 
    566       zmbk(:,:) = FLOAT( mbkv_d(:,:) )   ;   CALL lbc_lnk(zmbk,'V',1.)   ;   mbkv_d(:,:) = MAX( INT( zmbk(:,:) ), 1 ) 
     551      ! converte into REAL to use lbc_lnk ; impose a min value of 1 as a zero can be set in lbclnk  
     552      zmbk(:,:) = REAL( mbku_d(:,:), wp )   ;   CALL lbc_lnk(zmbk,'U',1.)   ;   mbku_d(:,:) = MAX( INT( zmbk(:,:) ), 1 ) 
     553      zmbk(:,:) = REAL( mbkv_d(:,:), wp )   ;   CALL lbc_lnk(zmbk,'V',1.)   ;   mbkv_d(:,:) = MAX( INT( zmbk(:,:) ), 1 ) 
    567554 
    568555                                        !* sign of grad(H) at u- and v-points 
Note: See TracChangeset for help on using the changeset viewer.