Skip to content

Commit

Permalink
Merge pull request #225 from derpycode/_DEV_radfor
Browse files Browse the repository at this point in the history
_DEV_radfor -> master
  • Loading branch information
derpycode committed Jul 14, 2023
2 parents 4fc9dae + a450023 commit f613bd8
Show file tree
Hide file tree
Showing 6 changed files with 52 additions and 36 deletions.
58 changes: 27 additions & 31 deletions genie-atchem/src/fortran/atchem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -35,28 +35,26 @@ SUBROUTINE atchem( &
! fractional reduction factors for decaying isotopes
loc_fracdecay_atm(:) = EXP(-loc_dtyr*const_lambda_atm(:))

! *** OXIDIZE CH4 [NOTE: for schemes that initially homogenize atmospheric composition]***
select case (par_atm_CH4_photochem)
! *** OXIDIZE CH4 ***
! NOTE: these subrouotines will oxidize CH4 acorss the entire 2D tracer array
! confusingly, later, in the grid point loop, there are further CH4 oxidation possibilities ...
! NOTE: all implicitly deal with 13 and 14C
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
select case (par_atm_CH4_photochem)
case ('claire06')
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
CALL sub_calc_oxidize_CH4_claire06(loc_dtyr,loc_conv_atm_mol(:,:))
END IF
CALL sub_calc_oxidize_CH4_claire06(loc_dtyr,loc_conv_atm_mol(:,:))
case('claire06_fixed')
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
CALL sub_calc_oxidize_CH4_claire06_fixed(loc_dtyr,loc_conv_atm_mol(:,:))
END IF
CALL sub_calc_oxidize_CH4_claire06_fixed(loc_dtyr,loc_conv_atm_mol(:,:))
case ('claire06H')
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
CALL sub_calc_oxidize_CH4_claire06H(loc_dtyr,loc_conv_atm_mol(:,:))
END IF
CALL sub_calc_oxidize_CH4_claire06H(loc_dtyr,loc_conv_atm_mol(:,:))
case ('goldblatt06')
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
CALL sub_calc_oxidize_CH4_goldblatt06(loc_dtyr,loc_conv_atm_mol(:,:))
END IF
case default
!!! NOTHING
end select

CALL sub_calc_oxidize_CH4_goldblatt06(loc_dtyr,loc_conv_atm_mol(:,:))
case ('NONE')
! (no CH4 oxidation)
case default
! (no 2D array oxidation selected, but CH4 oxidation might occur via a grid-point specific subroutine later ...)
end select
END IF

! >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> !
! *** (i,j) GRID PT LOOP START *** !
Expand All @@ -75,26 +73,24 @@ SUBROUTINE atchem( &
end do

! *** OXIDIZE CH4 ***
select case (par_atm_CH4_photochem)
case ('default')
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
! NOTE: these are alternatives to the formulations and subroutines acting on the entire 2D tracer array (above)
! NOTE: all implicitly deal with 13 and 14C
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
select case (par_atm_CH4_photochem)
case ('default')
CALL sub_calc_oxidize_CH4_default(i,j,loc_dtyr)
END IF
case ('snowball')
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
case ('snowball')
if (sum(dum_sfcatm(ia_T,:,:))/size(dum_sfcatm(ia_T,:,:)) > 0.0) then
IF (atm(ia_pCH4,i,j) > 700.0E-9) THEN
CALL sub_calc_oxidize_CH4_default(i,j,loc_dtyr)
END if
END IF
END IF
case ('schmidt03')
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
case ('schmidt03')
CALL sub_calc_oxidize_CH4_schmidt03(i,j,loc_dtyr)
END IF
case default
!!! NOTHING
end select
case ('NONE')
! (no CH4 oxidation)
end select
END IF

! *** ADD CH4 ***
IF (atm_select(ia_pCH4) .AND. atm_select(ia_pCO2) .AND. atm_select(ia_pO2)) THEN
Expand Down
10 changes: 9 additions & 1 deletion genie-atchem/src/fortran/atchem_box.f90
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@ SUBROUTINE sub_calc_terrCO2exchange(dum_i,dum_j,dum_dtyr,dum_fatm)
END SUBROUTINE sub_calc_terrCO2exchange
! ****************************************************************************************************************************** !


! *****************************************************************************************************************************!
! OXIDIZE CH4 -- DEFAULT (ORIGINAL) SCHEME
SUBROUTINE sub_calc_oxidize_CH4_default(dum_i,dum_j,dum_dtyr)
Expand Down Expand Up @@ -82,6 +83,7 @@ SUBROUTINE sub_calc_oxidize_CH4_default(dum_i,dum_j,dum_dtyr)
END SUBROUTINE sub_calc_oxidize_CH4_default
! ****************************************************************************************************************************** !


! *****************************************************************************************************************************!
! OXIDIZE CH4 -- FIT TO DATA FROM 2-D PHOTOCHEMISTRY MODEL IN SCHMIDT & SCHINDELL [2003] (CTR|12-2017)
SUBROUTINE sub_calc_oxidize_CH4_schmidt03(dum_i,dum_j,dum_dtyr)
Expand Down Expand Up @@ -116,6 +118,7 @@ SUBROUTINE sub_calc_oxidize_CH4_schmidt03(dum_i,dum_j,dum_dtyr)
END SUBROUTINE sub_calc_oxidize_CH4_schmidt03
! ****************************************************************************************************************************** !


! ****************************************************************************************************************************** !
! OXIDIZE CH4 -- PHOTOCHEMICAL SCHEME AFTER CLAIRE ET AL. [2006], NO H ESCAPE (CTR|01-2018)
SUBROUTINE sub_calc_oxidize_CH4_claire06(dum_dtyr,dum_conv_atm_mol)
Expand Down Expand Up @@ -247,6 +250,7 @@ SUBROUTINE sub_calc_oxidize_CH4_claire06(dum_dtyr,dum_conv_atm_mol)

END SUBROUTINE sub_calc_oxidize_CH4_claire06
! ****************************************************************************************************************************** !


! ****************************************************************************************************************************** !
! OXIDIZE CH4 -- PHOTOCHEMICAL SCHEME AFTER CLAIRE ET AL. [2006], NO H ESCAPE, FIXED ATMOSPHERIC O2 (CTR|09-2018)
Expand Down Expand Up @@ -374,7 +378,8 @@ SUBROUTINE sub_calc_oxidize_CH4_claire06_fixed(dum_dtyr,dum_conv_atm_mol)

END SUBROUTINE sub_calc_oxidize_CH4_claire06_fixed
! ****************************************************************************************************************************** !



! ****************************************************************************************************************************** !
! OXIDIZE CH4 -- PHOTOCHEMICAL SCHEME AFTER CLAIRE ET AL. [2006], H ESCAPE ENABLED (CTR|05-2017)
SUBROUTINE sub_calc_oxidize_CH4_claire06H(dum_dtyr,dum_conv_atm_mol)
Expand Down Expand Up @@ -512,6 +517,7 @@ SUBROUTINE sub_calc_oxidize_CH4_claire06H(dum_dtyr,dum_conv_atm_mol)

END SUBROUTINE sub_calc_oxidize_CH4_claire06H
! ****************************************************************************************************************************** !


! ****************************************************************************************************************************** !
! OXIDIZE CH4 -- UPDATED PHOTOCHEMICAL SCHEME AFTER GOLDBLATT ET AL. [2006] (SLO|2015, CTR|05-2017)
Expand Down Expand Up @@ -576,6 +582,7 @@ SUBROUTINE sub_calc_oxidize_CH4_goldblatt06(dum_dtyr,dum_conv_atm_mol)
END SUBROUTINE sub_calc_oxidize_CH4_goldblatt06
! ****************************************************************************************************************************** !


! ****************************************************************************************************************************** !
! WETLANDS CH4 FLUX
SUBROUTINE sub_calc_wetlands_CH4(dum_dtyr,dum_fatm)
Expand Down Expand Up @@ -622,6 +629,7 @@ SUBROUTINE sub_calc_wetlands_CH4(dum_dtyr,dum_fatm)
END SUBROUTINE sub_calc_wetlands_CH4
! ****************************************************************************************************************************** !


! ****************************************************************************************************************************** !
! PRODUCE 14C
SUBROUTINE sub_calc_generate_14C(dum_dtyr,dum_fatm)
Expand Down
3 changes: 2 additions & 1 deletion genie-embm/src/fortran/embm.cmn
Original file line number Diff line number Diff line change
Expand Up @@ -306,7 +306,8 @@ c AR : radiative forcing by CH4 and N2O
real alphach4,alphan2o
common /embm_greenhouse/alphach4,alphan2o
logical opt_delf2x_cesm
common /embm_greenhouse/opt_delf2x_cesm
logical opt_co2ch4radfor
common /embm_greenhouse/opt_delf2x_cesm,opt_co2ch4radfor

c orography
real lapse_rate
Expand Down
2 changes: 1 addition & 1 deletion genie-embm/src/fortran/initialise_embm.F
Original file line number Diff line number Diff line change
Expand Up @@ -279,7 +279,7 @@ subroutine initialise_embm(alon1,alat1,alon2,alat2,
NAMELIST /ini_embm_nml/par_albedo1d_name,par_albedo2d_name
NAMELIST /ini_embm_nml/par_orbit_osce,par_orbit_oscsob
NAMELIST /ini_embm_nml/par_orbit_oscgam,par_orbit_osctau0
NAMELIST /ini_embm_nml/opt_delf2x_cesm
NAMELIST /ini_embm_nml/opt_delf2x_cesm,opt_co2ch4radfor

c ------------------------------------------------------------ c
c INITIALIZE VARIABLES
Expand Down
11 changes: 9 additions & 2 deletions genie-embm/src/fortran/surflux.F
Original file line number Diff line number Diff line change
Expand Up @@ -798,8 +798,16 @@ subroutine surflux(istep,
tv1 = b01 + rq*(b11 + b21*rq)
tv2 = b02 + rq*(b12 + b22*rq)
tv3 = b03 + rq*(b13 + b23*rq)
c aAlow for the CH4 concentration to drive CO2 radiative forcing instead of actual CO2
c (allowing varying CO2 radiative forcing while allowing CO2 to independently vary and respond to climate feedbacks)
c If so: the CH4 term must be set to zero (and associated N2O term))
if(opt_co2ch4radfor) then
co2(i,j) = ch4(i,j)
ch4(i,j) = ch40
n2o(i,j) = n2o0
endif
c calculate CO2 contribution
c MLI (16/09/20) State dependent climate sensitivity
c MLI (16/09/20) State dependent climate sensitivity
if(opt_delf2x_cesm) then
co2_t1 = co2(i,j)*1e6
co2_t2 = (7.58434074655/1e10) * (co2_t1**(3.))
Expand Down Expand Up @@ -1409,7 +1417,6 @@ subroutine surflux(istep,
print*,'istep ',istep
print*,' '
endif
enddo
Expand Down
4 changes: 4 additions & 0 deletions genie-main/src/xml-config/xml/definition.xml
Original file line number Diff line number Diff line change
Expand Up @@ -2110,6 +2110,10 @@
<value datatype="boolean">.false.</value>
<description>apply CESM state-dependent climate sensitivity</description>
</param>
<param name="opt_co2ch4radfor">
<value datatype="boolean">.false.</value>
<description>allow CH4 concentration to be substituted into the CO2 radiative forcing calculation</description>
</param>
</namelist>
</file>
</model>
Expand Down

0 comments on commit f613bd8

Please sign in to comment.