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 4007 for branches/2013/dev_r3987_METO1_MERCATOR6_OBC_BDY_merge/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90 – NEMO

Ignore:
Timestamp:
2013-08-28T10:10:35+02:00 (11 years ago)
Author:
davestorkey
Message:
  1. Bug fixes for flagu/flagv calculation in bdyini.F90.
  2. Introduce masking of derivatives in radiation velocity calculation in bdylib.F90
  3. Change relaxation term in Orlanski implementation to explicit timestepping in bdylib.F90.
  4. Remove bdyfmask (redundant).
File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3987_METO1_MERCATOR6_OBC_BDY_merge/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r3991 r4007  
    2121   !!   bdy_init       : Initialization of unstructured open boundaries 
    2222   !!---------------------------------------------------------------------- 
     23   USE wrk_nemo        ! Memory Allocation 
    2324   USE timing          ! Timing 
    2425   USE oce             ! ocean dynamics and tracers variables 
     
    9293      INTEGER :: com_east_b, com_west_b, com_south_b, com_north_b  ! Flags for boundaries receiving 
    9394      INTEGER :: iw_b(4), ie_b(4), is_b(4), in_b(4)                ! Arrays for neighbours coordinates 
     95      REAL(wp), POINTER, DIMENSION(:,:)       ::   zfmask  ! temporary fmask array excluding coastal boundary condition (shlat) 
    9496 
    9597      !! 
     
    11781180      ENDDO 
    11791181 
    1180       ! bdyfmask required for flagu, flagv calculations below even though F-points  
    1181       ! not defined for BDY grid.  
     1182      ! For the flagu/flagv calculation below we require a version of fmask without 
     1183      ! the land boundary condition (shlat) included: 
     1184      CALL wrk_alloc(jpi,jpj,zfmask)  
    11821185      DO ij = 2, jpjm1 
    11831186         DO ii = 2, jpim1 
    1184             bdyfmask(ii,ij) = bdytmask(ii,ij  ) * bdytmask(ii+1,ij  )   & 
    1185            &                * bdytmask(ii,ij+1) * bdytmask(ii+1,ij+1) 
     1187            zfmask(ii,ij) = tmask(ii,ij  ,1) * tmask(ii+1,ij  ,1)   & 
     1188           &              * tmask(ii,ij+1,1) * tmask(ii+1,ij+1,1) 
    11861189         END DO       
    11871190      END DO 
    11881191 
    11891192      ! Lateral boundary conditions 
     1193      CALL lbc_lnk( zfmask       , 'F', 1. ) 
    11901194      CALL lbc_lnk( fmask        , 'F', 1. )   ;   CALL lbc_lnk( bdytmask(:,:), 'T', 1. ) 
    11911195      CALL lbc_lnk( bdyumask(:,:), 'U', 1. )   ;   CALL lbc_lnk( bdyvmask(:,:), 'V', 1. ) 
     
    12051209            SELECT CASE( igrd ) 
    12061210               CASE( 1 ) 
    1207                   cgrid = 'T'  
    12081211                  pmask => umask(:,:,1) 
    12091212                  i_offset = 0 
    12101213               CASE( 2 )  
    1211                   cgrid = 'U' 
    12121214                  pmask => bdytmask 
    12131215                  i_offset = 1 
    12141216               CASE( 3 )  
    1215                   cgrid = 'V' 
    1216                   pmask => fmask(:,:,1) 
     1217                  pmask => zfmask(:,:) 
    12171218                  i_offset = 0 
    12181219            END SELECT  
     
    12231224               zefl = pmask(nbi+i_offset-1,nbj) 
    12241225               zwfl = pmask(nbi+i_offset,nbj) 
    1225                IF( zefl + zwfl == 2 * i_offset ) THEN 
     1226               ! This error check only works if you are using the bdyXmask arrays 
     1227               IF( i_offset == 1 .and. zefl + zwfl == 2 ) THEN 
    12261228                  icount = icount + 1 
    12271229                  IF(lwp) WRITE(numout,*) 'Problem with igrd = ',igrd,' at (global) nbi, nbj : ',mig(nbi),mjg(nbj) 
    12281230               ELSE 
    1229                   idx_bdy(ib_bdy)%flagu(ib,igrd)=-zefl+zwfl 
     1231                  idx_bdy(ib_bdy)%flagu(ib,igrd) = -zefl + zwfl 
    12301232               ENDIF 
    12311233            END DO 
    12321234            IF( icount /= 0 ) THEN 
    12331235               IF(lwp) WRITE(numout,*) 
    1234                IF(lwp) WRITE(numout,*) ' E R R O R : Some ',cgrid,' grid points,',   & 
     1236               IF(lwp) WRITE(numout,*) ' E R R O R : Some ',cgrid(igrd),' grid points,',   & 
    12351237                  ' are not boundary points (flagu calculation). Check nbi, nbj, indices for boundary set ',ib_bdy 
    12361238               IF(lwp) WRITE(numout,*) ' ========== ' 
     
    12411243 
    12421244         ! Calculate relationship of V direction to the local orientation of the boundary 
    1243          ! flagv = -1 : u component is normal to the dynamical boundary but its direction is outward 
    1244          ! flagv =  0 : u is tangential 
    1245          ! flagv =  1 : u is normal to the boundary and is direction is inward 
     1245         ! flagv = -1 : v component is normal to the dynamical boundary but its direction is outward 
     1246         ! flagv =  0 : v is tangential 
     1247         ! flagv =  1 : v is normal to the boundary and is direction is inward 
    12461248 
    12471249         DO igrd = 1,jpbgrd  
    12481250            SELECT CASE( igrd ) 
    12491251               CASE( 1 ) 
    1250                   cgrid = 'T' 
    12511252                  pmask => vmask(:,:,1) 
    12521253                  j_offset = 0 
    12531254               CASE( 2 ) 
    1254                   cgrid = 'U' 
    1255                   pmask => fmask(:,:,1) 
     1255                  pmask => zfmask(:,:) 
    12561256                  j_offset = 0 
    12571257               CASE( 3 ) 
    1258                   cgrid = 'V' 
    12591258                  pmask => bdytmask 
    12601259                  j_offset = 1 
     
    12661265               znfl = pmask(nbi,nbj+j_offset-1  ) 
    12671266               zsfl = pmask(nbi,nbj+j_offset) 
    1268                IF( znfl + zsfl == 2 * j_offset ) THEN 
     1267               ! This error check only works if you are using the bdyXmask arrays 
     1268               IF( j_offset == 1 .and. znfl + zsfl == 2 ) THEN 
    12691269                  IF(lwp) WRITE(numout,*) 'Problem with igrd = ',igrd,' at (global) nbi, nbj : ',mig(nbi),mjg(nbj) 
    12701270                  icount = icount + 1 
     
    12751275            IF( icount /= 0 ) THEN 
    12761276               IF(lwp) WRITE(numout,*) 
    1277                IF(lwp) WRITE(numout,*) ' E R R O R : Some ',cgrid,' grid points,',   & 
     1277               IF(lwp) WRITE(numout,*) ' E R R O R : Some ',cgrid(igrd),' grid points,',   & 
    12781278                  ' are not boundary points (flagv calculation). Check nbi, nbj, indices for boundary set ',ib_bdy 
    12791279               IF(lwp) WRITE(numout,*) ' ========== ' 
     
    13241324         DEALLOCATE(nbidta, nbjdta, nbrdta) 
    13251325      ENDIF 
     1326 
     1327      CALL wrk_dealloc(jpi,jpj,zfmask)  
    13261328 
    13271329      IF( nn_timing == 1 ) CALL timing_stop('bdy_init') 
Note: See TracChangeset for help on using the changeset viewer.