Skip to content

Commit

Permalink
Merge pull request #237 from jmaerz/feature-hamocc_beyond-CMIP6
Browse files Browse the repository at this point in the history
Merge latest `master` changes into the `feature-hamocc_beyond-CMIP6` and align commit history again getting a new common hook.
  • Loading branch information
jmaerz authored Feb 9, 2023
2 parents aaa5258 + cbc8a33 commit 417bdd8
Show file tree
Hide file tree
Showing 2 changed files with 99 additions and 43 deletions.
40 changes: 32 additions & 8 deletions cime_config/buildnml
Original file line number Diff line number Diff line change
Expand Up @@ -263,9 +263,14 @@ if ($HAMOCC_VSLS == TRUE && $OCN_GRID != tnx1v4) then
endif
# For the following options, there are currently no switches in Case-XML files.
# These options can be activated by expert users via user namelist.
set DO_OALK = .false.
set OALKSCEN = "''"
set OALKFILE = "''"
set BGCOAFX_DO_OALK = .false.
set BGCOAFX_OALKSCEN = "''"
set BGCOAFX_OALKFILE = "''"
set BGCOAFX_ADDALK = 0.135
set BGCOAFX_CDRMIP_LATMAX = 70.0
set BGCOAFX_CDRMIP_LATMIN = -60.0
set BGCOAFX_RAMP_START = 2025
set BGCOAFX_RAMP_END = 2035
set WITH_DMSPH = .false.
set PI_PH_FILE = "''"
set L_3DVARSEDPOR = .false.
Expand Down Expand Up @@ -1536,9 +1541,6 @@ cat >>! $RUNDIR/ocn_in$inststr << EOF
RIVINFILE = $RIVINFILE
DO_NDEP = $DO_NDEP
NDEPFILE = $NDEPFILE
DO_OALK = $DO_OALK
OALKSCEN = $OALKSCEN
OALKFILE = $OALKFILE
DO_SEDSPINUP = $DO_SEDSPINUP
SEDSPIN_YR_S = $SEDSPIN_YR_S
SEDSPIN_YR_E = $SEDSPIN_YR_E
Expand All @@ -1557,6 +1559,28 @@ cat >>! $RUNDIR/ocn_in$inststr << EOF
SEDPORFILE = $SEDPORFILE
/
! NAMELIST FOR ALKALINIZATION SCENARIO
!
! CONTENTS:
!
! ADDALK : Pmol alkalinity/yr added in the scenarios.
! CDRMIP_LATMAX : Max latitude where alkalinity is added according to the
! CDRMIP protocol
! CDRMIP_LATMIN : Min latitude where alkalinity is added according to the
! CDRMIP protocol
! RAMP_START : Start year for ramp up in 'ramp' scenario
! RAMP_END : End year for 'ramp' scenario
&BGCOAFX
DO_OALK = $BGCOAFX_DO_OALK
OALKSCEN = $BGCOAFX_OALKSCEN
OALKFILE = $BGCOAFX_OALKFILE
ADDALK = $BGCOAFX_ADDALK
CDRMIP_LATMAX = $BGCOAFX_CDRMIP_LATMAX
CDRMIP_LATMIN = $BGCOAFX_CDRMIP_LATMIN
RAMP_START = $BGCOAFX_RAMP_START
RAMP_END = $BGCOAFX_RAMP_END
/
! IO-NAMELIST FOR DIAGNOSTIC iHAMOCC OUTPUT
!
! Namelist acronyms:
Expand Down Expand Up @@ -1958,9 +1982,9 @@ cat >> $CASEBUILD/blom.input_data_list << EOF
n_deposition_file = `echo $NDEPFILE | tr -d '"' | tr -d "'"`
EOF
endif
if ($OALKFILE != "''") then
if ($BGCOAFX_OALKFILE != "''") then
cat >> $CASEBUILD/blom.input_data_list << EOF
oafx_file = `echo $OALKFILE | tr -d '"' | tr -d "'"`
oafx_file = `echo $BGCOAFX_OALKFILE | tr -d '"' | tr -d "'"`
EOF
endif
if ($HAMOCC_VSLS == TRUE) then
Expand Down
102 changes: 67 additions & 35 deletions hamocc/mo_read_oafx.F90
Original file line number Diff line number Diff line change
Expand Up @@ -45,11 +45,14 @@ module mo_read_oafx
! issued. The input data must be already pre-interpolated to the ocean grid.
!
! Currently available ocean alkalinisation scenarios:
! -'const_0p14': constant alkalinity flux of 0.14 Pmol yr-1 applied to the
! surface ocean between 60S and 70N (no input file needed)
! -'const_0p56': constant alkalinity flux of 0.56 Pmol yr-1 applied to the
! surface ocean between 60S and 70N (no input file needed)
!
! (no input file needed, flux and latitude range can be defined in the
! namelist, default values are defined):
! -'const': constant alkalinity flux applied to the surface ocean
! between two latitudes.
! -'ramp': ramping-up alkalinity flux from 0 Pmol yr-1 to a maximum
! value between two specified years and kept constant
! onward, applied to the surface ocean between two
! latitudes.
!
! -subroutine ini_read_oafx
! Initialise the module
Expand All @@ -66,24 +69,32 @@ module mo_read_oafx

