Skip to content

Commit

Permalink
Merge pull request #7 from eclare108213/snicar
Browse files Browse the repository at this point in the history
Snicar-ad port to Icepack from MPAS-SI
  • Loading branch information
eclare108213 authored Sep 30, 2022
2 parents 4ff4e28 + 9ae618c commit 8aef3f7
Show file tree
Hide file tree
Showing 26 changed files with 12,264 additions and 1,573 deletions.
8 changes: 6 additions & 2 deletions columnphysics/icepack_intfc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -45,13 +45,15 @@ module icepack_intfc
use icepack_tracers, only: icepack_max_iso => max_iso
use icepack_tracers, only: icepack_nmodal1 => nmodal1
use icepack_tracers, only: icepack_nmodal2 => nmodal2
use icepack_parameters, only: icepack_nspint => nspint

use icepack_shortwave_data, only: icepack_nspint_3bd => nspint_3bd
use icepack_shortwave_data, only: icepack_nspint_5bd => nspint_5bd

use icepack_parameters, only: icepack_init_parameters
use icepack_parameters, only: icepack_query_parameters
use icepack_parameters, only: icepack_write_parameters
use icepack_parameters, only: icepack_recompute_constants
use icepack_parameters, only: nspint, secday, spval_const
use icepack_parameters, only: secday, spval_const
use icepack_parameters, only: c0, c1, c1p5, c2, c3, c4, c5, c6, c8
use icepack_parameters, only: c10, c15, c16, c20, c25, c100, c1000
use icepack_parameters, only: p001, p01, p1, p2, p4, p5, p6, p05
Expand Down Expand Up @@ -85,6 +87,7 @@ module icepack_intfc
use icepack_snow, only: icepack_init_snow
use icepack_snow, only: icepack_step_snow

use icepack_shortwave, only: icepack_init_radiation
use icepack_shortwave, only: icepack_prep_radiation
use icepack_shortwave, only: icepack_step_radiation

Expand Down Expand Up @@ -121,6 +124,7 @@ module icepack_intfc
use icepack_warnings, only: icepack_warnings_print
use icepack_warnings, only: icepack_warnings_flush
use icepack_warnings, only: icepack_warnings_aborted
use icepack_warnings, only: icepack_warnings_getall

!autodocument_end icepack_intfc.F90

Expand Down
6 changes: 4 additions & 2 deletions columnphysics/icepack_mechred.F90
Original file line number Diff line number Diff line change
Expand Up @@ -433,8 +433,10 @@ subroutine ridge_ice (dt, ndtd, &
!-----------------------------------------------------------------

if (iterate_ridging) then
write(warnstr,*) subname, 'Repeat ridging, niter =', niter
call icepack_warnings_add(warnstr)
if (niter > 1) then
write(warnstr,*) subname, 'Repeat ridging, niter =', niter
call icepack_warnings_add(warnstr)
endif
else
exit rdg_iteration
endif
Expand Down
61 changes: 36 additions & 25 deletions columnphysics/icepack_parameters.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,9 +29,6 @@ module icepack_parameters
! parameter constants
!-----------------------------------------------------------------

integer (kind=int_kind), parameter, public :: &
nspint = 3 ! number of solar spectral intervals

real (kind=dbl_kind), parameter, public :: &
c0 = 0.0_dbl_kind, &
c1 = 1.0_dbl_kind, &
Expand Down Expand Up @@ -217,10 +214,22 @@ module icepack_parameters
awtidf = 0.36218_dbl_kind ! near IR, diffuse

character (len=char_len), public :: &
shortwave = 'dEdd', & ! shortwave method, 'ccsm3' or 'dEdd'
shortwave = 'dEdd', & ! shortwave method, 'ccsm3' or 'dEdd' or 'dEdd_snicar_ad'
albedo_type = 'ccsm3' ! albedo parameterization, 'ccsm3' or 'constant'
! shortwave='dEdd' overrides this parameter

! Parameters for shortwave redistribution
logical (kind=log_kind), public :: &
sw_redist = .false.

real (kind=dbl_kind), public :: &
sw_frac = 0.9_dbl_kind , & ! Fraction of internal shortwave moved to surface
sw_dtemp = 0.02_dbl_kind ! temperature difference from melting

! Parameters for dEdd_snicar_ad
character (len=char_len), public :: &
snw_ssp_table = 'test' ! lookup table: 'snicar' or 'test'

!-----------------------------------------------------------------------
! Parameters for dynamics, including ridging and strength
!-----------------------------------------------------------------------
Expand Down Expand Up @@ -419,18 +428,6 @@ module icepack_parameters
t_sk_conv = 3.0_dbl_kind , & ! Stefels conversion time (d)
t_sk_ox = 10.0_dbl_kind ! DMS oxidation time (d)


!-----------------------------------------------------------------------
! Parameters for shortwave redistribution
!-----------------------------------------------------------------------

logical (kind=log_kind), public :: &
sw_redist = .false.

real (kind=dbl_kind), public :: &
sw_frac = 0.9_dbl_kind , & ! Fraction of internal shortwave moved to surface
sw_dtemp = 0.02_dbl_kind ! temperature difference from melting

!=======================================================================

contains
Expand Down Expand Up @@ -491,7 +488,7 @@ subroutine icepack_init_parameters( &
snwlvlfac_in, isnw_T_in, isnw_Tgrd_in, isnw_rhos_in, &
snowage_rhos_in, snowage_Tgrd_in, snowage_T_in, &
snowage_tau_in, snowage_kappa_in, snowage_drdt0_in, &
snw_aging_table_in)
snw_aging_table_in, snw_ssp_table_in )

