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 14016 for NEMO/branches/2020/tickets_icb_1900/src/ICE/icedyn_rdgrft.F90 – NEMO

Ignore:
Timestamp:
2020-12-02T16:28:39+01:00 (3 years ago)
Author:
mathiot
Message:

ticket 1900: upgrade to trunk@r14015 (head trunk at 16h27)

Location:
NEMO/branches/2020/tickets_icb_1900
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/tickets_icb_1900

    • Property svn:externals
      •  

        old new  
        88 
        99# SETTE 
        10 ^/utils/CI/sette_MPI3_LoopFusion@13943         sette 
         10^/utils/CI/sette_wave@13990         sette 
  • NEMO/branches/2020/tickets_icb_1900/src/ICE/icedyn_rdgrft.F90

    r13899 r14016  
    140140      INTEGER , DIMENSION(jpij) ::   iptidx        ! compute ridge/raft or not 
    141141      REAL(wp), DIMENSION(jpij) ::   zdivu, zdelt  ! 1D divu_i & delta_i 
     142      REAL(wp), DIMENSION(jpij) ::   zconv         ! 1D rdg_conv (if EAP rheology) 
    142143      ! 
    143144      INTEGER, PARAMETER ::   jp_itermax = 20     
     
    175176         ! just needed here 
    176177         CALL tab_2d_1d( npti, nptidx(1:npti), zdelt   (1:npti)      , delta_i ) 
     178         CALL tab_2d_1d( npti, nptidx(1:npti), zconv   (1:npti)      , rdg_conv ) 
    177179         ! needed here and in the iteration loop 
    178180         CALL tab_2d_1d( npti, nptidx(1:npti), zdivu   (1:npti)      , divu_i) ! zdivu is used as a work array here (no change in divu_i) 
     
    184186            ! closing_net = rate at which open water area is removed + ice area removed by ridging  
    185187            !                                                        - ice area added in new ridges 
    186             closing_net(ji) = rn_csrdg * 0.5_wp * ( zdelt(ji) - ABS( zdivu(ji) ) ) - MIN( zdivu(ji), 0._wp ) 
     188            IF( ln_rhg_EVP .OR. ln_rhg_VP ) &  
     189               &               closing_net(ji) = rn_csrdg * 0.5_wp * ( zdelt(ji) - ABS( zdivu(ji) ) ) - MIN( zdivu(ji), 0._wp ) 
     190            IF( ln_rhg_EAP )   closing_net(ji) = zconv(ji) 
    187191            ! 
    188192            IF( zdivu(ji) < 0._wp )   closing_net(ji) = MAX( closing_net(ji), -zdivu(ji) )   ! make sure the closing rate is large enough 
     
    575579               oirft2(ji) = oa_i_2d(ji,jl1)   * afrft * hi_hrft  
    576580 
    577                IF ( ln_pnd_LEV ) THEN 
     581               IF ( ln_pnd_LEV .OR. ln_pnd_TOPO ) THEN 
    578582                  aprdg1     = a_ip_2d(ji,jl1) * afrdg 
    579583                  aprdg2(ji) = a_ip_2d(ji,jl1) * afrdg * hi_hrdg(ji,jl1) 
     
    612616               sv_i_2d(ji,jl1) = sv_i_2d(ji,jl1) - sirdg1    - sirft(ji) 
    613617               oa_i_2d(ji,jl1) = oa_i_2d(ji,jl1) - oirdg1    - oirft1 
    614                IF ( ln_pnd_LEV ) THEN 
     618               IF ( ln_pnd_LEV .OR. ln_pnd_TOPO ) THEN 
    615619                  a_ip_2d(ji,jl1) = a_ip_2d(ji,jl1) - aprdg1    - aprft1 
    616620                  v_ip_2d(ji,jl1) = v_ip_2d(ji,jl1) - vprdg(ji) - vprft(ji) 
     
    709713                  v_s_2d (ji,jl2) = v_s_2d (ji,jl2) + ( vsrdg (ji) * rn_fsnwrdg * fvol(ji)  +  & 
    710714                     &                                  vsrft (ji) * rn_fsnwrft * zswitch(ji) ) 
    711                   IF ( ln_pnd_LEV ) THEN 
     715                  IF ( ln_pnd_LEV .OR. ln_pnd_TOPO ) THEN 
    712716                     v_ip_2d (ji,jl2) = v_ip_2d(ji,jl2) + (   vprdg (ji) * rn_fpndrdg * fvol   (ji)   & 
    713717                        &                                   + vprft (ji) * rn_fpndrft * zswitch(ji)   ) 
     
    776780      !                              !--------------------------------------------------! 
    777781         strength(:,:) = rn_pstar * SUM( v_i(:,:,:), dim=3 ) * EXP( -rn_crhg * ( 1._wp - SUM( a_i(:,:,:), dim=3 ) ) ) 
    778          ismooth = 1 
     782         ismooth = 1    ! original code 
     783!        ismooth = 0    ! try for EAP stability 
    779784         !                           !--------------------------------------------------! 
    780785      ELSE                           ! Zero strength                                    ! 
Note: See TracChangeset for help on using the changeset viewer.