Changeset 9912
- Timestamp:
- 2018-07-10T14:07:44+02:00 (5 years ago)
- Location:
- NEMO/trunk/src/ICE
- Files:
-
- 7 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/trunk/src/ICE/ice.F90
r9910 r9912 256 256 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: hfx_err_dif !: heat flux remaining due to change in non-solar flux [W.m-2] 257 257 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: hfx_err_rem !: heat flux error after heat remapping [W.m-2] 258 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: hfx_in!: heat flux available for thermo transformations [W.m-2]259 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: hfx_out!: heat flux remaining at the end of thermo transformations [W.m-2]258 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qt_atm_oi !: heat flux available for thermo transformations [W.m-2] 259 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qt_oce_ai !: heat flux remaining at the end of thermo transformations [W.m-2] 260 260 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: wfx_err_sub !: mass flux error after sublimation [kg.m-2.s-1] 261 261 … … 387 387 388 388 ii = ii + 1 389 ALLOCATE( t_bo (jpi,jpj) , wfx_snw_sni(jpi,jpj) , &390 & wfx_snw (jpi,jpj) , wfx_snw_dyn(jpi,jpj) , wfx_snw_sum(jpi,jpj) , wfx_snw_sub(jpi,jpj) , &391 & wfx_ice (jpi,jpj) , wfx_sub (jpi,jpj) , wfx_ice_sub(jpi,jpj) , wfx_lam (jpi,jpj) , &392 & wfx_pnd (jpi,jpj) , &393 & wfx_bog (jpi,jpj) , wfx_dyn(jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,&394 & wfx_res (jpi,jpj) , wfx_sni(jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,&395 & afx_tot (jpi,jpj) , rn_amax_2d(jpi,jpj), &396 & fhtur (jpi,jpj) , qlead (jpi,jpj) ,&397 & sfx_res (jpi,jpj) , sfx_bri(jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) , &398 & sfx_bog (jpi,jpj) , sfx_bom(jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) , &399 & hfx_res (jpi,jpj) , hfx_snw(jpi,jpj) , hfx_sub(jpi,jpj) , &400 & hfx_in (jpi,jpj) , hfx_out(jpi,jpj) , fhld (jpi,jpj) , &401 & hfx_sum (jpi,jpj) , hfx_bom(jpi,jpj) , hfx_bog(jpi,jpj) , hfx_dif(jpi,jpj) , &402 & hfx_opw (jpi,jpj) , hfx_thd(jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj) , &403 & hfx_err_dif(jpi,jpj) , hfx_err_rem(jpi,jpj) , wfx_err_sub(jpi,jpj) , STAT=ierr(ii) )389 ALLOCATE( t_bo (jpi,jpj) , wfx_snw_sni(jpi,jpj) , & 390 & wfx_snw (jpi,jpj) , wfx_snw_dyn(jpi,jpj) , wfx_snw_sum(jpi,jpj) , wfx_snw_sub(jpi,jpj) , & 391 & wfx_ice (jpi,jpj) , wfx_sub (jpi,jpj) , wfx_ice_sub(jpi,jpj) , wfx_lam (jpi,jpj) , & 392 & wfx_pnd (jpi,jpj) , & 393 & wfx_bog (jpi,jpj) , wfx_dyn (jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) , & 394 & wfx_res (jpi,jpj) , wfx_sni (jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) , & 395 & afx_tot (jpi,jpj) , rn_amax_2d(jpi,jpj), & 396 & fhtur (jpi,jpj) , qlead (jpi,jpj) , & 397 & sfx_res (jpi,jpj) , sfx_bri (jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) , & 398 & sfx_bog (jpi,jpj) , sfx_bom (jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) , & 399 & hfx_res (jpi,jpj) , hfx_snw (jpi,jpj) , hfx_sub(jpi,jpj) , & 400 & qt_atm_oi(jpi,jpj) , qt_oce_ai (jpi,jpj) , fhld (jpi,jpj) , & 401 & hfx_sum (jpi,jpj) , hfx_bom (jpi,jpj) , hfx_bog(jpi,jpj) , hfx_dif(jpi,jpj) , & 402 & hfx_opw (jpi,jpj) , hfx_thd (jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj) , & 403 & hfx_err_dif(jpi,jpj) , hfx_err_rem(jpi,jpj) , wfx_err_sub(jpi,jpj) , STAT=ierr(ii) ) 404 404 405 405 ! * Ice global state variables -
NEMO/trunk/src/ICE/ice1d.F90
r9910 r9912 53 53 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: hfx_err_rem_1d 54 54 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: hfx_err_dif_1d 55 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: hfx_out_1d55 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: qt_oce_ai_1d 56 56 57 57 ! heat flux associated with ice-atmosphere mass exchange … … 190 190 & hfx_thd_1d(jpij) , hfx_spr_1d (jpij) , & 191 191 & hfx_snw_1d(jpij) , hfx_sub_1d (jpij) , & 192 & hfx_res_1d(jpij) , hfx_err_rem_1d(jpij) , hfx_err_dif_1d(jpij) , hfx_out_1d(jpij), STAT=ierr(ii) )192 & hfx_res_1d(jpij) , hfx_err_rem_1d(jpij) , hfx_err_dif_1d(jpij) , qt_oce_ai_1d(jpij), STAT=ierr(ii) ) 193 193 ! 194 194 ii = ii + 1 -
NEMO/trunk/src/ICE/icectl.F90
r9604 r9912 189 189 190 190 ! heat flux 191 zhfx = glob_sum( ( hfx_in - hfx_out- diag_heat - diag_trp_ei - diag_trp_es &191 zhfx = glob_sum( ( qt_atm_oi - qt_oce_ai - diag_heat - diag_trp_ei - diag_trp_es & 192 192 ! & - SUM( qevap_ice * a_i_b, dim=3 ) & !!clem: I think this line must be commented (but need check) 193 193 & ) * e1e2t ) * zconv … … 572 572 WRITE(numout,*) 573 573 WRITE(numout,*) ' hfx_mass : ', hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_snw(ji,jj) + hfx_res(ji,jj) 574 WRITE(numout,*) ' hfx_in : ', hfx_in(ji,jj)575 WRITE(numout,*) ' hfx_out : ', hfx_out(ji,jj)574 WRITE(numout,*) ' qt_atm_oi : ', qt_atm_oi(ji,jj) 575 WRITE(numout,*) ' qt_oce_ai : ', qt_oce_ai(ji,jj) 576 576 WRITE(numout,*) ' dhc : ', diag_heat(ji,jj) 577 577 WRITE(numout,*) -
NEMO/trunk/src/ICE/icedia.F90
r9604 r9912 95 95 ! 2 - Trends due to forcing ! 96 96 ! ---------------------------! 97 z_frc_volbot = r1_rau0 * glob_sum( - ( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater flux ice/snow-ocean98 z_frc_voltop = r1_rau0 * glob_sum( - ( wfx_sub(:,:) + wfx_spr(:,:) ) * e1e2t(:,:) ) * 1.e-9! freshwater flux ice/snow-atm99 z_frc_sal = r1_rau0 * glob_sum( - sfx(:,:) * e1e2t(:,:) ) * 1.e-9! salt fluxes ice/snow-ocean100 z_frc_tembot = glob_sum( hfx_out(:,:) * e1e2t(:,:) ) * 1.e-20! heat on top of ocean (and below ice)101 z_frc_temtop = glob_sum( hfx_in (:,:) * e1e2t(:,:) ) * 1.e-20! heat on top of ice-coean97 z_frc_volbot = r1_rau0 * glob_sum( - ( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater flux ice/snow-ocean 98 z_frc_voltop = r1_rau0 * glob_sum( - ( wfx_sub(:,:) + wfx_spr(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater flux ice/snow-atm 99 z_frc_sal = r1_rau0 * glob_sum( - sfx(:,:) * e1e2t(:,:) ) * 1.e-9 ! salt fluxes ice/snow-ocean 100 z_frc_tembot = glob_sum( qt_oce_ai(:,:) * e1e2t(:,:) ) * 1.e-20 ! heat on top of ocean (and below ice) 101 z_frc_temtop = glob_sum( qt_atm_oi(:,:) * e1e2t(:,:) ) * 1.e-20 ! heat on top of ice-coean 102 102 ! 103 103 frc_voltop = frc_voltop + z_frc_voltop * rdt_ice ! km3 … … 110 110 ! 3 - Content variations ! 111 111 ! ----------------------- ! 112 zdiff_vol = r1_rau0 * glob_sum( ( rhoic*vt_i(:,:) + rhosn*vt_s(:,:) - vol_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater trend (km3)113 zdiff_sal = r1_rau0 * glob_sum( ( rhoic* SUM( sv_i(:,:,:), dim=3 ) - sal_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9! salt content trend (km3*pss)114 zdiff_tem = glob_sum( ( et_i(:,:) + et_s(:,:) - tem_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-20 ! heat content trend (1.e20 J)112 zdiff_vol = r1_rau0 * glob_sum( ( rhoic*vt_i(:,:) + rhosn*vt_s(:,:) - vol_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater trend (km3) 113 zdiff_sal = r1_rau0 * glob_sum( ( rhoic* SUM( sv_i(:,:,:), dim=3 ) - sal_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! salt content trend (km3*pss) 114 zdiff_tem = glob_sum( ( et_i(:,:) + et_s(:,:) - tem_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-20 ! heat content trend (1.e20 J) 115 115 ! + SUM( qevap_ice * a_i_b, dim=3 ) !! clem: I think this term should not be there (but needs a check) 116 116 -
NEMO/trunk/src/ICE/icethd.F90
r9910 r9912 177 177 ! Net heat flux on top of the ice-ocean [W.m-2] 178 178 ! --------------------------------------------- 179 hfx_in(ji,jj) = qns_tot(ji,jj) + qsr_tot(ji,jj)179 qt_atm_oi(ji,jj) = qns_tot(ji,jj) + qsr_tot(ji,jj) 180 180 END DO 181 181 END DO … … 185 185 ! In case we bypass growing/melting from top and bottom: we suppose ice is impermeable => ocean is isolated from atmosphere 186 186 IF( .NOT. ln_icedH ) THEN 187 hfx_in(:,:) = ( 1._wp - at_i_b(:,:) ) * ( qns_oce(:,:) + qsr_oce(:,:) ) + qemp_oce(:,:)188 fhtur (:,:) = 0._wp189 fhld (:,:) = 0._wp187 qt_atm_oi(:,:) = ( 1._wp - at_i_b(:,:) ) * ( qns_oce(:,:) + qsr_oce(:,:) ) + qemp_oce(:,:) 188 fhtur (:,:) = 0._wp 189 fhld (:,:) = 0._wp 190 190 ENDIF 191 191 … … 196 196 ! Second step in icethd_dh : heat remaining if total melt (zq_rema) 197 197 ! Third step in iceupdate.F90 : heat from ice-ocean mass exchange (zf_mass) + solar 198 hfx_out(:,:) = ( 1._wp - at_i_b(:,:) ) * qns_oce(:,:) + qemp_oce(:,:) & ! Non solar heat flux received by the ocean199 & - qlead(:,:) * r1_rdtice & ! heat flux taken from the ocean where there is open water ice formation200 & - at_i (:,:) * fhtur(:,:) & ! heat flux taken by turbulence201 & - at_i (:,:) * fhld(:,:) ! heat flux taken during bottom growth/melt202 ! (fhld should be 0 while bott growth)198 qt_oce_ai(:,:) = ( 1._wp - at_i_b(:,:) ) * qns_oce(:,:) + qemp_oce(:,:) & ! Non solar heat flux received by the ocean 199 & - qlead(:,:) * r1_rdtice & ! heat flux taken from the ocean where there is open water ice formation 200 & - at_i (:,:) * fhtur(:,:) & ! heat flux taken by turbulence 201 & - at_i (:,:) * fhld(:,:) ! heat flux taken during bottom growth/melt 202 ! ! (fhld should be 0 while bott growth) 203 203 !-------------------------------------------------------------------------------------------! 204 204 ! Thermodynamic computation (only on grid points covered by ice) => loop over ice categories … … 429 429 CALL tab_2d_1d( npti, nptidx(1:npti), hfx_err_dif_1d(1:npti), hfx_err_dif ) 430 430 CALL tab_2d_1d( npti, nptidx(1:npti), hfx_err_rem_1d(1:npti), hfx_err_rem ) 431 CALL tab_2d_1d( npti, nptidx(1:npti), hfx_out_1d (1:npti), hfx_out)431 CALL tab_2d_1d( npti, nptidx(1:npti), qt_oce_ai_1d (1:npti), qt_oce_ai ) 432 432 ! 433 433 ! SIMIP diagnostics … … 507 507 CALL tab_1d_2d( npti, nptidx(1:npti), sfx_lam_1d (1:npti), sfx_lam ) 508 508 ! 509 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_thd_1d (1:npti), hfx_thd)510 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_spr_1d (1:npti), hfx_spr)511 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_sum_1d (1:npti), hfx_sum)512 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_bom_1d (1:npti), hfx_bom)513 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_bog_1d (1:npti), hfx_bog)514 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_dif_1d (1:npti), hfx_dif)515 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_opw_1d (1:npti), hfx_opw)516 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_snw_1d (1:npti), hfx_snw)517 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_sub_1d (1:npti), hfx_sub)518 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_res_1d (1:npti), hfx_res)509 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_thd_1d (1:npti), hfx_thd ) 510 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_spr_1d (1:npti), hfx_spr ) 511 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_sum_1d (1:npti), hfx_sum ) 512 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_bom_1d (1:npti), hfx_bom ) 513 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_bog_1d (1:npti), hfx_bog ) 514 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_dif_1d (1:npti), hfx_dif ) 515 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_opw_1d (1:npti), hfx_opw ) 516 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_snw_1d (1:npti), hfx_snw ) 517 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_sub_1d (1:npti), hfx_sub ) 518 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_res_1d (1:npti), hfx_res ) 519 519 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_err_dif_1d(1:npti), hfx_err_dif ) 520 520 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_err_rem_1d(1:npti), hfx_err_rem ) 521 CALL tab_1d_2d( npti, nptidx(1:npti), hfx_out_1d (1:npti), hfx_out)521 CALL tab_1d_2d( npti, nptidx(1:npti), qt_oce_ai_1d (1:npti), qt_oce_ai ) 522 522 ! 523 523 CALL tab_1d_2d( npti, nptidx(1:npti), qns_ice_1d (1:npti), qns_ice (:,:,kl) ) -
NEMO/trunk/src/ICE/icethd_dh.F90
r9910 r9912 570 570 ! 571 571 ! Remaining heat flux (W.m-2) is sent to the ocean heat budget 572 hfx_out_1d(ji) = hfx_out_1d(ji) + ( zq_rema(ji) * a_i_1d(ji) ) * r1_rdtice572 qt_oce_ai_1d(ji) = qt_oce_ai_1d(ji) + ( zq_rema(ji) * a_i_1d(ji) ) * r1_rdtice 573 573 574 574 IF( ln_icectl .AND. zq_rema(ji) < 0. .AND. lwp ) WRITE(numout,*) 'ALERTE zq_rema <0 = ', zq_rema(ji) -
NEMO/trunk/src/ICE/iceupdate.F90
r9910 r9912 107 107 ! --- case we bypass ice thermodynamics --- ! 108 108 IF( .NOT. ln_icethd ) THEN ! we suppose ice is impermeable => ocean is isolated from atmosphere 109 hfx_in(:,:) = ( 1._wp - at_i_b(:,:) ) * ( qns_oce(:,:) + qsr_oce(:,:) ) + qemp_oce(:,:)110 hfx_out(:,:) = ( 1._wp - at_i_b(:,:) ) * qns_oce(:,:) + qemp_oce(:,:)109 qt_atm_oi (:,:) = ( 1._wp - at_i_b(:,:) ) * ( qns_oce(:,:) + qsr_oce(:,:) ) + qemp_oce(:,:) 110 qt_oce_ai (:,:) = ( 1._wp - at_i_b(:,:) ) * qns_oce(:,:) + qemp_oce(:,:) 111 111 qtr_ice_bot(:,:,:) = 0._wp 112 112 emp_ice (:,:) = 0._wp … … 122 122 zqsr = qsr_tot(ji,jj) - SUM( a_i_b(ji,jj,:) * ( qsr_ice(ji,jj,:) - qtr_ice_bot(ji,jj,:) ) ) 123 123 124 ! Total heat flux reaching the ocean = hfx_out(W.m-2)124 ! Total heat flux reaching the ocean = qt_oce_ai (W.m-2) 125 125 !--------------------------------------------------- 126 zqmass = hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_res(ji,jj) ! heat flux from snow is 0 (T=0 degC)127 hfx_out(ji,jj) = hfx_out(ji,jj) + zqmass + zqsr126 zqmass = hfx_thd(ji,jj) + hfx_dyn(ji,jj) + hfx_res(ji,jj) ! heat flux from snow is 0 (T=0 degC) 127 qt_oce_ai(ji,jj) = qt_oce_ai(ji,jj) + zqmass + zqsr 128 128 129 129 ! Add the residual from heat diffusion equation and sublimation (W.m-2) 130 130 !---------------------------------------------------------------------- 131 hfx_out(ji,jj) = hfx_out(ji,jj) + hfx_err_dif(ji,jj) + &132 & ( hfx_sub(ji,jj) - SUM( qevap_ice(ji,jj,:) * a_i_b(ji,jj,:) ) )131 qt_oce_ai(ji,jj) = qt_oce_ai(ji,jj) + hfx_err_dif(ji,jj) + & 132 & ( hfx_sub(ji,jj) - SUM( qevap_ice(ji,jj,:) * a_i_b(ji,jj,:) ) ) 133 133 134 134 ! New qsr and qns used to compute the oceanic heat flux at the next time step 135 135 !---------------------------------------------------------------------------- 136 136 qsr(ji,jj) = zqsr 137 qns(ji,jj) = hfx_out(ji,jj) - zqsr137 qns(ji,jj) = qt_oce_ai(ji,jj) - zqsr 138 138 139 139 ! Mass flux at the atm. surface … … 254 254 IF( iom_use('qt_oce' ) ) CALL iom_put( "qt_oce" , ( qsr_oce + qns_oce ) * ( 1._wp - at_i_b ) + qemp_oce ) 255 255 IF( iom_use('qt_ice' ) ) CALL iom_put( "qt_ice" , SUM( ( qns_ice + qsr_ice ) * a_i_b, dim=3 ) + qemp_ice ) 256 IF( iom_use('qt_oce_ai' ) ) CALL iom_put( "qt_oce_ai" , hfx_out * tmask(:,:,1)) ! total heat flux at the ocean surface: interface oce-(ice+atm)257 IF( iom_use('qt_atm_oi' ) ) CALL iom_put( "qt_atm_oi" , hfx_in * tmask(:,:,1)) ! total heat flux at the oce-ice surface: interface atm-(ice+oce)256 IF( iom_use('qt_oce_ai' ) ) CALL iom_put( "qt_oce_ai" , qt_oce_ai * tmask(:,:,1) ) ! total heat flux at the ocean surface: interface oce-(ice+atm) 257 IF( iom_use('qt_atm_oi' ) ) CALL iom_put( "qt_atm_oi" , qt_atm_oi * tmask(:,:,1) ) ! total heat flux at the oce-ice surface: interface atm-(ice+oce) 258 258 IF( iom_use('qemp_oce' ) ) CALL iom_put( "qemp_oce" , qemp_oce ) ! Downward Heat Flux from E-P over ocean 259 259 IF( iom_use('qemp_ice' ) ) CALL iom_put( "qemp_ice" , qemp_ice ) ! Downward Heat Flux from E-P over ice … … 267 267 IF( iom_use('hfxdif' ) ) CALL iom_put ("hfxdif" , hfx_dif ) ! heat flux used for ice temperature change 268 268 IF( iom_use('hfxsnw' ) ) CALL iom_put ("hfxsnw" , hfx_snw ) ! heat flux used for snow melt 269 IF( iom_use('hfxerr' ) ) CALL iom_put ("hfxerr" , hfx_err_dif ) ! heat flux error after heat diffusion (included in hfx_out)269 IF( iom_use('hfxerr' ) ) CALL iom_put ("hfxerr" , hfx_err_dif ) ! heat flux error after heat diffusion (included in qt_oce_ai) 270 270 271 271 ! heat fluxes associated with mass exchange (freeze/melt/precip...)
Note: See TracChangeset
for help on using the changeset viewer.