diff --git a/columnphysics/icepack_fsd.F90 b/columnphysics/icepack_fsd.F90 index 2eb436e3..9735090f 100644 --- a/columnphysics/icepack_fsd.F90 +++ b/columnphysics/icepack_fsd.F90 @@ -90,11 +90,23 @@ module icepack_fsd ! ! authors: Lettie Roach, NIWA/VUW and C. M. Bitz, UW - subroutine icepack_init_fsd_bounds( write_diags ) ! flag for writing diagnostics + subroutine icepack_init_fsd_bounds( & + floe_rad_l_out, & ! fsd size lower bound in m (radius) + floe_rad_c_out, & ! fsd size bin centre in m (radius) + floe_binwidth_out, & ! fsd size bin width in m (radius) + c_fsd_range_out, & ! string for history output + write_diags) ! flag for writing diagnostics + real(kind=dbl_kind), dimension(:), intent(out), optional :: & + floe_rad_l_out, & ! fsd size lower bound in m (radius) + floe_rad_c_out, & ! fsd size bin centre in m (radius) + floe_binwidth_out ! fsd size bin width in m (radius) + + character (len=35), dimension(:), intent(out), optional :: & + c_fsd_range_out ! string for history output logical (kind=log_kind), intent(in), optional :: & - write_diags ! write diags flag + write_diags ! write diags flag !autodocument_end @@ -216,20 +228,56 @@ subroutine icepack_init_fsd_bounds( write_diags ) ! flag for writing diagnostic enddo if (present(write_diags)) then - if (write_diags) then - write(warnstr,*) ' ' - call icepack_warnings_add(warnstr) - write(warnstr,*) subname - call icepack_warnings_add(warnstr) - write(warnstr,*) 'floe_rad(n-1) < fsd Cat n < floe_rad(n)' - call icepack_warnings_add(warnstr) - do n = 1, nfsd - write(warnstr,*) floe_rad(n-1),' < fsd Cat ',n, ' < ',floe_rad(n) + if (write_diags) then + write(warnstr,*) ' ' call icepack_warnings_add(warnstr) - enddo - write(warnstr,*) ' ' - call icepack_warnings_add(warnstr) + write(warnstr,*) subname + call icepack_warnings_add(warnstr) + write(warnstr,*) 'floe_rad(n-1) < fsd Cat n < floe_rad(n)' + call icepack_warnings_add(warnstr) + do n = 1, nfsd + write(warnstr,*) floe_rad(n-1),' < fsd Cat ',n, ' < ',floe_rad(n) + call icepack_warnings_add(warnstr) + enddo + write(warnstr,*) ' ' + call icepack_warnings_add(warnstr) + endif + endif + + if (present(floe_rad_l_out)) then + if (size(floe_rad_l_out) /= size(floe_rad_l)) then + call icepack_warnings_add(subname//' floe_rad_l_out incorrect size') + call icepack_warnings_setabort(.true.,__FILE__,__LINE__) + return + endif + floe_rad_l_out(:) = floe_rad_l(:) + endif + + if (present(floe_rad_c_out)) then + if (size(floe_rad_c_out) /= size(floe_rad_c)) then + call icepack_warnings_add(subname//' floe_rad_c_out incorrect size') + call icepack_warnings_setabort(.true.,__FILE__,__LINE__) + return + endif + floe_rad_c_out(:) = floe_rad_c(:) endif + + if (present(floe_binwidth_out)) then + if (size(floe_binwidth_out) /= size(floe_binwidth)) then + call icepack_warnings_add(subname//' floe_binwidth_out incorrect size') + call icepack_warnings_setabort(.true.,__FILE__,__LINE__) + return + endif + floe_binwidth_out(:) = floe_binwidth(:) + endif + + if (present(c_fsd_range_out)) then + if (size(c_fsd_range_out) /= size(c_fsd_range)) then + call icepack_warnings_add(subname//' c_fsd_range_out incorrect size') + call icepack_warnings_setabort(.true.,__FILE__,__LINE__) + return + endif + c_fsd_range_out(:) = c_fsd_range(:) endif end subroutine icepack_init_fsd_bounds @@ -312,7 +360,6 @@ subroutine icepack_cleanup_fsd (afsdn) character(len=*), parameter :: subname='(icepack_cleanup_fsd)' - if (tr_fsd) then do n = 1, ncat diff --git a/columnphysics/icepack_therm_vertical.F90 b/columnphysics/icepack_therm_vertical.F90 index c838a727..b5108986 100644 --- a/columnphysics/icepack_therm_vertical.F90 +++ b/columnphysics/icepack_therm_vertical.F90 @@ -624,40 +624,40 @@ subroutine frzmlt_bottom_lateral (dt, & if (tr_fsd) then ! alter rsiden now since floes are not of size floediam - do n = 1, ncat - - G_radialn(n) = -wlat_loc ! negative + do n = 1, ncat + G_radialn(n) = -wlat_loc ! negative - if (any(afsdn(:,n) < c0)) then - write(warnstr,*) subname, 'lateral_melt B afsd < 0 ',n - call icepack_warnings_add(warnstr) - endif + ! afsdn present check up the calling tree + if (any(afsdn(:,n) < c0)) then + write(warnstr,*) subname, 'lateral_melt B afsd < 0 ',n + call icepack_warnings_add(warnstr) + endif - bin1_arealoss = -afsdn(1,n) / floe_binwidth(1) ! when scaled by *G_radialn(n)*dt*aicen(n) + bin1_arealoss = -afsdn(1,n) / floe_binwidth(1) ! when scaled by *G_radialn(n)*dt*aicen(n) - delta_an(n) = c0 - do k = 1, nfsd - ! this is delta_an(n) when scaled by *G_radialn(n)*dt*aicen(n) - delta_an(n) = delta_an(n) + ((c2/floe_rad_c(k)) * afsdn(k,n)) ! delta_an < 0 - end do + delta_an(n) = c0 + do k = 1, nfsd + ! this is delta_an(n) when scaled by *G_radialn(n)*dt*aicen(n) + delta_an(n) = delta_an(n) + ((c2/floe_rad_c(k)) * afsdn(k,n)) ! delta_an < 0 + end do - ! add negative area loss from fsd - delta_an(n) = (delta_an(n) - bin1_arealoss)*G_radialn(n)*dt + ! add negative area loss from fsd + delta_an(n) = (delta_an(n) - bin1_arealoss)*G_radialn(n)*dt - if (delta_an(n) > c0) then - write(warnstr,*) subname, 'ERROR delta_an > 0 ',delta_an(n) - call icepack_warnings_add(warnstr) - endif + if (delta_an(n) > c0) then + write(warnstr,*) subname, 'ERROR delta_an > 0 ',delta_an(n) + call icepack_warnings_add(warnstr) + endif - ! following original code, not necessary for fsd - if (aicen(n) > c0) rsiden(n) = MIN(-delta_an(n),c1) + ! following original code, not necessary for fsd + if (aicen(n) > c0) rsiden(n) = MIN(-delta_an(n),c1) - if (rsiden(n) < c0) then - write(warnstr,*) subname, 'ERROR rsiden < 0 ',rsiden(n) - call icepack_warnings_add(warnstr) - endif + if (rsiden(n) < c0) then + write(warnstr,*) subname, 'ERROR rsiden < 0 ',rsiden(n) + call icepack_warnings_add(warnstr) + endif + enddo ! ncat - enddo ! ncat endif ! if tr_fsd !----------------------------------------------------------------- @@ -2439,9 +2439,6 @@ subroutine icepack_step_therm1(dt, & real (kind=dbl_kind), dimension(ncat) :: & l_meltsliqn ! mass of snow melt local (kg/m^2) - real (kind=dbl_kind), dimension(:,:), allocatable :: & - l_afsdn ! (kg/m^2) - real (kind=dbl_kind) :: & l_fswthrun_vdr, & ! vis dir SW local n ice to ocean (W/m^2) l_fswthrun_vdf, & ! vis dif SW local n ice to ocean (W/m^2) @@ -2492,7 +2489,12 @@ subroutine icepack_step_therm1(dt, & endif if (tr_fsd) then if (.not.present(afsdn)) then - call icepack_warnings_add(subname//' error in fsd arguments, tr_fsd=T') + call icepack_warnings_add(subname//' error missing afsdn argument, tr_fsd=T') + call icepack_warnings_setabort(.true.,__FILE__,__LINE__) + return + endif + if (size(afsdn,dim=1) /= nfsd .or. size(afsdn,dim=2) /= ncat) then + call icepack_warnings_add(subname//' error size of afsdn argument, tr_fsd=T') call icepack_warnings_setabort(.true.,__FILE__,__LINE__) return endif @@ -2510,14 +2512,6 @@ subroutine icepack_step_therm1(dt, & l_meltsliq = c0 l_meltsliqn = c0 - if (tr_fsd) then - allocate(l_afsdn(nfsd,ncat)) - l_afsdn(:,:) = afsdn(:,:) - else - allocate(l_afsdn(1,1)) - l_afsdn = c0 - endif - ! solid and liquid components of snow mass massicen(:,:) = c0 massliqn(:,:) = c0 @@ -2584,10 +2578,10 @@ subroutine icepack_step_therm1(dt, & ustar_min, & fbot_xfer_type, & strocnxT, strocnyT, & - Tbot, fbot, & - rsiden, Cdn_ocn, & - wlat, aicen, & - afsdn = l_afsdn) + Tbot, fbot, & + rsiden, Cdn_ocn, & + wlat, aicen, & + afsdn) if (icepack_warnings_aborted(subname)) return diff --git a/columnphysics/icepack_wavefracspec.F90 b/columnphysics/icepack_wavefracspec.F90 index 68f78332..34c4e448 100644 --- a/columnphysics/icepack_wavefracspec.F90 +++ b/columnphysics/icepack_wavefracspec.F90 @@ -29,7 +29,6 @@ module icepack_wavefracspec use icepack_kinds - use icepack_parameters, only: p01, p5, c0, c1, c2, c3, c4, c10 use icepack_parameters, only: bignum, puny, gravit, pi use icepack_tracers, only: nt_fsd, ncat, nfsd diff --git a/configuration/driver/icedrv_InitMod.F90 b/configuration/driver/icedrv_InitMod.F90 index f852a53c..ba1b1de6 100644 --- a/configuration/driver/icedrv_InitMod.F90 +++ b/configuration/driver/icedrv_InitMod.F90 @@ -31,7 +31,7 @@ module icedrv_InitMod subroutine icedrv_initialize - use icedrv_arrays_column, only: hin_max, c_hi_range + use icedrv_arrays_column, only: hin_max, c_hi_range, floe_rad_c use icedrv_calendar, only: dt, time, istep, istep1, & init_calendar, calendar use icepack_intfc, only: icepack_init_itd, icepack_init_itd_hist @@ -96,7 +96,7 @@ subroutine icedrv_initialize endif if (tr_fsd) then - call icepack_init_fsd_bounds( write_diags=.true. ) + call icepack_init_fsd_bounds(floe_rad_c_out=floe_rad_c, write_diags=.true. ) call icepack_warnings_flush(nu_diag) if (icepack_warnings_aborted(subname)) then call icedrv_system_abort(file=__FILE__,line=__LINE__) diff --git a/configuration/driver/icedrv_arrays_column.F90 b/configuration/driver/icedrv_arrays_column.F90 index b55f129f..dbe1ab56 100644 --- a/configuration/driver/icedrv_arrays_column.F90 +++ b/configuration/driver/icedrv_arrays_column.F90 @@ -221,29 +221,22 @@ module icedrv_arrays_column ! floe size distribution real(kind=dbl_kind), dimension(nfsd), public :: & - floe_rad_l, & ! fsd size lower bound in m (radius) - floe_rad_c, & ! fsd size bin centre in m (radius) - floe_binwidth ! fsd size bin width in m (radius) + floe_rad_c ! fsd size bin centre in m (radius) real (kind=dbl_kind), dimension (nx), public :: & - wave_sig_ht ! significant height of waves (m) + wave_sig_ht ! significant height of waves (m) real (kind=dbl_kind), dimension (nfreq), public :: & - wavefreq, & ! wave frequencies - dwavefreq ! wave frequency bin widths + wavefreq, & ! wave frequencies + dwavefreq ! wave frequency bin widths real (kind=dbl_kind), dimension (nx,nfreq), public :: & - wave_spectrum ! wave spectrum + wave_spectrum ! wave spectrum real (kind=dbl_kind), dimension (nx,nfsd), public :: & ! change in floe size distribution due to processes d_afsd_newi, d_afsd_latg, d_afsd_latm, d_afsd_wave, d_afsd_weld - character (len=35), public, dimension(nfsd) :: & - c_fsd_range ! fsd floe_rad bounds (m) - - - !======================================================================= end module icedrv_arrays_column diff --git a/configuration/driver/icedrv_init.F90 b/configuration/driver/icedrv_init.F90 index 14a4586c..f342d74f 100644 --- a/configuration/driver/icedrv_init.F90 +++ b/configuration/driver/icedrv_init.F90 @@ -1296,7 +1296,6 @@ subroutine set_state_var (nx, & use icedrv_arrays_column, only: hin_max use icedrv_domain_size, only: nilyr, nslyr, max_ntrcr, ncat, nfsd - use icepack_fsd, only: floe_rad_c, floe_binwidth integer (kind=int_kind), intent(in) :: & nx ! number of grid cells diff --git a/doc/source/user_guide/interfaces.include b/doc/source/user_guide/interfaces.include index ae640d1b..b41f6055 100644 --- a/doc/source/user_guide/interfaces.include +++ b/doc/source/user_guide/interfaces.include @@ -142,22 +142,22 @@ icepack_init_fsd_bounds ! authors: Lettie Roach, NIWA/VUW and C. M. Bitz, UW subroutine icepack_init_fsd_bounds( & - floe_rad_l, & ! fsd size lower bound in m (radius) - floe_rad_c, & ! fsd size bin centre in m (radius) - floe_binwidth, & ! fsd size bin width in m (radius) - c_fsd_range, & ! string for history output - write_diags ) ! flag for writing diagnostics + floe_rad_l_out, & ! fsd size lower bound in m (radius) + floe_rad_c_out, & ! fsd size bin centre in m (radius) + floe_binwidth_out, & ! fsd size bin width in m (radius) + c_fsd_range_out, & ! string for history output + write_diags) ! flag for writing diagnostics - real(kind=dbl_kind), dimension(:), intent(inout) :: & - floe_rad_l, & ! fsd size lower bound in m (radius) - floe_rad_c, & ! fsd size bin centre in m (radius) - floe_binwidth ! fsd size bin width in m (radius) + real(kind=dbl_kind), dimension(:), intent(out), optional :: & + floe_rad_l_out, & ! fsd size lower bound in m (radius) + floe_rad_c_out, & ! fsd size bin centre in m (radius) + floe_binwidth_out ! fsd size bin width in m (radius) - character (len=35), intent(out) :: & - c_fsd_range(nfsd) ! string for history output + character (len=35), dimension(:), intent(out), optional :: & + c_fsd_range_out ! string for history output logical (kind=log_kind), intent(in), optional :: & - write_diags ! write diags flag + write_diags ! write diags flag @@ -172,18 +172,11 @@ icepack_init_fsd ! ! authors: Lettie Roach, NIWA/VUW - subroutine icepack_init_fsd(ice_ic, & - floe_rad_c, & ! fsd size bin centre in m (radius) - floe_binwidth, & ! fsd size bin width in m (radius) - afsd) ! floe size distribution tracer + subroutine icepack_init_fsd(ice_ic, afsd) ! floe size distribution tracer character(len=char_len_long), intent(in) :: & ice_ic ! method of ice cover initialization - real(kind=dbl_kind), dimension(:), intent(inout) :: & - floe_rad_c, & ! fsd size bin centre in m (radius) - floe_binwidth ! fsd size bin width in m (radius) - real (kind=dbl_kind), dimension (:), intent(inout) :: & afsd ! floe size tracer: fraction distribution of floes @@ -2253,8 +2246,8 @@ icepack_step_therm2 nt_strata, & Tf, sss, & salinz, & - rside, meltl, & - fside, wlat, & + rsiden, meltl, & + wlat, & frzmlt, frazil, & frain, fpond, & fresh, fsalt, & @@ -2271,8 +2264,7 @@ icepack_step_therm2 wavefreq, & dwavefreq, & d_afsd_latg, d_afsd_newi, & - d_afsd_latm, d_afsd_weld, & - floe_rad_c, floe_binwidth) + d_afsd_latm, d_afsd_weld) use icepack_parameters, only: icepack_init_parameters @@ -2286,7 +2278,6 @@ icepack_step_therm2 dt , & ! time step Tf , & ! freezing temperature (C) sss , & ! sea surface salinity (ppt) - rside , & ! fraction of ice that melts laterally frzmlt ! freezing/melting potential (W/m^2) integer (kind=int_kind), dimension (:), intent(in) :: & @@ -2301,13 +2292,13 @@ icepack_step_therm2 nt_strata ! indices of underlying tracer layers real (kind=dbl_kind), dimension(:), intent(in) :: & + rsiden , & ! fraction of ice that melts laterally salinz , & ! initial salinity profile ocean_bio ! ocean concentration of biological tracer real (kind=dbl_kind), intent(inout) :: & aice , & ! sea ice concentration aice0 , & ! concentration of open water - fside , & ! lateral heat flux (W/m^2) frain , & ! rainfall rate (kg/m^2 s) fpond , & ! fresh water flux to ponds (kg/m^2/s) fresh , & ! fresh water flux to ocean (kg/m^2/s) @@ -2370,10 +2361,6 @@ icepack_step_therm2 d_afsd_latm, & ! lateral melt d_afsd_weld ! welding - real (kind=dbl_kind), dimension (:), intent(in), optional :: & - floe_rad_c, & ! fsd size bin centre in m (radius) - floe_binwidth ! fsd size bin width in m (radius) - icepack_therm_shared.F90 @@ -2563,8 +2550,8 @@ icepack_step_therm1 strocnxT , strocnyT , & fbot , & Tbot , Tsnice , & - frzmlt , rside , & - fside , wlat , & + frzmlt , rsiden , & + wlat , & fsnow , frain , & fpond , fsloss , & fsurf , fsurfn , & @@ -2611,7 +2598,7 @@ icepack_step_therm1 lmask_n , lmask_s , & mlt_onset , frz_onset , & yday , prescribed_ice, & - zlvs) + zlvs , afsdn) real (kind=dbl_kind), intent(in) :: & dt , & ! time step @@ -2687,8 +2674,6 @@ icepack_step_therm1 strocnyT , & ! ice-ocean stress, y-direction fbot , & ! ice-ocean heat flux at bottom surface (W/m^2) frzmlt , & ! freezing/melting potential (W/m^2) - rside , & ! fraction of ice that melts laterally - fside , & ! lateral heat flux (W/m^2) sst , & ! sea surface temperature (C) Tf , & ! freezing temperature (C) Tbot , & ! ice bottom surface temperature (deg C) @@ -2701,7 +2686,7 @@ icepack_step_therm1 frz_onset ! day of year that freezing begins (congel or frazil) real (kind=dbl_kind), intent(out), optional :: & - wlat ! lateral melt rate (m/s) + wlat ! lateral melt rate (m/s) real (kind=dbl_kind), intent(inout), optional :: & fswthru_vdr , & ! vis dir shortwave penetrating to ocean (W/m^2) @@ -2735,6 +2720,9 @@ icepack_step_therm1 H2_18O_ocn , & ! ocean concentration of H2_18O (kg/kg) zlvs ! atm level height for scalars (if different than zlvl) (m) + real (kind=dbl_kind), dimension(:,:), intent(in), optional :: & + afsdn ! afsd tracer + real (kind=dbl_kind), dimension(:), intent(inout) :: & aicen_init , & ! fractional area of ice vicen_init , & ! volume per unit area of ice (m) @@ -2750,6 +2738,7 @@ icepack_step_therm1 ipnd , & ! melt pond refrozen lid thickness (m) iage , & ! volume-weighted ice age FY , & ! area-weighted first-year ice area + rsiden , & ! fraction of ice that melts laterally fsurfn , & ! net flux to top surface, excluding fcondtop fcondtopn , & ! downward cond flux at top surface (W m-2) fcondbotn , & ! downward cond flux at bottom surface (W m-2) @@ -3380,7 +3369,6 @@ icepack_step_wavefracture subroutine icepack_step_wavefracture(wave_spec_type, & dt, nfreq, & aice, vice, aicen, & - floe_rad_l, floe_rad_c, & wave_spectrum, wavefreq, dwavefreq, & trcrn, d_afsd_wave) @@ -3399,10 +3387,6 @@ icepack_step_wavefracture real (kind=dbl_kind), dimension(ncat), intent(in) :: & aicen ! ice area fraction (categories) - real(kind=dbl_kind), dimension(:), intent(in) :: & - floe_rad_l, & ! fsd size lower bound in m (radius) - floe_rad_c ! fsd size bin centre in m (radius) - real (kind=dbl_kind), dimension (:), intent(in) :: & wavefreq, & ! wave frequencies (s^-1) dwavefreq ! wave frequency bin widths (s^-1)