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 12252 for NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/icedyn_adv_umx.F90 – NEMO

Ignore:
Timestamp:
2019-12-14T14:57:23+01:00 (4 years ago)
Author:
smasson
Message:

rev12240_dev_r11943_MERGE_2019: same as [12251], merge trunk 12072:12248, all sette tests ok, GYRE_PISCES, AMM12, ISOMIP, VORTEX intentical to 12236

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/ICE/icedyn_adv_umx.F90

    r11627 r12252  
    352352         CALL ice_var_zapneg( zdt, pato_i, pv_i, pv_s, psv_i, poa_i, pa_i, pa_ip, pv_ip, pe_s, pe_i ) 
    353353         ! 
    354          ! Make sure ice thickness is not too big 
    355          !    (because ice thickness can be too large where ice concentration is very small) 
    356          CALL Hbig( zdt, zhi_max, zhs_max, zhip_max, pv_i, pv_s, psv_i, poa_i, pa_i, pa_ip, pv_ip, pe_s, pe_i ) 
    357  
     354         ! --- Make sure ice thickness is not too big --- ! 
     355         !     (because ice thickness can be too large where ice concentration is very small) 
     356         CALL Hbig( zdt, zhi_max, zhs_max, zhip_max, pv_i, pv_s, pa_i, pa_ip, pv_ip, pe_s ) 
     357         ! 
     358         ! --- Ensure snow load is not too big --- ! 
     359         CALL Hsnow( zdt, pv_i, pv_s, pa_i, pa_ip, pe_s ) 
     360         ! 
    358361      END DO 
    359362      ! 
     
    15141517 
    15151518 
    1516    SUBROUTINE Hbig( pdt, phi_max, phs_max, phip_max, pv_i, pv_s, psv_i, poa_i, pa_i, pa_ip, pv_ip, pe_s, pe_i ) 
     1519   SUBROUTINE Hbig( pdt, phi_max, phs_max, phip_max, pv_i, pv_s, pa_i, pa_ip, pv_ip, pe_s ) 
    15171520      !!------------------------------------------------------------------- 
    15181521      !!                  ***  ROUTINE Hbig  *** 
     
    15251528      !!              2- check whether snow thickness is larger than the surrounding 9-points 
    15261529      !!                 (before advection) and reduce it by sending the excess in the ocean 
    1527       !!              3- check whether snow load deplets the snow-ice interface below sea level$ 
    1528       !!                 and reduce it by sending the excess in the ocean 
    1529       !!              4- correct pond concentration to avoid a_ip > a_i 
    15301530      !! 
    15311531      !! ** input   : Max thickness of the surrounding 9-points 
     
    15331533      REAL(wp)                    , INTENT(in   ) ::   pdt                          ! tracer time-step 
    15341534      REAL(wp), DIMENSION(:,:,:)  , INTENT(in   ) ::   phi_max, phs_max, phip_max   ! max ice thick from surrounding 9-pts 
    1535       REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   pv_i, pv_s, psv_i, poa_i, pa_i, pa_ip, pv_ip 
     1535      REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   pv_i, pv_s, pa_i, pa_ip, pv_ip 
    15361536      REAL(wp), DIMENSION(:,:,:,:), INTENT(inout) ::   pe_s 
    1537       REAL(wp), DIMENSION(:,:,:,:), INTENT(inout) ::   pe_i 
    1538       ! 
    1539       INTEGER  ::   ji, jj, jk, jl         ! dummy loop indices 
    1540       REAL(wp) ::   z1_dt, zhip, zhi, zhs, zvs_excess, zfra 
    1541       REAL(wp), DIMENSION(jpi,jpj) ::   zswitch 
     1537      ! 
     1538      INTEGER  ::   ji, jj, jl         ! dummy loop indices 
     1539      REAL(wp) ::   z1_dt, zhip, zhi, zhs, zfra 
    15421540      !!------------------------------------------------------------------- 
    15431541      ! 
     
    15781576                     pv_s(ji,jj,jl)          = pa_i(ji,jj,jl) * phs_max(ji,jj,jl) 
    15791577                  ENDIF            
     1578                  !                   
     1579               ENDIF 
     1580            END DO 
     1581         END DO 
     1582      END DO  
     1583      ! 
     1584   END SUBROUTINE Hbig 
     1585 
     1586 
     1587   SUBROUTINE Hsnow( pdt, pv_i, pv_s, pa_i, pa_ip, pe_s ) 
     1588      !!------------------------------------------------------------------- 
     1589      !!                  ***  ROUTINE Hsnow  *** 
     1590      !! 
     1591      !! ** Purpose : 1- Check snow load after advection 
     1592      !!              2- Correct pond concentration to avoid a_ip > a_i 
     1593      !! 
     1594      !! ** Method :  If snow load makes snow-ice interface to deplet below the ocean surface 
     1595      !!              then put the snow excess in the ocean 
     1596      !! 
     1597      !! ** Notes :   This correction is crucial because of the call to routine icecor afterwards 
     1598      !!              which imposes a mini of ice thick. (rn_himin). This imposed mini can artificially 
     1599      !!              make the snow very thick (if concentration decreases drastically) 
     1600      !!              This behavior has been seen in Ultimate-Macho and supposedly it can also be true for Prather 
     1601      !!------------------------------------------------------------------- 
     1602      REAL(wp)                    , INTENT(in   ) ::   pdt   ! tracer time-step 
     1603      REAL(wp), DIMENSION(:,:,:)  , INTENT(inout) ::   pv_i, pv_s, pa_i, pa_ip 
     1604      REAL(wp), DIMENSION(:,:,:,:), INTENT(inout) ::   pe_s 
     1605      ! 
     1606      INTEGER  ::   ji, jj, jl   ! dummy loop indices 
     1607      REAL(wp) ::   z1_dt, zvs_excess, zfra 
     1608      !!------------------------------------------------------------------- 
     1609      ! 
     1610      z1_dt = 1._wp / pdt 
     1611      ! 
     1612      ! -- check snow load -- ! 
     1613      DO jl = 1, jpl 
     1614         DO jj = 1, jpj 
     1615            DO ji = 1, jpi 
     1616               IF ( pv_i(ji,jj,jl) > 0._wp ) THEN 
    15801617                  ! 
    1581                   !                               ! -- check snow load -- ! 
    1582                   ! if snow load makes snow-ice interface to deplet below the ocean surface => put the snow excess in the ocean 
    1583                   !    this correction is crucial because of the call to routine icecor afterwards which imposes a mini of ice thick. (rn_himin) 
    1584                   !    this imposed mini can artificially make the snow very thick (if concentration decreases drastically) 
    15851618                  zvs_excess = MAX( 0._wp, pv_s(ji,jj,jl) - pv_i(ji,jj,jl) * (rau0-rhoi) * r1_rhos ) 
    1586                   IF( zvs_excess > 0._wp ) THEN 
     1619                  ! 
     1620                  IF( zvs_excess > 0._wp ) THEN   ! snow-ice interface deplets below the ocean surface 
     1621                     ! put snow excess in the ocean 
    15871622                     zfra = ( pv_s(ji,jj,jl) - zvs_excess ) / MAX( pv_s(ji,jj,jl), epsi20 ) 
    15881623                     wfx_res(ji,jj) = wfx_res(ji,jj) + zvs_excess * rhos * z1_dt 
    15891624                     hfx_res(ji,jj) = hfx_res(ji,jj) - SUM( pe_s(ji,jj,1:nlay_s,jl) ) * ( 1._wp - zfra ) * z1_dt ! W.m-2 <0 
    1590                      ! 
     1625                     ! correct snow volume and heat content 
    15911626                     pe_s(ji,jj,1:nlay_s,jl) = pe_s(ji,jj,1:nlay_s,jl) * zfra 
    15921627                     pv_s(ji,jj,jl)          = pv_s(ji,jj,jl) - zvs_excess 
    15931628                  ENDIF 
    1594                    
     1629                  ! 
    15951630               ENDIF 
    15961631            END DO 
    15971632         END DO 
    1598       END DO  
    1599       !                                           !-- correct pond concentration to avoid a_ip > a_i 
     1633      END DO 
     1634      ! 
     1635      !-- correct pond concentration to avoid a_ip > a_i -- ! 
    16001636      WHERE( pa_ip(:,:,:) > pa_i(:,:,:) )   pa_ip(:,:,:) = pa_i(:,:,:) 
    16011637      ! 
    1602       ! 
    1603    END SUBROUTINE Hbig 
    1604     
     1638   END SUBROUTINE Hsnow 
     1639 
     1640 
    16051641#else 
    16061642   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.