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 3764 for branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90 – NEMO

Ignore:
Timestamp:
2013-01-23T15:33:04+01:00 (11 years ago)
Author:
smasson
Message:

dev_MERGE_2012: report bugfixes done in the trunk from r3555 to r3763 into dev_MERGE_2012

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r3702 r3764  
    1616   !!            3.3  ! 2010-11  (G. Madec) add mbk. arrays associated to the deepest ocean level 
    1717   !!            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   
    1819   !!---------------------------------------------------------------------- 
    1920 
     
    4041   USE lbclnk            ! ocean lateral boundary conditions (or mpp link) 
    4142   USE lib_mpp           ! distributed memory computing library 
    42    USE wrk_nemo        ! Memory allocation 
    43    USE timing          ! Timing 
     43   USE wrk_nemo          ! Memory allocation 
     44   USE timing            ! Timing 
    4445 
    4546   IMPLICIT NONE 
     
    8485      !!                ***  ROUTINE dom_zgr  *** 
    8586      !!                    
    86       !! ** Purpose :  set the depth of model levels and the resulting  
    87       !!      vertical scale factors. 
     87      !! ** Purpose :   set the depth of model levels and the resulting  
     88      !!              vertical scale factors. 
    8889      !! 
    8990      !! ** Method  : - reference 1D vertical coordinate (gdep._0, e3._0) 
     
    9798      !! ** Action  :   define gdep., e3., mbathy and bathy 
    9899      !!---------------------------------------------------------------------- 
    99       INTEGER ::   ioptio = 0   ! temporary integer 
     100      INTEGER ::   ioptio, ibat   ! local integer 
    100101      ! 
    101102      NAMELIST/namzgr/ ln_zco, ln_zps, ln_sco 
    102103      !!---------------------------------------------------------------------- 
    103104      ! 
    104       IF( nn_timing == 1 )  CALL timing_start('dom_zgr') 
     105      IF( nn_timing == 1 )   CALL timing_start('dom_zgr') 
    105106      ! 
    106107      REWIND( numnam )                 ! Read Namelist namzgr : vertical coordinate' 
     
    118119 
    119120      ioptio = 0                       ! Check Vertical coordinate options 
    120       IF( ln_zco ) ioptio = ioptio + 1 
    121       IF( ln_zps ) ioptio = ioptio + 1 
    122       IF( ln_sco ) ioptio = ioptio + 1 
     121      IF( ln_zco      )  ioptio = ioptio + 1 
     122      IF( ln_zps      )  ioptio = ioptio + 1 
     123      IF( ln_sco      )  ioptio = ioptio + 1 
    123124      IF( ioptio /= 1 )   CALL ctl_stop( ' none or several vertical coordinate options used' ) 
    124125      ! 
     
    127128                          CALL zgr_z            ! Reference z-coordinate system (always called) 
    128129                          CALL zgr_bat          ! Bathymetry fields (levels and meters) 
     130      IF( lk_c1d      )   CALL lbc_lnk( bathy , 'T', 1._wp )   ! 1D config.: same bathy value over the 3x3 domain 
    129131      IF( ln_zco      )   CALL zgr_zco          ! z-coordinate 
    130132      IF( ln_zps      )   CALL zgr_zps          ! Partial step z-coordinate 
     
    134136      ! ----------------------------------- 
    135137      IF( lzoom       )   CALL zgr_bat_zoom     ! correct mbathy in case of zoom subdomain 
    136       IF( .NOT.lk_c1d )   CALL zgr_bat_ctl      ! check bathymetry (mbathy) and suppress isoated ocean points 
     138      IF( .NOT.lk_c1d )   CALL zgr_bat_ctl      ! check bathymetry (mbathy) and suppress isolated ocean points 
    137139                          CALL zgr_bot_level    ! deepest ocean level for t-, u- and v-points 
    138140      ! 
    139       ! 
    140  
     141      IF( lk_c1d ) THEN                         ! 1D config.: same mbathy value over the 3x3 domain 
     142         ibat = mbathy(2,2) 
     143         mbathy(:,:) = ibat 
     144      END IF 
     145      ! 
    141146      IF( nprint == 1 .AND. lwp )   THEN 
    142147         WRITE(numout,*) ' MIN val mbathy ', MINVAL( mbathy(:,:) ), ' MAX ', MAXVAL( mbathy(:,:) ) 
     
    478483                    END DO 
    479484                 END DO 
    480                  IF(lwp) WRITE(numout,*) 
     485                 IF(lwp) WRITE(numout,*)      
    481486                 IF(lwp) WRITE(numout,*) '      orca_r2: Gibraltar strait open at i=',ii0,' j=',ij0 
    482487                 ! 
     
    742747      ! 
    743748      mbkt(:,:) = MAX( mbathy(:,:) , 1 )    ! bottom k-index of T-level (=1 over land) 
     749  
    744750      !                                     ! bottom k-index of W-level = mbkt+1 
    745751      DO jj = 1, jpjm1                      ! bottom k-index of u- (v-) level 
     
    12201226         END DO 
    12211227         ! 
    1222          ! Apply lateral boundary condition   CAUTION: kept the value when the lbc field is zero 
     1228         ! Apply lateral boundary condition   CAUTION: keep the value when the lbc field is zero 
    12231229         ztmp(:,:) = zenv(:,:)   ;   CALL lbc_lnk( zenv, 'T', 1._wp ) 
    12241230         DO jj = 1, nlcj 
     
    12311237      !                                                     ! ================ ! 
    12321238      ! 
    1233       !                                        ! envelop bathymetry saved in hbatt 
     1239      ! Fill ghost rows with appropriate values to avoid undefined e3 values with some mpp decompositions 
     1240      DO ji = nlci+1, jpi  
     1241         zenv(ji,1:nlcj) = zenv(nlci,1:nlcj) 
     1242      END DO 
     1243      ! 
     1244      DO jj = nlcj+1, jpj 
     1245         zenv(:,jj) = zenv(:,nlcj) 
     1246      END DO 
     1247      ! 
     1248      ! Envelope bathymetry saved in hbatt 
    12341249      hbatt(:,:) = zenv(:,:)  
    12351250      IF( MINVAL( gphit(:,:) ) * MAXVAL( gphit(:,:) ) <= 0._wp ) THEN 
Note: See TracChangeset for help on using the changeset viewer.