!-----------------------------------------------------------------
! control settings
Expand Down Expand Up @@ -613,7 +610,7 @@ subroutine icepack_init_parameters( &
awtidf_in ! near IR, diffuse

character (len=*), intent(in), optional :: &
shortwave_in, & ! shortwave method, 'ccsm3' or 'dEdd'
shortwave_in, & ! shortwave method, 'ccsm3' or 'dEdd' or 'dEdd_snicar_ad'
albedo_type_in ! albedo parameterization, 'ccsm3' or 'constant'
! shortwave='dEdd' overrides this parameter

Expand Down Expand Up @@ -844,8 +841,16 @@ subroutine icepack_init_parameters( &
snowage_kappa_in, &!
snowage_drdt0_in ! (10^-6 m/hr)

character (len=char_len), intent(in), optional :: &
snw_ssp_table_in ! lookup table: 'snicar' or 'test'

!autodocument_end

! local data

integer (kind=int_kind) :: &
dim1, dim2, dim3 ! array dimension sizes

character(len=*),parameter :: subname='(icepack_init_parameters)'

if (present(argcheck_in) ) argcheck = argcheck_in
Expand Down Expand Up @@ -980,6 +985,10 @@ subroutine icepack_init_parameters( &
if (present(windmin_in) ) windmin = windmin_in
if (present(drhosdwind_in) ) drhosdwind = drhosdwind_in
if (present(snwlvlfac_in) ) snwlvlfac = snwlvlfac_in

!-------------------
! SNOW table
!-------------------
if (present(isnw_T_in) ) isnw_T = isnw_T_in
if (present(isnw_Tgrd_in) ) isnw_Tgrd = isnw_Tgrd_in
if (present(isnw_rhos_in) ) isnw_rhos = isnw_rhos_in
Expand All @@ -1001,7 +1010,6 @@ subroutine icepack_init_parameters( &
endif
endif

! check array sizes and re/allocate if necessary
if (present(snowage_Tgrd_in) ) then
if (size(snowage_Tgrd_in) /= isnw_Tgrd) then
call icepack_warnings_add(subname//' incorrect size of snowage_Tgrd_in')
Expand All @@ -1018,7 +1026,6 @@ subroutine icepack_init_parameters( &
endif
endif

! check array sizes and re/allocate if necessary
if (present(snowage_T_in) ) then
if (size(snowage_T_in) /= isnw_T) then
call icepack_warnings_add(subname//' incorrect size of snowage_T_in')
Expand All @@ -1035,7 +1042,6 @@ subroutine icepack_init_parameters( &
endif
endif

! check array sizes and re/allocate if necessary
if (present(snowage_tau_in) ) then
if (size(snowage_tau_in) /= isnw_T*isnw_Tgrd*isnw_rhos) then
call icepack_warnings_add(subname//' incorrect size of snowage_tau_in')
Expand All @@ -1052,7 +1058,6 @@ subroutine icepack_init_parameters( &
endif
endif

! check array sizes and re/allocate if necessary
if (present(snowage_kappa_in) ) then
if (size(snowage_kappa_in) /= isnw_T*isnw_Tgrd*isnw_rhos) then
call icepack_warnings_add(subname//' incorrect size of snowage_kappa_in')
Expand All @@ -1069,7 +1074,6 @@ subroutine icepack_init_parameters( &
endif
endif

! check array sizes and re/allocate if necessary
if (present(snowage_drdt0_in) ) then
if (size(snowage_drdt0_in) /= isnw_T*isnw_Tgrd*isnw_rhos) then
call icepack_warnings_add(subname//' incorrect size of snowage_drdt0_in')
Expand All @@ -1086,6 +1090,7 @@ subroutine icepack_init_parameters( &
endif
endif

if (present(snw_ssp_table_in) ) snw_ssp_table = snw_ssp_table_in
if (present(bgc_flux_type_in) ) bgc_flux_type = bgc_flux_type_in
if (present(z_tracers_in) ) z_tracers = z_tracers_in
if (present(scale_bgc_in) ) scale_bgc = scale_bgc_in
Expand Down Expand Up @@ -1198,7 +1203,7 @@ subroutine icepack_query_parameters( &
snwlvlfac_out, isnw_T_out, isnw_Tgrd_out, isnw_rhos_out, &
snowage_rhos_out, snowage_Tgrd_out, snowage_T_out, &
snowage_tau_out, snowage_kappa_out, snowage_drdt0_out, &
snw_aging_table_out)
snw_aging_table_out, snw_ssp_table_out )

!-----------------------------------------------------------------
! control settings
Expand Down Expand Up @@ -1329,7 +1334,7 @@ subroutine icepack_query_parameters( &
awtidf_out ! near IR, diffuse

character (len=*), intent(out), optional :: &
shortwave_out, & ! shortwave method, 'ccsm3' or 'dEdd'
shortwave_out, & ! shortwave method, 'ccsm3' or 'dEdd' or 'dEdd_snicar_ad'
albedo_type_out ! albedo parameterization, 'ccsm3' or 'constant'
! shortwave='dEdd' overrides this parameter

Expand Down Expand Up @@ -1559,6 +1564,10 @@ subroutine icepack_query_parameters( &
snowage_tau_out, & ! (10^-6 m)
snowage_kappa_out, &!
snowage_drdt0_out ! (10^-6 m/hr)

character (len=char_len), intent(out), optional :: &
snw_ssp_table_out ! lookup table: 'snicar' or 'test'

!autodocument_end

character(len=*),parameter :: subname='(icepack_query_parameters)'
Expand Down Expand Up @@ -1741,6 +1750,7 @@ subroutine icepack_query_parameters( &
if (present(snowage_tau_out) ) snowage_tau_out = snowage_tau
if (present(snowage_kappa_out) ) snowage_kappa_out= snowage_kappa
if (present(snowage_drdt0_out) ) snowage_drdt0_out= snowage_drdt0
if (present(snw_ssp_table_out) ) snw_ssp_table_out= snw_ssp_table
if (present(bgc_flux_type_out) ) bgc_flux_type_out= bgc_flux_type
if (present(z_tracers_out) ) z_tracers_out = z_tracers
if (present(scale_bgc_out) ) scale_bgc_out = scale_bgc
Expand Down Expand Up @@ -1950,6 +1960,7 @@ subroutine icepack_write_parameters(iounit)
write(iounit,*) " snowage_tau = ", snowage_tau(1,1,1)
write(iounit,*) " snowage_kappa = ", snowage_kappa(1,1,1)
write(iounit,*) " snowage_drdt0 = ", snowage_drdt0(1,1,1)
write(iounit,*) " snw_ssp_table = ", trim(snw_ssp_table)
write(iounit,*) " bgc_flux_type = ", bgc_flux_type
write(iounit,*) " z_tracers = ", z_tracers
write(iounit,*) " scale_bgc = ", scale_bgc
Expand Down
Loading

0 comments on commit 8aef3f7

Please sign in to comment.