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 1502 for trunk/NEMO/OPA_SRC/BDY/bdydyn.F90 – NEMO

Ignore:
Timestamp:
2009-07-20T17:20:23+02:00 (15 years ago)
Author:
rblod
Message:

Update dynnxt and dynspg_ts for variable volume, see ticket #474

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/BDY/bdydyn.F90

    r1146 r1502  
    77   !!             -   !  2007-07  (D. Storkey) Move Flather implementation to separate routine. 
    88   !!            3.0  !  2008-04  (NEMO team)  add in the reference version 
     9   !!            3.2  !  2008-04  (R. Benshila) consider velocity instead of transport  
    910   !!---------------------------------------------------------------------- 
    1011#if defined key_bdy  
     
    8687         END DO  
    8788         ! 
    88          CALL lbc_lnk( ua, 'U', 1. )   ! Boundary points should be updated 
    89          CALL lbc_lnk( va, 'V', 1. )   ! 
     89         CALL lbc_lnk( ua, 'U', -1. )   ! Boundary points should be updated 
     90         CALL lbc_lnk( va, 'V', -1. )   ! 
    9091         ! 
    9192      ENDIF ! ln_bdy_dyn_frs 
     
    9697#if defined key_dynspg_exp || defined key_dynspg_ts 
    9798!! Option to use Flather with dynspg_flt not coded yet... 
    98    SUBROUTINE bdy_dyn_fla 
     99   SUBROUTINE bdy_dyn_fla( pssh ) 
    99100      !!---------------------------------------------------------------------- 
    100101      !!                 ***  SUBROUTINE bdy_dyn_fla  *** 
     
    116117      !!              continental shelf. Mem. Soc. R. Sci. Liege, Ser. 6,10, 141-164.      
    117118      !!---------------------------------------------------------------------- 
     119      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   pssh 
     120 
    118121      INTEGER  ::   ib, igrd                         ! dummy loop indices 
    119122      INTEGER  ::   ii, ij, iim1, iip1, ijm1, ijp1   ! 2D addresses 
    120123      REAL(wp) ::   zcorr                            ! Flather correction 
     124      REAL(wp) ::   zforc                            ! temporary scalar 
    121125      !!---------------------------------------------------------------------- 
    122126 
     
    127131      IF(ln_bdy_dyn_fla .OR. ln_bdy_tides) THEN ! If these are both false, then this routine does nothing.  
    128132 
    129       ! Fill temporary array with ssh data (here spgu): 
    130       igrd = 1 
    131       spgu(:,:) = 0.0 
    132       DO ib = 1, nblenrim(igrd) 
    133          ii = nbi(ib,igrd) 
    134          ij = nbj(ib,igrd) 
    135          IF( ln_bdy_dyn_fla ) spgu(ii, ij) = sshbdy(ib) 
    136          IF( ln_bdy_tides )   spgu(ii, ij) = spgu(ii, ij) + sshtide(ib) 
    137       END DO 
     133         ! Fill temporary array with ssh data (here spgu): 
     134         igrd = 1 
     135         spgu(:,:) = 0.0 
     136         DO ib = 1, nblenrim(igrd) 
     137            ii = nbi(ib,igrd) 
     138            ij = nbj(ib,igrd) 
     139            IF( ln_bdy_dyn_fla ) spgu(ii, ij) = sshbdy(ib) 
     140            IF( ln_bdy_tides )   spgu(ii, ij) = spgu(ii, ij) + sshtide(ib) 
     141         END DO 
     142         ! 
     143         igrd = 2      ! Flather bc on u-velocity;  
     144         !             ! remember that flagu=-1 if normal velocity direction is outward 
     145         !             ! I think we should rather use after ssh ? 
     146         DO ib = 1, nblenrim(igrd) 
     147            ii  = nbi(ib,igrd) 
     148            ij  = nbj(ib,igrd)  
     149            iim1 = ii + MAX( 0, INT( flagu(ib) ) )   ! T pts i-indice inside the boundary 
     150            iip1 = ii - MIN( 0, INT( flagu(ib) ) )   ! T pts i-indice outside the boundary  
     151            ! 
     152            zcorr = - flagu(ib) * SQRT( grav * hur_e(ii, ij) ) * ( pssh(iim1, ij) - spgu(iip1,ij) ) 
     153            zforc = ubtbdy(ib) + utide(ib) 
     154            ua_e(ii,ij) = zforc + zcorr * umask(ii,ij,1)  
     155         END DO 
     156         ! 
     157         igrd = 3      ! Flather bc on v-velocity 
     158         !             ! remember that flagv=-1 if normal velocity direction is outward 
     159         DO ib = 1, nblenrim(igrd) 
     160            ii  = nbi(ib,igrd) 
     161            ij  = nbj(ib,igrd)  
     162            ijm1 = ij + MAX( 0, INT( flagv(ib) ) )   ! T pts j-indice inside the boundary 
     163            ijp1 = ij - MIN( 0, INT( flagv(ib) ) )   ! T pts j-indice outside the boundary  
     164            ! 
     165            zcorr = - flagv(ib) * SQRT( grav * hvr_e(ii, ij) ) * ( pssh(ii, ijm1) - spgu(ii,ijp1) ) 
     166            zforc = vbtbdy(ib) + vtide(ib) 
     167            va_e(ii,ij) = zforc + zcorr * vmask(ii,ij,1) 
     168         END DO 
     169         CALL lbc_lnk( ua_e, 'U', 1. )   ! Boundary points should be updated 
     170         CALL lbc_lnk( va_e, 'V', 1. )   ! 
     171         ! 
     172      ENDIF ! ln_bdy_dyn_fla .or. ln_bdy_tides 
    138173      ! 
    139       igrd = 2      ! Flather bc on u-velocity;  
    140       !             ! remember that flagu=-1 if normal velocity direction is outward 
    141       !             ! I think we should rather use after ssh ? 
    142       DO ib = 1, nblenrim(igrd) 
    143          ii  = nbi(ib,igrd) 
    144          ij  = nbj(ib,igrd)  
    145          iim1 = ii + MAX( 0, INT( flagu(ib) ) )   ! T pts i-indice inside the boundary 
    146          iip1 = ii - MIN( 0, INT( flagu(ib) ) )   ! T pts i-indice outside the boundary  
    147          ! 
    148          zcorr = - flagu(ib) * SQRT( grav / (hu_e(ii, ij) + 1.e-20) ) * ( sshn_e(iim1, ij) - spgu(iip1,ij) ) 
    149          ua_e(ii, ij) = ( ubtbdy(ib) + utide(ib) ) * hu_e(ii,ij) 
    150          ua_e(ii,ij) = ua_e(ii,ij) + zcorr * umask(ii,ij,1) * hu_e(ii,ij) 
    151       END DO 
    152       ! 
    153       igrd = 3      ! Flather bc on v-velocity 
    154       !             ! remember that flagv=-1 if normal velocity direction is outward 
    155       DO ib = 1, nblenrim(igrd) 
    156          ii  = nbi(ib,igrd) 
    157          ij  = nbj(ib,igrd)  
    158          ijm1 = ij + MAX( 0, INT( flagv(ib) ) )   ! T pts j-indice inside the boundary 
    159          ijp1 = ij - MIN( 0, INT( flagv(ib) ) )   ! T pts j-indice outside the boundary  
    160          ! 
    161          zcorr = - flagv(ib) * SQRT( grav / (hv_e(ii, ij) + 1.e-20) ) * ( sshn_e(ii, ijm1) - spgu(ii,ijp1) ) 
    162          va_e(ii, ij) = ( vbtbdy(ib) + vtide(ib) ) * hv_e(ii,ij) 
    163          va_e(ii,ij) = va_e(ii,ij) + zcorr * vmask(ii,ij,1) * hv_e(ii,ij) 
    164       END DO 
    165       ! 
    166       CALL lbc_lnk( ua_e, 'U', 1. ) ! Boundary points should be updated 
    167       CALL lbc_lnk( va_e, 'V', 1. ) ! 
    168       ! 
    169       ENDIF ! ln_bdy_dyn_fla .or. ln_bdy_tides 
    170  
    171174   END SUBROUTINE bdy_dyn_fla 
    172175#endif 
Note: See TracChangeset for help on using the changeset viewer.