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

Changeset 8179


Ignore:
Timestamp:
2017-06-15T12:01:17+02:00 (7 years ago)
Author:
vancop
Message:

Replace total snow flux by snow meltwater flux

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

Legend:

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

    r8125 r8179  
    323323   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: snow-ocean mass exchange   [kg.m-2.s-1] 
    324324   ! MV MP 2016 
     325   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sum !: surface melt component of wfx_snw [kg.m-2.s-1] 
    325326   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_pnd     !: melt pond-ocean mass exchange   [kg.m-2.s-1] 
    326327   ! END MV MP 2016 
     
    508509         &      wfx_snw(jpi,jpj) , wfx_ice(jpi,jpj) , wfx_sub(jpi,jpj) , wfx_lam(jpi,jpj) ,     & 
    509510         ! MV MP 2016 
    510          &      wfx_pnd(jpi,jpj) ,                                                              & 
     511         &      wfx_pnd(jpi,jpj) , wfx_snw_sum(jpi,jpj) ,                                       & 
    511512         ! END MV MP 2016 
    512513         &      wfx_bog(jpi,jpj) , wfx_dyn(jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,     & 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limmp.F90

    r8142 r8179  
    129129      ENDIF 
    130130 
     131      IF ( ln_pnd .AND. ( nn_pnd_scheme == 0 ) .AND. ( ln_pnd_fw ) ) THEN 
     132         WRITE(numout,*) ' Prescribed melt ponds do not conserve fresh water mass, hence ln_pnd_fw must be set to false '  
     133         ln_pnd_fw     = .FALSE. 
     134         IF(lwp) THEN                     ! control print 
     135            WRITE(numout,*) '    Active melt ponds freshwater coupling                       ln_pnd_fw     = ', ln_pnd_fw 
     136         ENDIF 
     137      ENDIF 
     138 
    131139      IF ( ln_pnd .AND. ( nn_pnd_scheme == 2 ) .AND. ( jpl == 1 ) ) THEN 
    132140         WRITE(numout,*) ' Topographic melt ponds are incompatible with jpl = 1 ' 
     
    280288        !------------------------------------------------------------------ 
    281289  
    282         zwfx_mlw(:,:) = MAX( wfx_sum(:,:) + wfx_snw(:,:), 0._wp )        ! available meltwater for melt ponding 
     290        zwfx_mlw(:,:) = MAX( wfx_sum(:,:) + wfx_snw_sum(:,:), 0._wp )        ! available meltwater for melt ponding 
    283291 
    284292                ! NB: zwfx_mlw can be slightly negative for very small values (why?) 
     
    289297                ! if we understand and remove why wfx_sum or wfx_snw could be 
    290298                ! negative, then, we can remove the MAX 
     299                ! NB: I now changed to wfx_snw_sum, this may fix the problem.  
     300                ! We should check 
    291301  
    292302        zrfrac(:,:,:) = zrmin + ( zrmax - zrmin ) * a_i(:,:,:)   
     
    352362  
    353363                a_ip_frac(ji,jj,jl) = MIN( 1._wp , SQRT( v_ip(ji,jj,jl) * z1_zpnd_aspect / a_i(ji,jj,jl) ) ) 
     364                   !NB: the SQRT has been a recurring source of crash when v_ip or a_i tuns to be even only slightly negative 
    354365  
    355366                h_ip(ji,jj,jl)      = zpnd_aspect * a_ip_frac(ji,jj,jl) 
     
    374385        IF ( ln_pnd_fw ) THEN 
    375386  
    376             wfx_snw(:,:) = wfx_snw(:,:) *  ( 1. - zrmin - ( zrmax - zrmin ) * at_i(:,:) ) 
    377   
    378             wfx_sum(:,:) = wfx_sum(:,:) * ( 1. - zrmin - ( zrmax - zrmin ) * at_i(:,:) ) 
    379   
     387            wfx_snw_sum(:,:) = wfx_snw_sum(:,:) *  ( 1. - zrmin - ( zrmax - zrmin ) * at_i(:,:) )  
     388 
     389            wfx_sum(:,:)     = wfx_sum(:,:) * ( 1. - zrmin - ( zrmax - zrmin ) * at_i(:,:) ) 
     390 
    380391        ENDIF 
    381392 
     
    496507       kcells(:)   = 0 
    497508 
    498        zvolp(:,:) = wfx_sum(:,:) + wfx_snw(:,:) + vt_ip(:,:) ! Total available melt water, to be distributed as melt ponds 
     509       zvolp(:,:) = wfx_sum(:,:) + wfx_snw_sum(:,:) + vt_ip(:,:) ! Total available melt water, to be distributed as melt ponds 
    499510       zTsfcn(:,:,:) = zTsfcn(:,:,:) - rt0                   ! Convert in Celsius 
    500511  
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r8142 r8179  
    177177            IF ( ln_pnd_fw ) & 
    178178               wfx_ice(ji,jj) = wfx_ice(ji,jj) + wfx_pnd(ji,jj) 
     179 
     180            ! add the snow melt water to snow mass flux to the ocean 
     181            wfx_snw(:,:)      = wfx_snw(:,:) + wfx_snw_sum(:,:)  
    179182 
    180183            ! mass flux at the ocean/ice interface 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limthd.F90

    r6994 r8179  
    463463          
    464464         CALL tab_2d_1d( nbpb, wfx_snw_1d (1:nbpb), wfx_snw         , jpi, jpj, npb(1:nbpb) ) 
     465         CALL tab_2d_1d( nbpb, wfx_snw_sum_1d(1:nbpb), wfx_snw_sum  , jpi, jpj, npb(1:nbpb) ) 
    465466         CALL tab_2d_1d( nbpb, wfx_sub_1d (1:nbpb), wfx_sub         , jpi, jpj, npb(1:nbpb) ) 
    466467          
     
    514515          
    515516         CALL tab_1d_2d( nbpb, wfx_snw       , npb, wfx_snw_1d(1:nbpb)   , jpi, jpj ) 
     517         CALL tab_1d_2d( nbpb, wfx_snw_sum   , npb, wfx_snw_sum_1d(1:nbpb),jpi, jpj ) 
    516518         CALL tab_1d_2d( nbpb, wfx_sub       , npb, wfx_sub_1d(1:nbpb)   , jpi, jpj ) 
    517519          
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/limthd_dh.F90

    r6994 r8179  
    169169            hfx_res_1d(ji) = hfx_res_1d(ji) + q_s_1d(ji,1) * ht_s_1d(ji) * a_i_1d(ji) * r1_rdtice 
    170170            ! Contribution to mass flux 
    171             wfx_snw_1d(ji) = wfx_snw_1d(ji) + rhosn * ht_s_1d(ji) * a_i_1d(ji) * r1_rdtice 
     171            wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) + rhosn * ht_s_1d(ji) * a_i_1d(ji) * r1_rdtice 
    172172            ! updates 
    173173            ht_s_1d(ji)   = 0._wp 
     
    233233         hfx_snw_1d(ji) = hfx_snw_1d(ji) - zdeltah(ji,1) * a_i_1d(ji) * zqprec(ji) * r1_rdtice 
    234234         ! snow melting only = water into the ocean (then without snow precip), >0 
    235          wfx_snw_1d(ji) = wfx_snw_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,1) * r1_rdtice     
     235         wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,1) * r1_rdtice 
    236236         ! updates available heat + precipitations after melting 
    237237         zq_su     (ji) = MAX( 0._wp , zq_su (ji) + zdeltah(ji,1) * zqprec(ji) )       
     
    255255            hfx_snw_1d(ji)   = hfx_snw_1d(ji) - zdeltah(ji,jk) * a_i_1d(ji) * q_s_1d(ji,jk) * r1_rdtice  
    256256            ! snow melting only = water into the ocean (then without snow precip) 
    257             wfx_snw_1d(ji)   = wfx_snw_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,jk) * r1_rdtice 
     257            wfx_snw_sum_1d(ji)   = wfx_snw_sum_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,jk) * r1_rdtice 
    258258            ! updates available heat + thickness 
    259259            zq_su (ji)  = MAX( 0._wp , zq_su (ji) + zdeltah(ji,jk) * q_s_1d(ji,jk) ) 
     
    607607         hfx_snw_1d(ji)  = hfx_snw_1d(ji) - zdeltah(ji,1) * a_i_1d(ji) * q_s_1d(ji,1) * r1_rdtice ! W.m-2 (>0) 
    608608         ! Contribution to mass flux 
    609          wfx_snw_1d(ji)  =  wfx_snw_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,1) * r1_rdtice 
     609         wfx_snw_sum_1d(ji)  =  wfx_snw_sum_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,1) * r1_rdtice 
    610610         !     
    611611         ii = MOD( npb(ji) - 1, jpi ) + 1 ; ij = ( npb(ji) - 1 ) / jpi + 1 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/LIM_SRC_3/thd_ice.F90

    r6515 r8179  
    5454 
    5555   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   wfx_snw_1d  
     56   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   wfx_snw_sum_1d 
    5657   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   wfx_sub_1d 
    5758 
     
    142143      ii = ii + 1 
    143144      ALLOCATE( sprecip_1d (jpij) , frld_1d    (jpij) , at_i_1d    (jpij) ,                     & 
    144          &      fhtur_1d   (jpij) , wfx_snw_1d (jpij) , wfx_spr_1d (jpij) ,                     & 
     145         &      fhtur_1d   (jpij) , wfx_snw_1d (jpij) , wfx_spr_1d (jpij) , wfx_snw_sum_1d(jpij) , & 
    145146         &      fhld_1d    (jpij) , wfx_sub_1d (jpij) , wfx_bog_1d (jpij) , wfx_bom_1d(jpij) ,  & 
    146147         &      wfx_sum_1d(jpij)  , wfx_sni_1d (jpij) , wfx_opw_1d (jpij) , wfx_res_1d(jpij) ,  & 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/OPA_SRC/SBC/albedo.F90

    r8142 r8179  
    167167         ENDIF  
    168168 
    169          ! Note that this way of coding things means that the thickness 
    170          ! dependence of bare ice albedo is also altering the ponded ice albedo 
    171          ! I'm not sure that this is valid, but at least, this maintains 
    172          ! consistency with previous formulation (see below) 
    173       
    174169         DO jl = 1, ijpl 
    175170            DO jj = 1, jpj 
  • branches/2016/dev_r6859_LIM3_meltponds/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r8106 r8179  
    666666 
    667667      ! MV MP 2016 
    668       wfx_pnd(:,:) = 0._wp 
     668      wfx_pnd(:,:) = 0._wp   ;   wfx_snw_sum(:,:) = 0._wp 
    669669      ! END MV MP 2016 
    670670       
Note: See TracChangeset for help on using the changeset viewer.