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 13879 – NEMO

Changeset 13879


Ignore:
Timestamp:
2020-11-26T08:31:17+01:00 (3 years ago)
Author:
vancop
Message:

More decent computing cost

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/SI3-05_MeltPonds_topo/src/ICE/icethd_pnd.F90

    r13850 r13879  
    4040   INTEGER, PARAMETER ::   np_pndLEV  = 2   ! Level ice pond scheme 
    4141   INTEGER, PARAMETER ::   np_pndTOPO = 3   ! Level ice pond scheme 
     42 
     43   REAL(wp), PARAMETER :: &   ! shared parameters for topographic melt ponds 
     44      zhi_min = 0.1_wp        , & ! minimum ice thickness with ponds (m)  
     45      zTd     = 0.15_wp       , & ! temperature difference for freeze-up (C) 
     46      zvp_min = 1.e-4_wp          ! minimum pond volume (m) 
    4247 
    4348   !! * Substitutions 
     
    441446         zTp,     &   ! pond freezing temperature (C) 
    442447         zrhoi_L, &   ! volumetric latent heat of sea ice (J/m^3) 
    443          zdvn   , &   ! change in melt pond volume for fresh water budget (not used for now) 
    444448         zfr_mlt, &   ! fraction and volume of available meltwater retained for melt ponding 
    445449         z1_rhow, &   ! inverse water density 
     
    447451         zdum         ! dummy variable 
    448452 
    449       REAL(wp), PARAMETER :: & 
    450          zhi_min = 0.1_wp        , & ! minimum ice thickness with ponds (m)  
    451          zTd     = 0.15_wp       , & ! temperature difference for freeze-up (C) 
    452          zvp_min = 1.e-4_wp        ! minimum pond volume (m) 
    453  
    454       REAL(wp), DIMENSION(jpi,jpj) ::   zvolp !! total melt pond water available before redistribution and drainage 
     453      REAL(wp), DIMENSION(jpi,jpj) ::   zvolp, & !! total melt pond water available before redistribution and drainage 
     454                                        zvolp_res 
    455455 
    456456      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z1_a_i 
     
    466466       
    467467      !--------------------------------------------------------------- 
    468       ! Initialize 
     468      ! Initialise 
    469469      !--------------------------------------------------------------- 
    470470 
     
    487487      END WHERE 
    488488      h_i(:,:,:) = v_i (:,:,:) * z1_a_i(:,:,:) 
    489  
    490       !----------------------------------------------------------------- 
    491       ! Start pond loop 
    492       !-----------------------------------------------------------------       
     489       
     490      !--------------------------------------------------------------- 
     491      ! Change 2D to 1D 
     492      !--------------------------------------------------------------- 
     493 
     494      !-------------------------------------------------------------- 
     495      ! Collect total available pond water 
     496      !-------------------------------------------------------------- 
    493497 
    494498      zvolp(:,:) = 0._wp 
    495499 
    496       DO jj = 1, jpj 
    497          DO ji = 1, jpi 
    498           
    499             !-------------------------------------------------------------- 
    500             ! Collect meltwater on ponds 
    501             !-------------------------------------------------------------- 
    502             DO jl = 1, jpl 
    503              
     500      DO jl = 1, jpl 
     501         DO jj = 1, jpj 
     502            DO ji = 1, jpi 
     503                  
    504504               IF ( a_i(ji,jj,jl) > epsi10 ) THEN 
    505505             
     
    518518                  !--- Deepen existing ponds before redistribution and drainage(later on) 
    519519                  h_ip(ji,jj,jl) = ( zpond + h_ip(ji,jj,jl) * a_ip_frac(ji,jj,jl) ) / a_ip_frac(ji,jj,jl) 
    520                   zvolp(ji,jj)   = zvolp(ji,jj) + h_ip(ji,jj,jl) * a_ip_frac(ji,jj,jl)  
     520                  zvolp(ji,jj)   = zvolp(ji,jj) + h_ip(ji,jj,jl) * a_ip_frac(ji,jj,jl) * a_i(ji,jj,jl)  
    521521!                 zfpond(ji,jj) = zfpond(ji,jj) + zpond * a_ip_frac(ji,jj,jl) !useless 
    522522                    
    523523               ENDIF ! a_i 
    524524 
    525             END DO 
    526  
    527             h_ip(ji,jj,:)  = 0._wp ! pond thickness 
    528             a_ip(ji,jj,:)  = 0._wp ! pond fraction per grid area       
    529  
    530             !----------------------------------------------------------------- 
    531             ! Identify grid cells with ice 
    532             !----------------------------------------------------------------- 
     525            END DO! jl             
     526         END DO ! jj 
     527      END DO ! ji 
     528          
     529      h_ip(:,:,:)  = 0._wp ! pond thickness 
     530      a_ip(:,:,:)  = 0._wp ! pond fraction per grid area   
     531          
     532      !-------------------------------------------------------------- 
     533      ! Redistribute and drain water from ponds 
     534      !--------------------------------------------------------------    
     535      CALL ice_thd_pnd_area( zvolp, zvolp_res ) 
     536                                    
     537      !-------------------------------------------------------------- 
     538      ! Freeze and melt lid 
     539      !--------------------------------------------------------------    
     540      DO jj = 1, jpj 
     541         DO ji = 1, jpi 
    533542 
    534543            IF ( at_i(ji,jj) > 0.01 .AND. hm_i(ji,jj) > zhi_min .AND. vt_ip(ji,jj) > zvp_min *at_i(ji,jj) ) THEN 
    535        
    536                !---------------------------------------------------------------------------- 
    537                ! Calculate pond area and depth (redistribution of melt water on topography) 
    538                !---------------------------------------------------------------------------- 
    539 !              CALL ice_thd_pnd_area( at_i(ji,jj) , vt_i(ji,jj), & 
    540 !                                     a_i (ji,jj,:), v_i(ji,jj,:), v_s(ji,jj,:), & 
    541 !                                     t_i(ji,jj,:,:), sz_i(ji,jj,:,:), & 
    542 !                                     v_ip(ji,jj,:) , zvolp(ji,jj), & 
    543 !                                     a_ip(ji,jj,:), h_ip(ji,jj,:), zdvn) 
    544                                     
    545 !               zfpond(ji,jj) = zfpond(ji,jj) - zdvn ! ---> zdvn is drainage (useless for now since we dont change fw budget, no ?) 
    546              
     544                   
    547545               !-------------------------- 
    548546               ! Pond lid growth and melt 
     
    565563                     IF ( t_su(ji,jj,jl) > zTp ) THEN 
    566564 
    567                         zdvice = min( dh_i_sum_2d(ji,jj,jl)*a_ip(ji,jj,jl), v_il(ji,jj,jl)) 
     565                        zdvice = MIN( dh_i_sum_2d(ji,jj,jl)*a_ip(ji,jj,jl), v_il(ji,jj,jl) ) 
    568566                        IF ( zdvice > epsi10 ) then 
    569567                           v_il (ji,jj,jl) = v_il (ji,jj,jl)   - zdvice 
     
    617615                     ! flux is the same 
    618616                      
    619                      !!!!! FSURF !!!!! 
    620617                     !!! we need net surface energy flux, excluding conduction 
    621618                     !!! fsurf is summed over categories in CICE 
     
    639636 
    640637               v_ip(ji,jj,:) = 0._wp 
    641                v_il (ji,jj,:) = 0._wp 
     638               v_il(ji,jj,:) = 0._wp 
    642639!              zfpond(ji,jj) = zfpond(ji,jj)- zvolp(ji,jj) 
    643640!                 zvolp(ji,jj)    = 0._wp          
     
    645642            ENDIF 
    646643 
     644      END DO   ! jj 
     645   END DO   ! ji 
     646 
    647647      !--------------------------------------------------------------- 
    648       ! remove ice lid if there is no liquid pond 
    649       ! v_il may be nonzero on category ncat due to dynamics 
     648      ! Clean-up variables (probably duplicates what icevar would do) 
    650649      !--------------------------------------------------------------- 
     650      ! MV comment 
     651      ! In the ideal world, the lines above should update only v_ip, a_ip, v_il 
     652      ! icevar should recompute all other variables (if needed at all) 
    651653 
    652654      DO jl = 1, jpl 
     655         DO jj = 1, jpj 
     656            DO ji = 1, jpi 
     657 
     658               IF ( a_i(ji,jj,jl) > epsi10 .AND. v_ip(ji,jj,jl) < epsi10 & 
     659                                   .AND. v_il (ji,jj,jl) > epsi10) THEN 
     660                  v_il(ji,jj,jl) = 0._wp 
     661               ENDIF 
    653662       
    654          IF ( a_i(ji,jj,jl) > epsi10 .AND. v_ip(ji,jj,jl) < epsi10 & 
    655                              .AND. v_il (ji,jj,jl) > epsi10) THEN 
    656             v_il(ji,jj,jl) = 0._wp 
    657          ENDIF 
    658  
    659          ! reload tracers 
    660          IF ( a_ip(ji,jj,jl) > epsi10) THEN 
    661             h_il(ji,jj,jl) = v_il(ji,jj,jl) / a_ip(ji,jj,jl) ! MV in principle, useless as computed in icevar 
    662          ELSE 
    663             v_il(ji,jj,jl) = 0._wp 
    664             h_il(ji,jj,jl) = 0._wp ! MV in principle, useless as a_ip_frac computed in icevar 
    665          ENDIF 
    666          IF ( a_ip(ji,jj,jl) > epsi10 ) THEN 
    667             a_ip_frac(ji,jj,jl) = a_ip(ji,jj,jl) / a_i(ji,jj,jl) ! MV in principle, useless as computed in icevar 
    668             !h_ip(ji,jj,jl) = zhpondn(ji,jj,jl) 
    669          ELSE 
    670             a_ip_frac(ji,jj,jl) = 0._wp 
    671             h_ip(ji,jj,jl)      = 0._wp ! MV in principle, useless as computed in icevar 
    672             h_il(ji,jj,jl)      = 0._wp ! MV in principle, useless as omputed in icevar 
    673          ENDIF 
     663               ! reload tracers 
     664               IF ( a_ip(ji,jj,jl) > epsi10) THEN 
     665                  h_il(ji,jj,jl) = v_il(ji,jj,jl) / a_ip(ji,jj,jl) ! MV in principle, useless as computed in icevar 
     666               ELSE 
     667                  v_il(ji,jj,jl) = 0._wp 
     668                  h_il(ji,jj,jl) = 0._wp ! MV in principle, useless as a_ip_frac computed in icevar 
     669               ENDIF 
     670                
     671               IF ( a_ip(ji,jj,jl) > epsi10 ) THEN 
     672                  a_ip_frac(ji,jj,jl) = a_ip(ji,jj,jl) / a_i(ji,jj,jl) ! MV in principle, useless as computed in icevar 
     673                  !h_ip(ji,jj,jl) = zhpondn(ji,jj,jl) 
     674               ELSE 
     675                  a_ip_frac(ji,jj,jl) = 0._wp 
     676                  h_ip(ji,jj,jl)      = 0._wp ! MV in principle, useless as computed in icevar 
     677                  h_il(ji,jj,jl)      = 0._wp ! MV in principle, useless as omputed in icevar 
     678               ENDIF 
    674679          
    675       END DO       ! jl 
    676  
    677       END DO   ! jj 
    678       END DO   ! ji 
     680            END DO       ! ji 
     681         END DO   ! jj 
     682      END DO   ! jl 
    679683 
    680684   END SUBROUTINE pnd_TOPO 
    681685 
    682686    
    683        SUBROUTINE ice_thd_pnd_area(aice,  vice, & 
    684                            aicen, vicen, vsnon, ticen, & 
    685                            salin, zvolpn, zvolp,         & 
    686                            zapondn,zhpondn,dvolp) 
     687   SUBROUTINE ice_thd_pnd_area( zvolp , zdvolp ) 
    687688 
    688689       !!------------------------------------------------------------------- 
    689690       !!                ***  ROUTINE ice_thd_pnd_area *** 
    690691       !! 
    691        !! ** Purpose : Given the total volume of meltwater, update 
    692        !!              pond fraction (a_ip) and depth (should be volume) 
     692       !! ** Purpose : Given the total volume of available pond water,  
     693       !!              redistribute and drain water 
    693694       !! 
    694695       !! ** 
    695696       !! 
    696697       !!------------------------------------------------------------------ 
    697  
    698        REAL (wp), INTENT(IN) :: & 
    699           aice, vice 
    700  
    701        REAL (wp), DIMENSION(jpl), INTENT(IN) :: & 
    702           aicen, vicen, vsnon 
    703  
    704        REAL (wp), DIMENSION(nlay_i,jpl), INTENT(IN) :: & 
    705           ticen, salin 
    706  
    707        REAL (wp), DIMENSION(jpl), INTENT(INOUT) :: & 
    708           zvolpn 
    709  
    710        REAL (wp), INTENT(INOUT) :: & 
    711           zvolp, dvolp 
    712  
    713        REAL (wp), DIMENSION(jpl), INTENT(OUT) :: & 
    714           zapondn, zhpondn 
     698        
     699       REAL (wp), DIMENSION(jpi,jpj),     INTENT(INOUT) :: & 
     700          zvolp,                                           &  ! total available pond water 
     701          zdvolp                                              ! remaining meltwater after redistribution 
    715702 
    716703       INTEGER :: & 
    717           n, ns,   & 
     704          ns,   & 
    718705          m_index, & 
    719706          permflag 
     
    744731          viscosity = 1.79e-3_wp     ! kinematic water viscosity in kg/m/s 
    745732 
     733       INTEGER  ::   ji, jj, jk, jl                    ! loop indices 
     734 
    746735      !-----------| 
    747736      !           | 
     
    752741      !           |           |   |        | 
    753742      !           |           |   |        |-----------|              |------- 
    754       !           |           |   |alfan(n)|           |              | 
     743      !           |           |   |alfan(jl)|           |              | 
    755744      !           |           |   |        |           |--------------| 
    756745      !           |           |   |        |           |              | 
     
    758747      !           |           |   ^        |           |              | 
    759748      !           |           |   |        |           |--------------| 
    760       !           |           |   |betan(n)|           |              | 
     749      !           |           |   |betan(jl)|           |              | 
    761750      !           |           |   |        |-----------|              |------- 
    762751      !           |           |   |        | 
     
    767756      !-----------| 
    768757 
     758      a_ip(:,:,:) = 0._wp 
     759      h_ip(:,:,:) = 0._wp 
     760 
     761      DO jj = 1, jpj 
     762         DO ji = 1, jpi 
     763 
     764            IF ( at_i(ji,jj) > 0.01 .AND. hm_i(ji,jj) > zhi_min .AND. zvolp(ji,jj) > zvp_min * at_i(ji,jj) ) THEN 
     765 
    769766       !------------------------------------------------------------------- 
    770767       ! initialize 
    771768       !------------------------------------------------------------------- 
    772769 
    773        DO n = 1, jpl 
    774  
    775           zapondn(n) = 0._wp 
    776           zhpondn(n) = 0._wp 
     770       DO jl = 1, jpl 
     771 
     772          a_ip(ji,jj,jl) = 0._wp 
     773          h_ip(ji,jj,jl) = 0._wp 
    777774 
    778775          !---------------------------------------- 
    779           ! X) compute the effective snow fraction 
     776          ! compute the effective snow fraction 
    780777          !---------------------------------------- 
    781           IF (aicen(n) < epsi10)  THEN 
    782              hicen(n) =  0._wp 
    783              hsnon(n) =  0._wp 
    784              reduced_aicen(n) = 0._wp 
    785              asnon(n) = 0._wp         !js: in CICE 5.1.2: make sense as the compiler may not initiate the variables 
     778 
     779          IF (a_i(ji,jj,jl) < epsi10)  THEN 
     780             hicen(jl) =  0._wp 
     781             hsnon(jl) =  0._wp 
     782             reduced_aicen(jl) = 0._wp 
     783             asnon(jl) = 0._wp         !js: in CICE 5.1.2: make sense as the compiler may not initiate the variables 
    786784          ELSE 
    787              hicen(n) = vicen(n) / aicen(n) 
    788              hsnon(n) = vsnon(n) / aicen(n) 
    789              reduced_aicen(n) = 1._wp ! n=jpl 
     785             hicen(jl) = v_i(ji,jj,jl) / a_i(ji,jj,jl) 
     786             hsnon(jl) = v_s(ji,jj,jl) / a_i(ji,jj,jl) 
     787             reduced_aicen(jl) = 1._wp ! n=jpl 
    790788 
    791789             !js: initial code in NEMO_DEV 
    792              !IF (n < jpl) reduced_aicen(n) = aicen(n) & 
    793              !                     * (-0.024_wp*hicen(n) + 0.832_wp) 
     790             !IF (n < jpl) reduced_aicen(jl) = aicen(jl) & 
     791             !                     * (-0.024_wp*hicen(jl) + 0.832_wp) 
    794792 
    795793             !js: from CICE 5.1.2: this limit reduced_aicen to 0.2 when hicen is too large 
    796              IF (n < jpl) reduced_aicen(n) = aicen(n) & 
    797                                   * max(0.2_wp,(-0.024_wp*hicen(n) + 0.832_wp)) 
    798  
    799              asnon(n) = reduced_aicen(n)  ! effective snow fraction (empirical) 
     794             IF (jl < jpl) reduced_aicen(jl) = a_i(ji,jj,jl) &  
     795                                  * max(0.2_wp,(-0.024_wp*hicen(jl) + 0.832_wp)) 
     796 
     797             asnon(jl) = reduced_aicen(jl)  ! effective snow fraction (empirical) 
    800798             ! MV should check whether this makes sense to have the same effective snow fraction in here 
    801799             ! OLI: it probably doesn't 
     
    817815 ! Where does that choice come from ? => OLI : Coz' Chuck Norris said so... 
    818816 
    819           alfan(n) = 0.6 * hicen(n) 
    820           betan(n) = 0.4 * hicen(n) 
    821  
    822           cum_max_vol(n)     = 0._wp 
    823           cum_max_vol_tmp(n) = 0._wp 
     817          alfan(jl) = 0.6 * hicen(jl) 
     818          betan(jl) = 0.4 * hicen(jl) 
     819 
     820          cum_max_vol(jl)     = 0._wp 
     821          cum_max_vol_tmp(jl) = 0._wp 
    824822 
    825823       END DO ! jpl 
     
    827825       cum_max_vol_tmp(0) = 0._wp 
    828826       drain = 0._wp 
    829        dvolp = 0._wp 
     827       zdvolp(ji,jj) = 0._wp 
    830828 
    831829       !---------------------------------------------------------- 
    832        ! x) Drain overflow water, update pond fraction and volume 
     830       ! Drain overflow water, update pond fraction and volume 
    833831       !---------------------------------------------------------- 
    834832 
     
    836834       ! the maximum amount of water that can be contained up to each ice category 
    837835       !-------------------------------------------------------------------------- 
    838  
    839        ! MV 
    840836       ! If melt ponds are too deep to be sustainable given the ITD (OVERFLOW) 
    841837       ! Then the excess volume cum_max_vol(jl) drains out of the system 
    842838       ! It should be added to wfx_pnd_out 
    843        ! END MV 
    844        !js 18/04/19: XXX do something about this flux thing 
    845  
    846        DO n = 1, jpl-1 ! last category can not hold any volume 
    847  
    848           IF (alfan(n+1) >= alfan(n) .AND. alfan(n+1) > 0._wp ) THEN 
     839 
     840       DO jl = 1, jpl-1 ! last category can not hold any volume 
     841 
     842          IF (alfan(jl+1) >= alfan(jl) .AND. alfan(jl+1) > 0._wp ) THEN 
    849843 
    850844             ! total volume in level including snow 
    851              cum_max_vol_tmp(n) = cum_max_vol_tmp(n-1) + & 
    852                 (alfan(n+1) - alfan(n)) * sum(reduced_aicen(1:n)) 
     845             cum_max_vol_tmp(jl) = cum_max_vol_tmp(jl-1) + & 
     846                (alfan(jl+1) - alfan(jl)) * sum(reduced_aicen(1:jl)) 
    853847 
    854848             ! subtract snow solid volumes from lower categories in current level 
    855              DO ns = 1, n 
    856                 cum_max_vol_tmp(n) = cum_max_vol_tmp(n) & 
     849             DO ns = 1, jl 
     850                cum_max_vol_tmp(jl) = cum_max_vol_tmp(jl) & 
    857851                   - rhos/rhow * &   ! free air fraction that can be filled by water 
    858852                     asnon(ns)  * &    ! effective areal fraction of snow in that category 
    859                      max(min(hsnon(ns)+alfan(ns)-alfan(n), alfan(n+1)-alfan(n)), 0._wp) 
     853                     max(min(hsnon(ns)+alfan(ns)-alfan(jl), alfan(jl+1)-alfan(jl)), 0._wp) 
    860854             END DO 
    861855 
    862856          ELSE ! assume higher categories unoccupied 
    863              cum_max_vol_tmp(n) = cum_max_vol_tmp(n-1) 
     857             cum_max_vol_tmp(jl) = cum_max_vol_tmp(jl-1) 
    864858          END IF 
    865           !IF (cum_max_vol_tmp(n) < z0) THEN 
     859          !IF (cum_max_vol_tmp(jl) < z0) THEN 
    866860          !   CALL abort_ice('negative melt pond volume') 
    867861          !END IF 
     
    873867       ! is there more meltwater than can be held in the floe? 
    874868       !---------------------------------------------------------------- 
    875        IF (zvolp >= cum_max_vol(jpl)) THEN 
    876           drain = zvolp - cum_max_vol(jpl) + epsi10 
    877           zvolp = zvolp - drain ! update meltwater volume available 
    878           dvolp = drain         ! this is the drained water 
    879           IF (zvolp < epsi10) THEN 
    880              dvolp = dvolp + zvolp 
    881              zvolp = 0._wp 
     869       IF (zvolp(ji,jj) >= cum_max_vol(jpl)) THEN 
     870          drain = zvolp(ji,jj) - cum_max_vol(jpl) + epsi10 
     871          zvolp(ji,jj) = zvolp(ji,jj) - drain ! update meltwater volume available 
     872          zdvolp(ji,jj) = drain         ! this is the drained water 
     873          IF (zvolp(ji,jj) < epsi10) THEN 
     874             zdvolp(ji,jj) = zdvolp(ji,jj) + zvolp(ji,jj) 
     875             zvolp(ji,jj) = 0._wp 
    882876          END IF 
    883877       END IF 
    884878 
    885879       ! height and area corresponding to the remaining volume 
    886  
    887       CALL ice_thd_pnd_depth(reduced_aicen, asnon, hsnon, alfan, zvolp, cum_max_vol, hpond, m_index) 
    888  
    889        DO n=1, m_index 
    890           !zhpondn(n) = hpond - alfan(n) + alfan(1) ! here oui choulde update 
     880       CALL ice_thd_pnd_depth(reduced_aicen, asnon, hsnon, alfan, zvolp(ji,jj), cum_max_vol, hpond, m_index) 
     881 
     882       DO jl = 1, m_index 
     883          !h_ip(jl) = hpond - alfan(jl) + alfan(1) ! here oui choulde update 
    891884          !                                         !  volume instead, no ? 
    892           zhpondn(n) = max((hpond - alfan(n) + alfan(1)), 0._wp)      !js: from CICE 5.1.2 
    893           zapondn(n) = reduced_aicen(n) 
     885          h_ip(ji,jj,jl) = max((hpond - alfan(jl) + alfan(1)), 0._wp)      !js: from CICE 5.1.2 
     886          a_ip(ji,jj,jl) = reduced_aicen(jl) 
    894887          ! in practise, pond fraction depends on the empirical snow fraction 
    895888          ! so in turn on ice thickness 
    896889       END DO 
    897        !zapond = sum(zapondn(1:m_index))     !js: from CICE 5.1.2; not in Icepack1.1.0-6-gac6195d 
     890       !zapond = sum(a_ip(1:m_index))     !js: from CICE 5.1.2; not in Icepack1.1.0-6-gac6195d 
    898891 
    899892       !------------------------------------------------------------------------ 
     
    903896 
    904897       ! sea water level 
    905        msno =0._wp  
    906        DO n=1,jpl 
    907          msno = msno + vsnon(n) * rhos 
     898       msno = 0._wp  
     899       DO jl = 1 , jpl 
     900         msno = msno + v_s(ji,jj,jl) * rhos 
    908901       END DO 
    909        floe_weight = (msno + rhoi*vice + rau0*zvolp) / aice 
     902       floe_weight = ( msno + rhoi*vt_i(ji,jj) + rau0*zvolp(ji,jj) ) / at_i(ji,jj) 
    910903       hsl_rel = floe_weight / rau0 & 
    911                - ((sum(betan(:)*aicen(:))/aice) + alfan(1)) 
     904               - ( ( sum(betan(:)*a_i(ji,jj,:)) / at_i(ji,jj) ) + alfan(1) ) 
    912905 
    913906       deltah = hpond - hsl_rel 
     
    916909       ! drain if ice is permeable 
    917910       permflag = 0 
     911 
    918912       IF (pressure_head > 0._wp) THEN 
    919           DO n = 1, jpl-1 
    920              IF (hicen(n) /= 0._wp) THEN 
    921              !IF (hicen(n) > 0._wp) THEN           !js: from CICE 5.1.2 
     913          DO jl = 1, jpl-1 
     914             IF ( hicen(jl) /= 0._wp ) THEN 
     915 
     916             !IF (hicen(jl) > 0._wp) THEN           !js: from CICE 5.1.2 
     917 
    922918                perm = 0._wp ! MV ugly dummy patch 
    923                 CALL ice_thd_pnd_perm(ticen(:,n), salin(:,n), perm) 
     919                ! CALL ice_thd_pnd_perm(t_i(ji,jj,:,jl),  sz_i(ji,jj,:,jl), perm) ! bof  
    924920                IF (perm > 0._wp) permflag = 1 
    925921 
    926                 drain = perm*zapondn(n)*pressure_head*rdt_ice / & 
    927                                          (viscosity*hicen(n)) 
    928                 dvolp = dvolp + min(drain, zvolp) 
    929                 zvolp = max(zvolp - drain, 0._wp) 
    930                 IF (zvolp < epsi10) THEN 
    931                    dvolp = dvolp + zvolp 
    932                    zvolp = 0._wp 
     922                drain = perm*a_ip(ji,jj,jl)*pressure_head*rdt_ice / & 
     923                                         (viscosity*hicen(jl)) 
     924                zdvolp(ji,jj) = zdvolp(ji,jj) + min(drain, zvolp(ji,jj)) 
     925                zvolp(ji,jj) = max(zvolp(ji,jj) - drain, 0._wp) 
     926                IF (zvolp(ji,jj) < epsi10) THEN 
     927                   zdvolp(ji,jj) = zdvolp(ji,jj) + zvolp(ji,jj) 
     928                   zvolp(ji,jj) = 0._wp 
    933929                END IF 
    934930            END IF 
     
    938934          IF (permflag > 0) THEN 
    939935             ! recompute pond depth 
    940             CALL ice_thd_pnd_depth(reduced_aicen, asnon, hsnon, alfan, zvolp, cum_max_vol, hpond, m_index) 
    941              DO n=1, m_index 
    942                 zhpondn(n) = hpond - alfan(n) + alfan(1) 
    943                 zapondn(n) = reduced_aicen(n) 
     936            CALL ice_thd_pnd_depth(reduced_aicen, asnon, hsnon, alfan, zvolp(ji,jj), cum_max_vol, hpond, m_index) 
     937             DO jl = 1, m_index 
     938                h_ip(ji,jj,jl) = hpond - alfan(jl) + alfan(1) 
     939                a_ip(ji,jj,jl) = reduced_aicen(jl) 
    944940             END DO 
    945              !zapond = sum(zapondn(1:m_index))       !js: from CICE 5.1.2; not in Icepack1.1.0-6-gac6195d 
     941             !zapond = sum(a_ip(1:m_index))       !js: from CICE 5.1.2; not in Icepack1.1.0-6-gac6195d 
    946942          END IF 
    947943       END IF ! pressure_head 
    948944 
    949945       !------------------------------- 
    950        ! X) remove water from the snow 
     946       ! remove water from the snow 
    951947       !------------------------------- 
    952948       !------------------------------------------------------------------------ 
     
    956952 
    957953       ! Calculate pond volume for lower categories 
    958        DO n=1,m_index-1 
    959           zvolpn(n) = zapondn(n) * zhpondn(n) & ! what is not in the snow 
    960                    - (rhos/rhow) * asnon(n) * min(hsnon(n), zhpondn(n)) 
     954       DO jl = 1,m_index-1 
     955          v_ip(ji,jj,jl) = a_ip(ji,jj,jl) * h_ip(ji,jj,jl) & ! what is not in the snow 
     956                     - (rhos/rhow) * asnon(jl) * min(hsnon(jl), h_ip(ji,jj,jl)) 
    961957       END DO 
    962958 
     
    968964       ! m_index = last category with melt pond 
    969965 
    970        IF (m_index == 1) zvolpn(m_index) = zvolp ! volume of mw in 1st category is the total volume of melt water 
     966       IF (m_index == 1) v_ip(ji,jj,m_index) = zvolp(ji,jj) ! volume of mw in 1st category is the total volume of melt water 
    971967 
    972968       IF (m_index > 1) THEN 
    973          IF (zvolp > sum(zvolpn(1:m_index-1))) THEN 
    974            zvolpn(m_index) = zvolp - sum(zvolpn(1:m_index-1)) 
     969         IF (zvolp(ji,jj) > sum( v_ip(ji,jj,1:m_index-1))) THEN 
     970            v_ip(ji,jj,m_index) = zvolp(ji,jj) - sum(v_ip(ji,jj,1:m_index-1)) 
    975971         ELSE 
    976            zvolpn(m_index) = 0._wp  
    977            zhpondn(m_index) = 0._wp 
    978            zapondn(m_index) = 0._wp 
    979            ! If remaining pond volume is negative reduce pond volume of 
    980            ! lower category 
    981            IF (zvolp+epsi10 < sum(zvolpn(1:m_index-1))) & 
    982              zvolpn(m_index-1) = zvolpn(m_index-1) - sum(zvolpn(1:m_index-1)) + zvolp 
     972            v_ip(ji,jj,m_index) = 0._wp  
     973            h_ip(ji,jj,m_index) = 0._wp 
     974            a_ip(ji,jj,m_index) = 0._wp 
     975            ! If remaining pond volume is negative reduce pond volume of 
     976            ! lower category 
     977            IF ( zvolp(ji,jj) + epsi10 < SUM(v_ip(ji,jj,1:m_index-1))) & 
     978             v_ip(ji,jj,m_index-1) = v_ip(ji,jj,m_index-1) - sum(v_ip(ji,jj,1:m_index-1)) + zvolp(ji,jj) 
    983979         END IF 
    984980       END IF 
    985981 
    986        DO n=1,m_index 
    987           IF (zapondn(n) > epsi10) THEN 
    988               zhpondn(n) = zvolpn(n) / zapondn(n) 
     982       DO jl = 1,m_index 
     983          IF (a_ip(ji,jj,jl) > epsi10) THEN 
     984              h_ip(ji,jj,jl) = v_ip(ji,jj,jl) / a_ip(ji,jj,jl) 
    989985          ELSE 
    990              dvolp = dvolp + zvolpn(n) 
    991              zhpondn(n) = 0._wp  
    992              zvolpn(n)  = 0._wp 
    993              zapondn(n) = 0._wp 
     986             zdvolp(ji,jj) = zdvolp(ji,jj) + v_ip(ji,jj,jl) 
     987             h_ip(ji,jj,jl) = 0._wp  
     988             v_ip(ji,jj,jl)  = 0._wp 
     989             a_ip(ji,jj,jl) = 0._wp 
    994990          END IF 
    995991       END DO 
    996        DO n = m_index+1, jpl 
    997           zhpondn(n) = 0._wp  
    998           zapondn(n) = 0._wp  
    999           zvolpn (n) = 0._wp  
     992       DO jl = m_index+1, jpl 
     993          h_ip(ji,jj,jl) = 0._wp  
     994          a_ip(ji,jj,jl) = 0._wp  
     995          v_ip(ji,jj,jl) = 0._wp  
    1000996       END DO 
     997        
     998          ENDIF 
     999       END DO ! ji 
     1000    END DO ! jj 
    10011001 
    10021002    END SUBROUTINE ice_thd_pnd_area 
Note: See TracChangeset for help on using the changeset viewer.