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

Changeset 7319


Ignore:
Timestamp:
2016-11-23T12:33:41+01:00 (7 years ago)
Author:
vancop
Message:

Sea ice model infrastructure for melt ponds part 2 (advection, transport in thickness space, ridging/rafting)

Location:
branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/ice.F90

    r7306 r7319  
    272272   REAL(wp), PUBLIC ::   rn_por_rdg       !: initial porosity of ridges (0.3 regular value) 
    273273   REAL(wp), PUBLIC ::   rn_fsnowrdg      !: fractional snow loss to the ocean during ridging 
     274   REAL(wp), PUBLIC ::   rn_fpondrdg      !: fractional melt pond loss to the ocean during ridging 
    274275   LOGICAL , PUBLIC ::   ln_rafting       !: rafting of ice or not                         
    275276   REAL(wp), PUBLIC ::   rn_hraft         !: threshold thickness (m) for rafting / ridging  
    276277   REAL(wp), PUBLIC ::   rn_craft         !: coefficient for smoothness of the hyperbolic tangent in rafting 
    277278   REAL(wp), PUBLIC ::   rn_fsnowrft      !: fractional snow loss to the ocean during ridging 
     279   REAL(wp), PUBLIC ::   rn_fpondrft      !: fractional snow loss to the ocean during rafting 
    278280 
    279281   ! MV MP 2016 
     
    316318 
    317319   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: snow-ocean mass exchange   [kg.m-2.s-1] 
     320   ! MV MP 2016 
     321   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_pnd     !: melt pond-ocean mass exchange   [kg.m-2.s-1] 
     322   ! END MV MP 2016 
    318323   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_spr     !: snow precipitation on ice  [kg.m-2.s-1] 
    319324   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sub     !: snow/ice sublimation       [kg.m-2.s-1] 
     
    498503      ALLOCATE( t_bo   (jpi,jpj) , frld   (jpi,jpj) , pfrld  (jpi,jpj) , phicif (jpi,jpj) ,     & 
    499504         &      wfx_snw(jpi,jpj) , wfx_ice(jpi,jpj) , wfx_sub(jpi,jpj) , wfx_lam(jpi,jpj) ,     & 
     505         ! MV MP 2016 
     506         &      wfx_pnd(jpi,jpj) ,                                                              & 
     507         ! END MV MP 2016 
    500508         &      wfx_bog(jpi,jpj) , wfx_dyn(jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,     & 
    501509         &      wfx_res(jpi,jpj) , wfx_sni(jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,     & 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90

    r7306 r7319  
    418418      ! 
    419419      IF ( ln_limMP ) THEN 
    420          a_ip(:,:,:) = 0._wp 
    421          v_ip(:,:,:) = 0._wp 
     420         a_ip(:,:,:) = 0.1_wp 
     421         v_ip(:,:,:) = 0.1_wp 
    422422         h_ip(:,:,:) = 0._wp 
    423423         a_ip_frac(:,:,:) = 0._wp 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limitd_me.F90

    r6994 r7319  
    507507      REAL(wp), POINTER, DIMENSION(:) ::   ardg1 , ardg2    ! area of ice ridged & new ridges 
    508508      REAL(wp), POINTER, DIMENSION(:) ::   vsrdg , esrdg    ! snow volume & energy of ridging ice 
     509      ! MV MP 2016 
     510      REAL(wp), POINTER, DIMENSION(:) ::   vprdg            ! pond volume of ridging ice 
     511      ! END MV MP 2016 
    509512      REAL(wp), POINTER, DIMENSION(:) ::   dhr   , dhr2     ! hrmax - hrmin  &  hrmax^2 - hrmin^2 
    510513 
     
    520523      REAL(wp), POINTER, DIMENSION(:) ::   arft1 , arft2    ! area of ice rafted and new rafted zone 
    521524      REAL(wp), POINTER, DIMENSION(:) ::   virft , vsrft    ! ice & snow volume of rafting ice 
     525      ! MV MP 2016 
     526      REAL(wp), POINTER, DIMENSION(:) ::   vprft            ! pond volume of rafting ice 
     527      ! END MV MP 2016 
    522528      REAL(wp), POINTER, DIMENSION(:) ::   esrft , smrft    ! snow energy & salinity of rafting ice 
    523529      REAL(wp), POINTER, DIMENSION(:) ::   oirft1, oirft2   ! ice age of ice rafted 
     
    531537      CALL wrk_alloc( jpij,        indxi, indxj ) 
    532538      CALL wrk_alloc( jpij,        zswitch, fvol ) 
    533       CALL wrk_alloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, dhr, dhr2 ) 
     539      ! MV MP 2016 
     540      !CALL wrk_alloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, dhr, dhr2 ) 
     541      CALL wrk_alloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, vprdg, dhr, dhr2 ) 
     542      ! END MV MP 2016 
    534543      CALL wrk_alloc( jpij,        vrdg1, vrdg2, vsw  , srdg1, srdg2, smsw, oirdg1, oirdg2 ) 
    535       CALL wrk_alloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, smrft, oirft1, oirft2 ) 
     544      ! MV MP 2016 
     545      !CALL wrk_alloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, smrft, oirft1, oirft2 ) 
     546      CALL wrk_alloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, vprft, smrft, oirft1, oirft2 ) 
     547      ! END MV MP 2016 
    536548      CALL wrk_alloc( jpij,nlay_i, eirft, erdg1, erdg2, ersw ) 
    537549 
     
    595607            vsrdg (ij) = v_s  (ji,jj,  jl1) * afrac(ij) 
    596608            esrdg (ij) = e_s  (ji,jj,1,jl1) * afrac(ij) 
     609            !MV MP 2016 
     610            IF ( ln_limMP ) THEN 
     611               vprdg(ij) = v_ip(ji,jj, jl1) * afrac(ij) 
     612            ENDIF 
     613            ! END MV MP 2016 
    597614            srdg1 (ij) = smv_i(ji,jj,  jl1) * afrac(ij) 
    598615            oirdg1(ij) = oa_i (ji,jj,  jl1) * afrac(ij) 
     
    602619            virft (ij) = v_i  (ji,jj,  jl1) * afrft(ij) 
    603620            vsrft (ij) = v_s  (ji,jj,  jl1) * afrft(ij) 
     621            !MV MP 2016 
     622            IF ( ln_limMP ) THEN 
     623               vprft(ij) = v_ip(ji,jj,jl1) * afrft(ij) 
     624            ENDIF 
     625            ! END MV MP 2016 
     626            srdg1 (ij) = smv_i(ji,jj,  jl1) * afrac(ij) 
    604627            esrft (ij) = e_s  (ji,jj,1,jl1) * afrft(ij) 
    605628            smrft (ij) = smv_i(ji,jj,  jl1) * afrft(ij)  
     
    637660               &                                - esrft(ij) * ( 1._wp - rn_fsnowrft ) ) * r1_rdtice        ! heat sink for ocean (<0, W.m-2) 
    638661 
     662            ! MV MP 2016 
     663            !------------------------------------------             
     664            ! 3.X Put the melt pond water in the ocean 
     665            !------------------------------------------             
     666            !  Place part of the melt pond volume into the ocean.  
     667            IF ( ln_limMP .AND. ( ( nn_limMP .EQ. 3 ) .OR. ( nn_limMP .EQ. 1 ) ) )  THEN 
     668               wfx_pnd(ji,jj) = wfx_pnd(ji,jj) + ( rhofw * vprdg(ij) * ( 1._wp - rn_fpondrdg )   &  
     669               &                                 + rhofw * vprft(ij) * ( 1._wp - rn_fpondrft ) ) * r1_rdtice  ! fresh water source for ocean 
     670            ENDIF 
     671            ! END MV MP 2016 
     672 
    639673            !----------------------------------------------------------------- 
    640674            ! 3.8 Compute quantities used to apportion ice among categories 
     
    652686            smv_i(ji,jj,  jl1) = smv_i(ji,jj,  jl1) - srdg1 (ij) - smrft (ij) 
    653687            oa_i (ji,jj,  jl1) = oa_i (ji,jj,  jl1) - oirdg1(ij) - oirft1(ij) 
     688 
     689            ! MV MP 2016 
     690            IF ( ln_limMP ) THEN 
     691               v_ip (ji,jj,jl1) = v_ip (ji,jj,jl1) - vprdg (ij) - vprft (ij) 
     692            ENDIF 
     693            ! END MV MP 2016 
    654694 
    655695         END DO 
     
    716756               e_s  (ji,jj,1,jl2) = e_s  (ji,jj,1,jl2) + ( esrdg (ij) * rn_fsnowrdg * fvol(ij)  +  & 
    717757                  &                                        esrft (ij) * rn_fsnowrft * zswitch(ij) ) 
     758               ! MV MP 2016 
     759               IF ( ln_limMP ) THEN 
     760                  v_ip (ji,jj,jl2) = v_ip (ji,jj,jl2)  + ( vprdg (ij) * rn_fpondrdg * fvol(ij)  +  & 
     761                  &                                        vprft (ij) * rn_fpondrft * zswitch(ij) ) 
     762               ENDIF 
     763               ! END MV MP 2016 
    718764 
    719765            END DO 
     
    734780      CALL wrk_dealloc( jpij,        indxi, indxj ) 
    735781      CALL wrk_dealloc( jpij,        zswitch, fvol ) 
    736       CALL wrk_dealloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, dhr, dhr2 ) 
     782      ! MV MP 2016 
     783      !CALL wrk_dealloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, dhr, dhr2 ) 
     784      CALL wrk_dealloc( jpij,        afrac, ardg1, ardg2, vsrdg, esrdg, vprdg, dhr, dhr2 ) 
     785      ! END MV MP 2016 
    737786      CALL wrk_dealloc( jpij,        vrdg1, vrdg2, vsw  , srdg1, srdg2, smsw, oirdg1, oirdg2 ) 
    738       CALL wrk_dealloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, smrft, oirft1, oirft2 ) 
     787      ! MV MP 2016 
     788      !CALL wrk_dealloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, smrft, oirft1, oirft2 ) 
     789      CALL wrk_dealloc( jpij,        afrft, arft1, arft2, virft, vsrft, esrft, vprft, smrft, oirft1, oirft2 ) 
    739790      CALL wrk_dealloc( jpij,nlay_i, eirft, erdg1, erdg2, ersw ) 
    740791      ! 
     
    915966      INTEGER :: ios                 ! Local integer output status for namelist read 
    916967      NAMELIST/namiceitdme/ rn_cs, nn_partfun, rn_gstar, rn_astar,             &  
    917         &                   ln_ridging, rn_hstar, rn_por_rdg, rn_fsnowrdg, ln_rafting, rn_hraft, rn_craft, rn_fsnowrft 
     968        &                   ln_ridging, rn_hstar, rn_por_rdg, rn_fsnowrdg, rn_fpondrdg, &  
     969                            ln_rafting, rn_hraft, rn_craft,   rn_fsnowrft, rn_fpondrft 
    918970      !!------------------------------------------------------------------- 
    919971      ! 
     
    939991         WRITE(numout,*)'   Initial porosity of ridges                              rn_por_rdg  = ', rn_por_rdg 
    940992         WRITE(numout,*)'   Fraction of snow volume conserved during ridging        rn_fsnowrdg = ', rn_fsnowrdg  
     993         WRITE(numout,*)'   Fraction of pond volume conserved during ridging        rn_fpondrdg = ', rn_fpondrdg  
    941994         WRITE(numout,*)'   Rafting of ice sheets or not                            ln_rafting  = ', ln_rafting 
    942995         WRITE(numout,*)'   Parmeter thickness (threshold between ridge-raft)       rn_hraft    = ', rn_hraft 
    943996         WRITE(numout,*)'   Rafting hyperbolic tangent coefficient                  rn_craft    = ', rn_craft   
    944997         WRITE(numout,*)'   Fraction of snow volume conserved during ridging        rn_fsnowrft = ', rn_fsnowrft  
     998         WRITE(numout,*)'   Fraction of pond volume conserved during rafting        rn_fpondrft = ', rn_fpondrft  
    945999      ENDIF 
    9461000      ! 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limitd_th.F90

    r6746 r7319  
    357357         IF ( a_i(ii,ij,1) > epsi10 .AND. ht_i(ii,ij,1) < rn_himin ) THEN 
    358358            a_i (ii,ij,1) = a_i(ii,ij,1) * ht_i(ii,ij,1) / rn_himin  
     359            ! MV MP 2016 
     360            IF ( ln_limMP ) THEN 
     361               a_ip(ii,ij,1) = a_ip(ii,ij,1) * ht_i(ii,ij,1) / rn_himin 
     362            ENDIF 
     363            ! END MV MP 2016 
    359364            ht_i(ii,ij,1) = rn_himin 
    360365         ENDIF 
     
    485490      REAL(wp) ::   zdo_aice           ! ice age times volume transferred 
    486491      REAL(wp) ::   zdaTsf             ! aicen*Tsfcn transferred 
     492      ! MV MP 2016  
     493      REAL(wp) ::   zdapnd             ! pond fraction transferred 
     494      REAL(wp) ::   zdvpnd             ! pond volume transferred 
     495      ! END MV MP 2016  
    487496 
    488497      INTEGER, POINTER, DIMENSION(:) ::   nind_i, nind_j   ! compressed indices for i/j directions 
     
    576585            zaTsfn(ii,ij,jl1)  = zaTsfn(ii,ij,jl1) - zdaTsf 
    577586            zaTsfn(ii,ij,jl2)  = zaTsfn(ii,ij,jl2) + zdaTsf  
     587 
     588            ! MV MP 2016  
     589            IF ( ln_limMP ) THEN 
     590            !--------------------- 
     591            ! Pond fraction 
     592            !--------------------- 
     593               zdapnd             = a_ip(ii,ij,jl1) * zdaice(ii,ij,jl) 
     594               a_ip(ii,ij,jl1)    = a_ip(ii,ij,jl1) - zdapnd 
     595               a_ip(ii,ij,jl2)    = a_ip(ii,ij,jl2) + zdapnd 
     596 
     597            !--------------------- 
     598            ! Pond volume 
     599            !--------------------- 
     600               zdvpnd             = v_ip(ii,ij,jl1) * zdaice(ii,ij,jl) 
     601               v_ip(ii,ij,jl1)    = v_ip(ii,ij,jl1) - zdvpnd 
     602               v_ip(ii,ij,jl2)    = v_ip(ii,ij,jl2) + zdvpnd 
     603 
     604            ENDIF 
     605            ! END MV MP 2016  
    578606 
    579607         END DO 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limtrp.F90

    r6994 r7319  
    7676      ! --- diffusion --- ! 
    7777      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   zhdfptab 
    78       INTEGER , PARAMETER                    ::   ihdf_vars  = 6 ! Number of variables in which we apply horizontal diffusion 
     78      ! MV MP 2016 
     79      ! With melt ponds, we have to diffuse them 
     80      ! We hard code the number of variables to diffuse 
     81      ! since we can't put an IF ( ln_limMP ) for a declaration 
     82      ! ideally, the ihdf_vars should probably be passed as an argument and 
     83      ! defined somewhere depending on ln_limMP 
     84      ! END MV MP 2016 
     85      INTEGER , PARAMETER                    ::   ihdf_vars  = 8 ! Number of variables in which we apply horizontal diffusion 
    7986                                                                 !  inside limtrp for each ice category , not counting the  
    8087                                                                 !  variables corresponding to ice_layers  
     
    8693      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   z0opw 
    8794      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   z0ice, z0snw, z0ai, z0es , z0smi , z0oi 
     95      ! MV MP 2016 
     96      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   z0ap , z0vp 
     97      REAL(wp) ::   za_old 
     98      ! END MV MP 2016 
    8899      REAL(wp), POINTER, DIMENSION(:,:,:,:)  ::   z0ei 
    89100      !! 
     
    205216               CALL lim_adv_umx( kt, zdt, zudy, zvdx, zcu_box, zcv_box, v_s(:,:,jl) )      ! Snow volume 
    206217               CALL lim_adv_umx( kt, zdt, zudy, zvdx, zcu_box, zcv_box, e_s(:,:,1,jl) )    ! Snow heat content 
     218               ! MV MP 2016 
     219               IF ( ln_limMP ) THEN 
     220                  CALL lim_adv_umx( kt, zdt, zudy, zvdx, zcu_box, zcv_box, a_ip(:,:,jl) )  ! Melt pond fraction 
     221                  CALL lim_adv_umx( kt, zdt, zudy, zvdx, zcu_box, zcv_box, v_ip(:,:,jl) )  ! Melt pond volume 
     222               ENDIF 
     223               ! END MV MP 2016 
    207224            END DO 
    208225         END DO 
     
    222239         CALL wrk_alloc( jpi,jpj,1,          z0opw ) 
    223240         CALL wrk_alloc( jpi,jpj,jpl,        z0ice, z0snw, z0ai, z0es , z0smi , z0oi ) 
     241         CALL wrk_alloc( jpi,jpj,jpl,        z0ap , z0vp ) 
    224242         CALL wrk_alloc( jpi,jpj,nlay_i,jpl, z0ei ) 
    225243          
     
    246264               z0ei  (:,:,jk,jl) = e_i  (:,:,jk,jl) * e12t(:,:) ! Ice  heat content 
    247265            END DO 
     266            ! MV MP 2016 
     267            IF ( ln_limMP ) THEN 
     268               z0ap  (:,:,jl)  = a_ip (:,:,jl) * e12t(:,:) ! Melt pond fraction 
     269               z0vp  (:,:,jl)  = v_ip (:,:,jl) * e12t(:,:) ! Melt pond volume 
     270            ENDIF 
     271            ! END MV MP 2016 
     272 
    248273         END DO 
    249274          
     
    288313                        &                                         syye(:,:,jk,jl), sxye(:,:,jk,jl) ) 
    289314                  END DO 
     315                  ! MV MP 2016 
     316                  CALL lim_adv_x( zusnit, u_ice, 1._wp, zarea, z0ap  (:,:,jl), sxap (:,:,jl),   &    !--- melt pond fraction -- 
     317                     &                                         sxxap (:,:,jl), syap (:,:,jl), syyap (:,:,jl), sxyap (:,:,jl)  ) 
     318                  CALL lim_adv_y( zusnit, v_ice, 0._wp, zarea, z0ap  (:,:,jl), sxap (:,:,jl),   &  
     319                     &                                         sxxap (:,:,jl), syap (:,:,jl), syyap (:,:,jl), sxyap (:,:,jl)  ) 
     320                  CALL lim_adv_x( zusnit, u_ice, 1._wp, zarea, z0vp  (:,:,jl), sxvp (:,:,jl),   &    !--- melt pond volume   -- 
     321                     &                                         sxxvp (:,:,jl), syvp (:,:,jl), syyvp (:,:,jl), sxyvp (:,:,jl)  ) 
     322                  CALL lim_adv_y( zusnit, v_ice, 0._wp, zarea, z0vp  (:,:,jl), sxvp (:,:,jl),   &  
     323                     &                                         sxxvp (:,:,jl), syvp (:,:,jl), syyvp (:,:,jl), sxyvp (:,:,jl)  ) 
     324                  ! END MV MP 2016 
    290325               END DO 
    291326            END DO 
     
    329364                        &                                         syye(:,:,jk,jl), sxye(:,:,jk,jl) ) 
    330365                  END DO 
     366                  ! MV MP 2016 
     367                  IF ( ln_limMP ) THEN 
     368                     CALL lim_adv_y( zusnit, v_ice, 1._wp, zarea, z0ap  (:,:,jl), sxap (:,:,jl),   &   !--- melt pond fraction --- 
     369                     &                                         sxxap (:,:,jl), syap (:,:,jl), syyap (:,:,jl), sxyap (:,:,jl)  ) 
     370                     CALL lim_adv_x( zusnit, u_ice, 0._wp, zarea, z0ap  (:,:,jl), sxap (:,:,jl),   & 
     371                     &                                         sxxap (:,:,jl), syap (:,:,jl), syyap (:,:,jl), sxyap (:,:,jl)  ) 
     372                     CALL lim_adv_y( zusnit, v_ice, 1._wp, zarea, z0vp  (:,:,jl), sxvp (:,:,jl),   &   !--- melt pond volume   --- 
     373                     &                                         sxxvp (:,:,jl), syvp (:,:,jl), syyvp (:,:,jl), sxyvp (:,:,jl)  ) 
     374                     CALL lim_adv_x( zusnit, u_ice, 0._wp, zarea, z0vp  (:,:,jl), sxvp (:,:,jl),   & 
     375                     &                                         sxxvp (:,:,jl), syvp (:,:,jl), syyvp (:,:,jl), sxyvp (:,:,jl)  ) 
     376                  ENDIF 
     377                  ! END MV MP 2016 
    331378               END DO 
    332379            END DO 
     
    347394               e_i(:,:,jk,jl) = z0ei(:,:,jk,jl) * r1_e12t(:,:) 
    348395            END DO 
     396            ! MV MP 2016 
     397            IF ( ln_limMP ) THEN 
     398               a_ip  (:,:,jl)   = z0ap (:,:,jl) * r1_e12t(:,:) 
     399               v_ip  (:,:,jl)   = z0vp (:,:,jl) * r1_e12t(:,:) 
     400            ENDIF 
     401            ! END MV MP 2016 
    349402         END DO 
    350403          
     
    357410         CALL wrk_dealloc( jpi,jpj,1,          z0opw ) 
    358411         CALL wrk_dealloc( jpi,jpj,jpl,        z0ice, z0snw, z0ai, z0es , z0smi , z0oi ) 
     412         ! MV MP 2016 
     413         CALL wrk_dealloc( jpi,jpj,jpl,        z0ap , z0vp ) 
     414         ! END MV MP 2016 
    359415         CALL wrk_dealloc( jpi,jpj,nlay_i,jpl, z0ei ) 
    360416 
     
    385441            zhdfptab(:,:,jm)= oa_i (:,:,  jl); jm = jm + 1 
    386442            zhdfptab(:,:,jm)= e_s  (:,:,1,jl); jm = jm + 1 
     443            ! MV MP 2016 
     444            IF ( ln_limMP ) THEN 
     445               zhdfptab(:,:,jm)= a_ip  (:,:,  jl); jm = jm + 1 
     446               zhdfptab(:,:,jm)= v_ip  (:,:,  jl); jm = jm + 1 
     447            ENDIF 
     448            ! END MV MP 2016 
    387449            ! Sample of adding more variables to apply lim_hdf (ihdf_vars must be increased) 
    388450            !   zhdfptab(:,:,jm) = variable_1 (:,:,1,jl); jm = jm + 1   
     
    418480            oa_i (:,:,  jl) = zhdfptab(:,:,jm); jm = jm + 1 
    419481            e_s  (:,:,1,jl) = zhdfptab(:,:,jm); jm = jm + 1 
     482            ! MV MP 2016 
     483            IF ( ln_limMP ) THEN 
     484               a_ip (:,:,  jl) = zhdfptab(:,:,jm); jm = jm + 1 
     485               v_ip (:,:,  jl) = zhdfptab(:,:,jm); jm = jm + 1 
     486            ENDIF 
    420487            ! Sample of adding more variables to apply lim_hdf 
    421488            !   variable_1  (:,:,1,jl) = zhdfptab(:,:, jm  ) ; jm + 1  
     
    470537                        e_s(ji,jj,1,jl)        = rswitch * e_s(ji,jj,1,jl) 
    471538                        e_i(ji,jj,1:nlay_i,jl) = rswitch * e_i(ji,jj,1:nlay_i,jl) 
     539 
     540                        ! MV MP 2016 
     541                        IF ( ln_limMP ) THEN 
     542                           a_ip (ji,jj,jl)        = rswitch * a_ip (ji,jj,jl) 
     543                           v_ip (ji,jj,jl)        = rswitch * v_ip (ji,jj,jl) 
     544                        ENDIF 
     545                        ! END MV MP 2016 
    472546                                                 
    473547                     ENDIF 
     
    482556         DO jj = 1, jpj 
    483557            DO ji = 1, jpi 
     558               ! MV MP 2016 
     559               za_old = a_i(ji,jj,jpl) 
     560               ! END MV MP 2016 
    484561               rswitch         = MAX( 0._wp , SIGN( 1._wp, ht_i(ji,jj,jpl) - epsi20 ) ) 
    485562               ht_i(ji,jj,jpl) = MIN( ht_i(ji,jj,jpl) , hi_max(jpl) ) 
    486563               a_i (ji,jj,jpl) = v_i(ji,jj,jpl) / MAX( ht_i(ji,jj,jpl) , epsi20 ) * rswitch 
    487             END DO 
    488          END DO 
     564               ! MV MP 2016 
     565               IF ( ln_limMP ) THEN 
     566                  ! correct pond fraction to avoid a_ip > a_i 
     567                  a_ip(ji,jj,jpl) = a_ip(ji,jj,jpl) * a_i(ji,jj,jpl) / MAX( za_old , epsi20 ) * rswitch 
     568               ENDIF 
     569               ! END MP 2016 
     570            END DO 
     571         END DO 
     572 
    489573 
    490574      ENDIF 
     
    512596      vt_s(:,:) = SUM( v_s(:,:,:), dim=3 ) 
    513597      at_i(:,:) = SUM( a_i(:,:,:), dim=3 ) 
     598 
     599      ! MV MP 2016 (remove once we get rid of a_i_frac and ht_i) 
     600      IF ( ln_limMP ) THEN 
     601          at_ip(:,:) = SUM( a_ip(:,:,:), dim = 3 ) 
     602          vt_ip(:,:) = SUM( v_ip(:,:,:), dim = 3 ) 
     603      ENDIF 
     604      ! END MP 2016 
    514605       
    515606      ! --- open water = 1 if at_i=0 -------------------------------- 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/OPA_SRC/DOM/phycst.F90

    r5147 r7319  
    5555 
    5656   REAL(wp), PUBLIC ::   rhosn    =  330._wp         !: volumic mass of snow          [kg/m3] 
     57   ! MV MP 2016 
     58   REAL(wp), PUBLIC ::   rhofw    = 1000._wp         !: volumic mass of freshwater in melt ponds [kg/m3] 
     59   ! END MV MP 2016 
    5760   REAL(wp), PUBLIC ::   emic     =    0.97_wp       !: emissivity of snow or ice 
    5861   REAL(wp), PUBLIC ::   sice     =    6.0_wp        !: salinity of ice               [psu] 
     
    192195         WRITE(numout,*) '          density of sea ice                        = ', rhoic   , ' kg/m^3' 
    193196         WRITE(numout,*) '          density of snow                           = ', rhosn   , ' kg/m^3' 
     197         WRITE(numout,*) '          density of freshwater (in melt ponds)     = ', rhofw   , ' kg/m^3' 
    194198         WRITE(numout,*) '          emissivity of snow or ice                 = ', emic   
    195199         WRITE(numout,*) '          salinity of ice                           = ', sice    , ' psu' 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r7293 r7319  
    658658      wfx_res(:,:) = 0._wp   ;   wfx_sub(:,:) = 0._wp 
    659659      wfx_spr(:,:) = 0._wp   ;   wfx_lam(:,:) = 0._wp   
     660 
     661      ! MV MP 2016 
     662      wfx_pnd(:,:) = 0._wp 
     663      ! END MV MP 2016 
    660664       
    661665      hfx_thd(:,:) = 0._wp   ;    
Note: See TracChangeset for help on using the changeset viewer.