real,allocatable, save :: oalkflx(:,:)

character(len=128), save :: oalkscen=''
character(len=512), save :: oalkfile=''
character(len=128), save :: oalkscen =''
character(len=512), save :: oalkfile =''
real, parameter :: Pmol2kmol = 1.0e12

! Parameter used in the definition of alkalinization scenarios. The following
! scenarios are defined in this module:
!
! const_0p14 Homogeneous addition of 0.14 Pmol ALK/yr-1 over the ice-free
! surface ocean (assumed to be between 60S and 70N)
! const_0p56 Homogeneous addition of 0.56 Pmol ALK/yr-1 over the ice-free
! surface ocean (assumed to be between 60S and 70N)
! const Constant homogeneous addition of alkalinity between latitude
! cdrmip_latmin and latitude cdrmip_latmax
! ramp Linear increase of homogeneous addition from 0 to addalk
! Pmol ALK/yr-1 from year ramp_start to year ramp_end between
! latitude cdrmip_latmin and latitude cdrmip_latmax
!
real, parameter :: addalk_0p14 = 0.14 ! Pmol alkalinity/yr added in the
real, parameter :: addalk_0p56 = 0.56 ! 'const_0p14' and 'const_0p56'
! scenarios
real, parameter :: cdrmip_latmax = 70.0 ! Min and max latitude where
real, parameter :: cdrmip_latmin = -60.0 ! alkalinity is added according
! to the CDRMIP protocol
real, protected :: addalk = 0.56 ! Pmol alkalinity/yr added in the
! scenarios. Read from namelist file
! to overwrite default value.
real, protected :: cdrmip_latmax = 70.0 ! Min and max latitude where
real, protected :: cdrmip_latmin = -60.0 ! alkalinity is added according
! to the CDRMIP protocol. Read from
! namelist file to overwrite default
! value.
integer, protected :: ramp_start = 2025 ! In 'ramp' scenario, start at
integer, protected :: ramp_end = 2035 ! 0 Pmol/yr in ramp_start, and max
! addalk Pmol/yr in ramp_end.
! Read from namelist file to
! overwrite default value.

logical, save :: lini = .false.

Expand Down Expand Up @@ -115,19 +126,30 @@ subroutine ini_read_oafx(kpie,kpje,pdlxp,pdlyp,pglat,omask)
!
!******************************************************************************
use mod_xc, only: xcsum,xchalt,mnproc,nbdy,ips
use mo_control_bgc, only: io_stdo_bgc,do_oalk
use mo_control_bgc, only: io_stdo_bgc,do_oalk,bgc_namelist,get_bgc_namelist

implicit none
implicit none

integer, intent(in) :: kpie,kpje
real, intent(in) :: pdlxp(kpie,kpje), pdlyp(kpie,kpje)
real, intent(in) :: pglat(1-nbdy:kpie+nbdy,1-nbdy:kpje+nbdy)
real, intent(in) :: pglat(1-nbdy:kpie+nbdy,1-nbdy:kpje+nbdy)
real, intent(in) :: omask(kpie,kpje)

integer :: i,j,errstat
real :: avflx,ztotarea,addalk_tot
integer :: iounit
real :: avflx,ztotarea
real :: ztmp1(1-nbdy:kpie+nbdy,1-nbdy:kpje+nbdy)

