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 4161 for branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90 – NEMO

Ignore:
Timestamp:
2013-11-07T11:01:27+01:00 (10 years ago)
Author:
cetlod
Message:

dev_LOCEAN_2013 : merge in the 3rd dev branch dev_r4028_CNRS_LIM3, see ticket #1169

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r3791 r4161  
    4141   USE agrif_lim2_interp 
    4242#endif 
     43#if defined key_bdy 
     44   USE bdyice_lim 
     45#endif 
    4346 
    4447   IMPLICIT NONE 
     
    5356#  include "vectopt_loop_substitute.h90" 
    5457   !!---------------------------------------------------------------------- 
    55    !! NEMO/LIM3 3.4 , UCL - NEMO Consortium (2011) 
     58   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011) 
    5659   !! $Id$ 
    5760   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    413416 
    414417               delta = SQRT( zdd(ji,jj)*zdd(ji,jj) + ( zdt(ji,jj)*zdt(ji,jj) + zzdst*zzdst ) * usecc2 )   
    415                deltat(ji,jj) = MAX( SQRT(zdd(ji,jj)**2 + (zdt(ji,jj)**2 + zzdst**2)*usecc2), creepl ) 
    416 !!gm faster to replace the line above with simply: 
    417 !!                deltat(ji,jj) = MAX( delta, creepl ) 
    418 !!gm end  
    419  
     418               ! MV rewriting 
     419               ! deltat(ji,jj) = MAX( SQRT(zdd(ji,jj)**2 + (zdt(ji,jj)**2 + zzdst**2)*usecc2), creepl ) 
     420               !!gm faster to replace the line above with simply: 
     421               !!                deltat(ji,jj) = MAX( delta, creepl ) 
     422               !!gm end   
     423               deltat(ji,jj) = delta + creepl 
     424               ! END MV 
    420425               !-Calculate stress tensor components zs1 and zs2  
    421426               !-at centre of grid cells (see section 3.5 of CICE user's guide). 
     
    472477 
    473478         CALL lbc_lnk( zs12(:,:), 'F', 1. ) 
     479 
     480!#if defined key_bdy 
     481!         ! clem: change zs1, zs2, zs12 at the boundary for each iteration 
     482!         CALL bdy_ice_lim_dyn( 2, zs1, zs2, zs12 ) 
     483!         CALL lbc_lnk( zs1 (:,:), 'T', 1. ) 
     484!         CALL lbc_lnk( zs2 (:,:), 'T', 1. ) 
     485!         CALL lbc_lnk( zs12(:,:), 'F', 1. ) 
     486!#endif          
    474487 
    475488         ! Ice internal stresses (Appendix C of Hunke and Dukowicz, 2002) 
     
    520533 
    521534            CALL lbc_lnk( u_ice(:,:), 'U', -1. ) 
    522 #if defined key_agrif 
     535#if defined key_agrif && defined key_lim2 
    523536            CALL agrif_rhg_lim2( jter, nevp, 'U' ) 
    524537#endif 
     
    548561 
    549562            CALL lbc_lnk( v_ice(:,:), 'V', -1. ) 
    550 #if defined key_agrif 
     563#if defined key_agrif && defined key_lim2 
    551564            CALL agrif_rhg_lim2( jter, nevp, 'V' ) 
    552565#endif 
     
    577590 
    578591            CALL lbc_lnk( v_ice(:,:), 'V', -1. ) 
    579 #if defined key_agrif 
     592#if defined key_agrif && defined key_lim2 
    580593            CALL agrif_rhg_lim2( jter, nevp , 'V' ) 
    581594#endif 
     
    608621 
    609622            CALL lbc_lnk( u_ice(:,:), 'U', -1. ) 
    610 #if defined key_agrif 
     623#if defined key_agrif && defined key_lim2 
    611624            CALL agrif_rhg_lim2( jter, nevp, 'U' ) 
    612625#endif 
    613626 
    614627         ENDIF 
     628          
     629!#if defined key_bdy 
     630!         ! clem: change u_ice and v_ice at the boundary for each iteration 
     631!         CALL bdy_ice_lim_dyn( 1 ) 
     632!#endif          
    615633 
    616634         IF(ln_ctl) THEN 
     
    624642         ENDIF 
    625643 
    626          !                                                   ! ==================== ! 
     644         !                                                ! ==================== ! 
    627645      END DO                                              !  end loop over jter  ! 
    628646      !                                                   ! ==================== ! 
    629  
    630647      ! 
    631648      !------------------------------------------------------------------------------! 
    632649      ! 4) Prevent ice velocities when the ice is thin 
    633650      !------------------------------------------------------------------------------! 
    634       ! 
    635       ! If the ice thickness is below 1cm then ice velocity should equal the 
     651      !clem : add hminrhg in the namelist 
     652      ! 
     653      ! If the ice thickness is below hminrhg (5cm) then ice velocity should equal the 
    636654      ! ocean velocity,  
    637655      ! This prevents high velocity when ice is thin 
     
    641659         DO ji = fs_2, fs_jpim1 
    642660            zindb  = MAX( 0.0, SIGN( 1.0, at_i(ji,jj) - 1.0e-6 ) )  
    643             zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) 
    644             IF ( zdummy .LE. 5.0e-2 ) THEN 
     661            !zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) 
     662            zdummy = vt_i(ji,jj) 
     663            IF ( zdummy .LE. hminrhg ) THEN 
    645664               u_ice(ji,jj) = u_oce(ji,jj) 
    646665               v_ice(ji,jj) = v_oce(ji,jj) 
     
    651670      CALL lbc_lnk( u_ice(:,:), 'U', -1. )  
    652671      CALL lbc_lnk( v_ice(:,:), 'V', -1. )  
    653 #if defined key_agrif 
     672#if defined key_agrif && defined key_lim2 
    654673      CALL agrif_rhg_lim2( nevp , nevp, 'U' ) 
    655674      CALL agrif_rhg_lim2( nevp , nevp, 'V' ) 
    656675#endif 
     676#if defined key_bdy 
     677      ! clem: change u_ice and v_ice at the boundary 
     678      CALL bdy_ice_lim_dyn( 1 ) 
     679#endif          
    657680 
    658681      DO jj = k_j1+1, k_jpj-1  
    659682         DO ji = fs_2, fs_jpim1 
    660683            zindb  = MAX( 0.0, SIGN( 1.0, at_i(ji,jj) - 1.0e-6 ) )  
    661             zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) 
    662             IF ( zdummy .LE. 5.0e-2 ) THEN 
     684            !zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) 
     685            zdummy = vt_i(ji,jj) 
     686            IF ( zdummy .LE. hminrhg ) THEN 
    663687               v_ice1(ji,jj)  = 0.5*( (v_ice(ji,jj)+v_ice(ji,jj-1))*e1t(ji+1,jj)   & 
    664688                  &                 +(v_ice(ji+1,jj)+v_ice(ji+1,jj-1))*e1t(ji,jj)) & 
     
    683707            !- zds(:,:): shear on northeast corner of grid cells 
    684708            zindb  = MAX( 0.0, SIGN( 1.0, at_i(ji,jj) - 1.0e-6 ) )  
    685             zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) 
    686  
    687             IF ( zdummy .LE. 5.0e-2 ) THEN 
     709            !zdummy = zindb * vt_i(ji,jj) / MAX(at_i(ji,jj) , 1.0e-06 ) 
     710            zdummy = vt_i(ji,jj) 
     711            IF ( zdummy .LE. hminrhg ) THEN 
    688712 
    689713               zdd(ji,jj) = ( e2u(ji,jj)*u_ice(ji,jj)                      & 
     
    719743                  &           - e1v( ji  , jj-1 ) * u_ice2(ji  ,jj-1)  ) / area(ji,jj) 
    720744 
    721                deltat(ji,jj) = SQRT(    zdd(ji,jj)*zdd(ji,jj)   &  
    722                   &                 + ( zdt(ji,jj)*zdt(ji,jj) + zdst(ji,jj)*zdst(ji,jj) ) * usecc2 &  
    723                   &                          ) + creepl 
    724  
     745!              deltat(ji,jj) = SQRT(    zdd(ji,jj)*zdd(ji,jj)   &  
     746!                  &                 + ( zdt(ji,jj)*zdt(ji,jj) + zdst(ji,jj)*zdst(ji,jj) ) * usecc2 &  
     747!                  &                          ) + creepl 
     748               ! MV rewriting 
     749               delta = SQRT( zdd(ji,jj)*zdd(ji,jj) + ( zdt(ji,jj)*zdt(ji,jj) + zdst(ji,jj)*zdst(ji,jj) ) * usecc2 )   
     750               deltat(ji,jj) = delta + creepl 
     751               ! END MV 
     752             
    725753            ENDIF ! zdummy 
    726754 
     
    738766            divu_i (ji,jj) = zdd   (ji,jj) 
    739767            delta_i(ji,jj) = deltat(ji,jj) 
     768            ! begin TECLIM change  
     769            zdst(ji,jj)= (  e2u( ji  , jj   ) * v_ice1(ji,jj)           &    
     770               &          - e2u( ji-1, jj   ) * v_ice1(ji-1,jj)         &    
     771               &          + e1v( ji  , jj   ) * u_ice2(ji,jj)           &    
     772               &          - e1v( ji  , jj-1 ) * u_ice2(ji,jj-1) ) / area(ji,jj)  
    740773            shear_i(ji,jj) = SQRT( zdt(ji,jj) * zdt(ji,jj) + zdst(ji,jj) * zdst(ji,jj) ) 
     774            ! end TECLIM change 
    741775         END DO 
    742776      END DO 
    743       CALL lbc_lnk( divu_i (:,:), 'T', 1. )      ! Lateral boundary condition 
     777 
     778      ! Lateral boundary condition 
     779      CALL lbc_lnk( divu_i (:,:), 'T', 1. ) 
    744780      CALL lbc_lnk( delta_i(:,:), 'T', 1. ) 
     781      ! CALL lbc_lnk( shear_i(:,:), 'F', 1. ) 
    745782      CALL lbc_lnk( shear_i(:,:), 'T', 1. ) 
    746783 
Note: See TracChangeset for help on using the changeset viewer.