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 6125 – NEMO

Changeset 6125


Ignore:
Timestamp:
2015-12-18T13:58:12+01:00 (8 years ago)
Author:
jchanut
Message:

suppress bmask, #1648

Location:
trunk/NEMOGCM/NEMO/OPA_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r5836 r6125  
    11411141                  umask(ii,ij,ik) = umask(ii,ij,ik) * bdyumask(ii,ij) 
    11421142                  vmask(ii,ij,ik) = vmask(ii,ij,ik) * bdyvmask(ii,ij) 
    1143                   bmask(ii,ij)    = bmask(ii,ij)    * bdytmask(ii,ij) 
    11441143               END DO       
    11451144            END DO 
     
    11741173      ENDIF 
    11751174 
    1176       ! bdy masks and bmask are now set to zero on boundary points: 
    1177       igrd = 1       ! In the free surface case, bmask is at T-points 
    1178       DO ib_bdy = 1, nb_bdy 
    1179         DO ib = 1, idx_bdy(ib_bdy)%nblenrim(igrd)      
    1180           bmask(idx_bdy(ib_bdy)%nbi(ib,igrd), idx_bdy(ib_bdy)%nbj(ib,igrd)) = 0.e0 
    1181         ENDDO 
    1182       ENDDO 
     1175      ! bdy masks are now set to zero on boundary points: 
    11831176      ! 
    11841177      igrd = 1 
  • trunk/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r5930 r6125  
    253253   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bathy                              !: ocean depth (meters) 
    254254   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tmask_i, umask_i, vmask_i, fmask_i !: interior domain T-point mask 
    255    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bmask                              !: land/ocean mask of barotropic stream function 
    256255 
    257256   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   misfdep                 !: top first ocean level                (ISF) 
     
    386385      ALLOCATE( mbathy(jpi,jpj) , bathy(jpi,jpj) ,                                      & 
    387386         &     tmask_i(jpi,jpj) , umask_i(jpi,jpj), vmask_i(jpi,jpj), fmask_i(jpi,jpj), & 
    388          &     bmask  (jpi,jpj) ,                                                       & 
    389387         &     mbkt   (jpi,jpj) , mbku (jpi,jpj) , mbkv(jpi,jpj) , STAT=ierr(9) ) 
    390388 
  • trunk/NEMOGCM/NEMO/OPA_SRC/DOM/dommsk.F90

    r5930 r6125  
    5555      !! 
    5656      !! ** Purpose :   Compute land/ocean mask arrays at tracer points, hori- 
    57       !!      zontal velocity points (u & v), vorticity points (f) and baro- 
    58       !!      tropic stream function  points (b). 
     57      !!      zontal velocity points (u & v), vorticity points (f) points. 
    5958      !! 
    6059      !! ** Method  :   The ocean/land mask is computed from the basin bathy- 
     
    7473      !!                1. IF mbathy( ji ,jj) and mbathy( ji ,jj+1) 
    7574      !!                  and mbathy(ji+1,jj) and mbathy(ji+1,jj+1) >= jk. 
    76       !!      b-point : the same definition as for f-point of the first ocean 
    77       !!                level (surface level) but with 0 along coastlines. 
    7875      !!      tmask_i : interior ocean mask at t-point, i.e. excluding duplicated 
    7976      !!                rows/lines due to cyclic or North Fold boundaries as well 
     
    8986      !! 
    9087      !!      N.B. If nperio not equal to 0, the land/ocean mask arrays 
    91       !!      are defined with the proper value at lateral domain boundaries, 
    92       !!      but bmask. indeed, bmask defined the domain over which the 
    93       !!      barotropic stream function is computed. this domain cannot 
    94       !!      contain identical columns because the matrix associated with 
    95       !!      the barotropic stream function equation is then no more inverti- 
    96       !!      ble. therefore bmask is set to 0 along lateral domain boundaries 
    97       !!      even IF nperio is not zero. 
     88      !!      are defined with the proper value at lateral domain boundaries. 
    9889      !! 
    9990      !!      In case of open boundaries (lk_bdy=T): 
    10091      !!        - tmask is set to 1 on the points to be computed bay the open 
    10192      !!          boundaries routines. 
    102       !!        - bmask is  set to 0 on the open boundaries. 
    10393      !! 
    10494      !! ** Action :   tmask    : land/ocean mask at t-point (=0. or 1.) 
     
    10797      !!               fmask    : land/ocean mask at f-point (=0. or 1.) 
    10898      !!                          =rn_shlat along lateral boundaries 
    109       !!               bmask    : land/ocean mask at barotropic stream 
    110       !!                          function point (=0. or 1.) and set to 0 along lateral boundaries 
    11199      !!               tmask_i  : interior ocean mask 
    112100      !!---------------------------------------------------------------------- 
     
    254242      END DO 
    255243 
    256       ! 4. ocean/land mask for the elliptic equation 
    257       ! -------------------------------------------- 
    258       bmask(:,:) = ssmask(:,:)       ! elliptic equation is written at t-point 
    259       ! 
    260       !                               ! Boundary conditions 
    261       !                                    ! cyclic east-west : bmask must be set to 0. on rows 1 and jpi 
    262       IF( nperio == 1 .OR. nperio == 4 .OR. nperio == 6 ) THEN 
    263          bmask( 1 ,:) = 0._wp 
    264          bmask(jpi,:) = 0._wp 
    265       ENDIF 
    266       IF( nperio == 2 ) THEN               ! south symmetric :  bmask must be set to 0. on row 1 
    267          bmask(:, 1 ) = 0._wp 
    268       ENDIF 
    269       !                                    ! north fold :  
    270       IF( nperio == 3 .OR. nperio == 4 ) THEN   ! T-pt pivot : bmask set to 0. on row jpj and on half jpjglo-1 row 
    271          DO ji = 1, jpi                       
    272             ii = ji + nimpp - 1 
    273             bmask(ji,jpj-1) = bmask(ji,jpj-1) * tpol(ii) 
    274             bmask(ji,jpj  ) = 0._wp 
    275          END DO 
    276       ENDIF 
    277       IF( nperio == 5 .OR. nperio == 6 ) THEN   ! F-pt pivot and T-pt elliptic eq. : bmask set to 0. on row jpj 
    278          bmask(:,jpj) = 0._wp 
    279       ENDIF 
    280       ! 
    281       IF( lk_mpp ) THEN                    ! mpp specificities 
    282          !                                      ! bmask is set to zero on the overlap region 
    283          IF( nbondi /= -1 .AND. nbondi /= 2 )   bmask(  1 :jpreci,:) = 0._wp 
    284          IF( nbondi /=  1 .AND. nbondi /= 2 )   bmask(nlci:jpi   ,:) = 0._wp 
    285          IF( nbondj /= -1 .AND. nbondj /= 2 )   bmask(:,  1 :jprecj) = 0._wp 
    286          IF( nbondj /=  1 .AND. nbondj /= 2 )   bmask(:,nlcj:jpj   ) = 0._wp 
    287          ! 
    288          IF( npolj == 3 .OR. npolj == 4 ) THEN  ! north fold : bmask must be set to 0. on rows jpj-1 and jpj 
    289             DO ji = 1, nlci 
    290                ii = ji + nimpp - 1 
    291                bmask(ji,nlcj-1) = bmask(ji,nlcj-1) * tpol(ii) 
    292                bmask(ji,nlcj  ) = 0._wp 
    293             END DO 
    294          ENDIF 
    295          IF( npolj == 5 .OR. npolj == 6 ) THEN  ! F-pt pivot and T-pt elliptic eq. : bmask set to 0. on row jpj 
    296             DO ji = 1, nlci 
    297                bmask(ji,nlcj  ) = 0._wp 
    298             END DO 
    299          ENDIF 
    300       ENDIF 
    301  
    302244      ! Lateral boundary conditions on velocity (modify fmask) 
    303245      ! ---------------------------------------      
     
    438380               &                              1, jpj, 1, 1, numout ) 
    439381         END DO 
    440          WRITE(numout,*) 
    441          WRITE(numout,*) ' dom_msk: bmask ' 
    442          WRITE(numout,*) ' ---------------' 
    443          WRITE(numout,*) 
    444          imsk(:,:) = INT( bmask(:,:) ) 
    445          CALL prihin( imsk(:,:), jpi, jpj, 1, jpi, 1,   & 
    446             &                              1, jpj, 1, 1, numout ) 
    447382      ENDIF 
    448383      ! 
Note: See TracChangeset for help on using the changeset viewer.