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 12822 for NEMO/branches/2020/dev_r12527_Gurvan_ShallowWater/src/SWE/domain.F90 – NEMO

Ignore:
Timestamp:
2020-04-28T11:10:38+02:00 (4 years ago)
Author:
gm
Message:

symmetric sterss tensor and half cell modifications (wet point only, ghost cells)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12527_Gurvan_ShallowWater/src/SWE/domain.F90

    r12614 r12822  
    4444   USE lbclnk         ! ocean lateral boundary condition (or mpp link) 
    4545   USE lib_mpp        ! distributed memory computing library 
    46  
     46!!an45 
     47!   USE usrdef_nam, ONLY : ln_45machin 
     48   ! 
    4749   IMPLICIT NONE 
    4850   PRIVATE 
     
    5052   PUBLIC   dom_init     ! called by nemogcm.F90 
    5153   PUBLIC   domain_cfg   ! called by nemogcm.F90 
    52  
     54#  include "do_loop_substitute.h90" 
    5355   !!------------------------------------------------------------------------- 
    5456   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    8183      INTEGER , DIMENSION(jpi,jpj) ::   ik_top , ik_bot       ! top and bottom ocean level 
    8284      REAL(wp), DIMENSION(jpi,jpj) ::   z1_hu_0, z1_hv_0 
     85      REAL(wp)::   zcoeff                                     ! local real 
     86 
    8387      !!---------------------------------------------------------------------- 
    8488      ! 
     
    154158         hf_0(:,:) = hf_0(:,:) + e3f_0(:,:,jk) * ssfmask(:,:)     ! CAUTION : only valid in SWE, not with bathymetry 
    155159      END DO 
     160      ! 
     161!!anhf hf_0 = mean(ht_0*tmask) so hf = mimj( ht0 + ssht) 
     162! ne pas combiner avec an45 tout de suite 
     163!      DO_2D_10_10 
     164!         hf_0(ji,jj) = 0.25_wp * (   ht_0(ji,jj+1) * tmask(ji,jj+1,1) + ht_0(ji+1,jj+1) * tmask(ji+1,jj+1,1)   & 
     165!            &                      + ht_0(ji,jj  ) * tmask(ji,jj  ,1) + ht_0(ji+1,jj  ) * tmask(ji+1,jj  ,1)   ) 
     166!      END_2D 
     167!      CALL lbc_lnk( 'domain', hf_0, 'F', 1. )      ! Lateral boundary conditions 
     168!!anhf 
    156169      !                                 ! Inverse of reference ocean thickness 
    157170      r1_ht_0(:,:) =  ssmask(:,:) / ( ht_0(:,:) + 1._wp -  ssmask(:,:) ) 
     
    159172      r1_hv_0(:,:) = ssvmask(:,:) / ( hv_0(:,:) + 1._wp - ssvmask(:,:) ) 
    160173      r1_hf_0(:,:) = ssfmask(:,:) / ( hf_0(:,:) + 1._wp - ssfmask(:,:) ) 
    161        
     174      ! 
     175!!an45 Ligne de cote a 45deg : e1e2t *= ( mi(umask) + mj(vmask) ) /2 
     176!!                             idem pour e1e2f 
     177!      DO_2D_10_10 
     178!      zcoeff = 0.25_wp * (   umask(ji,jj+1,1) + umask(ji+1,jj+1,1)   & 
     179!         &                 + vmask(ji,jj  ,1) + vmask(ji+1,jj  ,1)   ) 
     180!         IF ( zcoeff /= 0._wp )   THEN 
     181!               e1e2t(ji,jj) =    e1e2t(ji,jj) * zcoeff 
     182!            r1_e1e2t(ji,jj) = r1_e1e2t(ji,jj) / zcoeff 
     183!         ENDIF 
     184!      END_2D 
     185!      WRITE(numout,*) '   an45 half T cell e1e2t ' 
     186!      zcoeff = 0.25_wp * (   umask(ji,jj+1,1) + umask(ji+1,jj+1,1)   & 
     187!         &                 + vmask(ji,jj  ,1) + vmask(ji+1,jj  ,1)   ) 
     188!         IF ( zcoeff /= 0._wp )   THEN 
     189!               e1e2t(ji,jj) =    e1e2t(ji,jj) * zcoeff 
     190!            r1_e1e2t(ji,jj) = r1_e1e2t(ji,jj) / zcoeff 
     191!!an45 
    162192      !           !==  time varying part of coordinate system  ==! 
    163193      ! 
Note: See TracChangeset for help on using the changeset viewer.