namelist /bgcoafx/ do_oalk,oalkscen,oalkfile,addalk,cdrmip_latmax, &
& cdrmip_latmin,ramp_start,ramp_end

! Read parameters for alkalinization fluxes from namelist file
if(.not. allocated(bgc_namelist)) call get_bgc_namelist
open (newunit=iounit, file=bgc_namelist, status='old' &
& ,action='read')
read (unit=iounit, nml=BGCOAFX)
close (unit=iounit)

! Return if alkalinization is turned off
if (.not. do_oalk) then
if (mnproc.eq.1) then
Expand All @@ -147,17 +169,14 @@ subroutine ini_read_oafx(kpie,kpje,pdlxp,pdlyp,pglat,omask)
write(io_stdo_bgc,*)' '
endif

!--------------------------------
! Scenarios of constant fluxes
!--------------------------------
if( trim(oalkscen)=='const_0p14' .or. trim(oalkscen)=='const_0p56' ) then
if( trim(oalkscen)=='const' .or. trim(oalkscen)=='ramp' ) then

if(mnproc.eq.1) then
write(io_stdo_bgc,*)'Using alkalinization scenario ', trim(oalkscen)
write(io_stdo_bgc,*)' '
endif

! Allocate field to hold constant alkalinization fluxes
! Allocate field to hold alkalinization fluxes
if(mnproc.eq.1) then
write(io_stdo_bgc,*)'Memory allocation for variable oalkflx ...'
write(io_stdo_bgc,*)'First dimension : ',kpie
Expand All @@ -181,18 +200,15 @@ subroutine ini_read_oafx(kpie,kpje,pdlxp,pdlyp,pglat,omask)

call xcsum(ztotarea,ztmp1,ips)

if( trim(oalkscen)=='const_0p14') then
addalk_tot = addalk_0p14
else
addalk_tot = addalk_0p56
endif

! Calculate alkalinity flux (kmol m^2 yr-1) to be applied
avflx = addalk_tot/ztotarea*Pmol2kmol
avflx = addalk/ztotarea*Pmol2kmol
if(mnproc.eq.1) then
write(io_stdo_bgc,*)' '
write(io_stdo_bgc,*)' applying alkalinity flux of ', avflx, ' kmol m-2 yr-1'
write(io_stdo_bgc,*)' over an area of ', ztotarea , ' m2'
if( trim(oalkscen)=='ramp' ) then
write(io_stdo_bgc,*)' ramping-up from ', ramp_start, ' to ', ramp_end
endif
endif

do j=1,kpje
Expand Down Expand Up @@ -248,14 +264,16 @@ subroutine get_oafx(kpie,kpje,kplyear,kplmon,omask,oafx)
! *REAL* *oaflx* - alkalinization flux [kmol m-2 yr-1]
!
!******************************************************************************
use mod_xc, only: xchalt
use mod_xc, only: xchalt,mnproc
use mo_control_bgc, only: io_stdo_bgc,do_oalk
use mod_time, only: nday_of_year

implicit none

integer, intent(in) :: kpie,kpje,kplyear,kplmon
real, intent(in) :: omask(kpie,kpje)
real, intent(out) :: oafx(kpie,kpje)
integer :: current_day

! local variables
integer :: i,j
Expand All @@ -268,10 +286,24 @@ subroutine get_oafx(kpie,kpje,kplyear,kplmon,omask,oafx)
!--------------------------------
! Scenarios of constant fluxes
!--------------------------------
if( trim(oalkscen)=='const_0p14' .or. trim(oalkscen)=='const_0p56' ) then
if( trim(oalkscen)=='const' ) then

oafx(:,:) = oalkflx(:,:)

!--------------------------------
! Scenario of ramping-up fluxes
!--------------------------------
elseif(trim(oalkscen)=='ramp' ) then

if(kplyear.lt.ramp_start ) then
oafx(:,:) = 0.0
elseif(kplyear.ge.ramp_end ) then
oafx(:,:) = oalkflx(:,:)
else
current_day = (kplyear-ramp_start)*365+nday_of_year
oafx(:,:) = oalkflx(:,:) * current_day / ((ramp_end-ramp_start)*365.)
endif

else

write(io_stdo_bgc,*) ''
Expand Down

0 comments on commit 417bdd8

Please sign in to comment.