Skip to content

Commit

Permalink
Move 3D chlorophyll to output_for_GCM_type
Browse files Browse the repository at this point in the history
This required a lot of small changes.

MARBL library:

1. Rename surface_flux_output* -> output_for_gcm*
2. Add total_Chl index to indexing type, and rename sfo_ind -> ofg_ind
3, Remove marbl_instance%get_output_for_GCM()
4. Add field_source to registry type as well as marbl_single_output_type (so
   GCM knows whether the field should be copied after surface_flux_compute() or
   after interior_tendency_compute())
5. Generalize registry definition, and make more specific error messages
   (flux_o2 requires both base_bio_on and lflux_gas_o2 to be true)
6. Pass output_for_GCM to interior_tendency_compute so it can populate
   total_Chl (if requested by GCM)

Stand-alone driver:

1. rename total_Chl -> interior_tendency_output, add num_vars dimension (this
   is the 3D equivalent to surface_flux_output). Note that there is an
   assumption that all outputs_for_GCM from surface_flux_compute are 2D, while
   all from interior_tendency_compute are 3D. This is fine for now, but we may
   need to introduce datatypes if future mods contradict that assumption
2. Rely on field_source in output_for_GCM type to know what to copy out of the
   type / when to copy it
3. Total Chl is no longer a special case in marbl_io_mod.F90, it comes through
   the output_for_GCM object
  • Loading branch information
mnlevy1981 committed Feb 13, 2024
1 parent 63307d2 commit d572db6
Show file tree
Hide file tree
Showing 7 changed files with 224 additions and 188 deletions.
81 changes: 25 additions & 56 deletions src/marbl_interface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -98,25 +98,26 @@ module marbl_interface
type(marbl_forcing_fields_type) , public, allocatable :: surface_flux_forcings(:) ! input
type(marbl_surface_flux_forcing_indexing_type) , public :: surface_flux_forcing_ind ! FIXME #311: should be private
real (r8) , public, allocatable :: surface_fluxes(:,:) ! output
type(marbl_output_for_GCM_registry_type) , public :: surface_flux_output_registry ! internal
type(marbl_output_for_GCM_type) , public :: surface_flux_output ! output
type(marbl_diagnostics_type) , public :: surface_flux_diags ! output

! public data that the GCM needs to explicitly request
type(marbl_output_for_GCM_type), public :: output_for_gcm ! output

! public data - global averages
real (r8) , public, allocatable :: glo_avg_fields_interior_tendency(:) ! output (nfields)
real (r8) , public, allocatable :: glo_avg_averages_interior_tendency(:) ! input (nfields)
real (r8) , public, allocatable :: glo_avg_fields_surface_flux(:,:) ! output (num_elements,nfields)
real (r8) , public, allocatable :: glo_avg_averages_surface_flux(:) ! input (nfields)
real (r8), public, allocatable :: glo_avg_fields_interior_tendency(:) ! output (nfields)
real (r8), public, allocatable :: glo_avg_averages_interior_tendency(:) ! input (nfields)
real (r8), public, allocatable :: glo_avg_fields_surface_flux(:,:) ! output (num_elements,nfields)
real (r8), public, allocatable :: glo_avg_averages_surface_flux(:) ! input (nfields)

! FIXME #77: for now, running means are being computed in the driver
! they will eventually be moved from the interface to inside MARBL
real (r8) , public, allocatable :: glo_scalar_interior_tendency(:)
real (r8) , public, allocatable :: glo_scalar_surface_flux(:)
real (r8), public, allocatable :: glo_scalar_interior_tendency(:)
real (r8), public, allocatable :: glo_scalar_surface_flux(:)

type(marbl_running_mean_0d_type) , public, allocatable :: glo_avg_rmean_interior_tendency(:)
type(marbl_running_mean_0d_type) , public, allocatable :: glo_avg_rmean_surface_flux(:)
type(marbl_running_mean_0d_type) , public, allocatable :: glo_scalar_rmean_interior_tendency(:)
type(marbl_running_mean_0d_type) , public, allocatable :: glo_scalar_rmean_surface_flux(:)
type(marbl_running_mean_0d_type), public, allocatable :: glo_avg_rmean_interior_tendency(:)
type(marbl_running_mean_0d_type), public, allocatable :: glo_avg_rmean_surface_flux(:)
type(marbl_running_mean_0d_type), public, allocatable :: glo_scalar_rmean_interior_tendency(:)
type(marbl_running_mean_0d_type), public, allocatable :: glo_scalar_rmean_surface_flux(:)

! private data
type(unit_system_type), private :: unit_system
Expand All @@ -140,6 +141,7 @@ module marbl_interface
type(marbl_internal_timers_type), private :: timers
type(marbl_timer_indexing_type), private :: timer_ids
type(marbl_settings_type), private :: settings
type(marbl_output_for_GCM_registry_type), private :: output_for_gcm_registry

contains

Expand All @@ -166,7 +168,6 @@ module marbl_interface
get_string
procedure, public :: get_settings_var_cnt
procedure, public :: add_output_for_GCM
procedure, public :: get_output_for_GCM
procedure, private :: inquire_settings_metadata_by_name
procedure, private :: inquire_settings_metadata_by_id
procedure, private :: put_real
Expand Down Expand Up @@ -304,7 +305,7 @@ subroutine init(this, &
! Register variables for add_output()
!-----------------------------------------------------------------------

call this%surface_flux_output_registry%create_registry(base_bio_on, this%unit_system%conc_flux_units)
call this%output_for_gcm_registry%create_registry(base_bio_on, this%unit_system%conc_flux_units)

!--------------------------------------------------------------------
! call constructors and allocate memory
Expand Down Expand Up @@ -787,55 +788,22 @@ subroutine add_output_for_GCM(this, num_elements, field_name, output_id, num_lev

character(len=*), parameter :: subname = 'marbl_interface:add_output_for_GCM'

call this%surface_flux_output%add_output(this%surface_flux_output_registry, &
num_elements, &
field_name, &
output_id, &
this%StatusLog, &
num_levels)
call this%output_for_gcm%add_output(this%output_for_gcm_registry, &
num_elements, &
field_name, &
output_id, &
this%StatusLog, &
num_levels)
if (this%StatusLog%labort_marbl) then
call this%StatusLog%log_error_trace('surface_flux_output%add_output()', subname)
call this%StatusLog%log_error_trace('output_for_gcm%add_output()', subname)
return
end if

end subroutine add_output_for_GCM

!***********************************************************************

subroutine get_output_for_GCM(this, field_ind, array_out)

use marbl_constants_mod, only : c0
use marbl_settings_mod, only : output_for_GCM_iopt_total_Chl_3d

class (marbl_interface_class), intent(inout) :: this
integer, intent(in) :: field_ind
real (r8), dimension(this%domain%km), intent(out) :: array_out

character(len=*), parameter :: subname = 'marbl_interface:get_output_for_GCM'
character(len=char_len) :: log_message
integer :: auto_ind, tr_ind

select case(field_ind)
case (output_for_GCM_iopt_total_Chl_3d)
if (.not. base_bio_on) then
log_message = "Can not provide 3D Chl without the base biotic tracers"
call this%StatusLog%log_error(log_message, subname)
end if
array_out(:) = c0
do auto_ind=1,size(this%tracer_indices%auto_inds)
tr_ind = this%tracer_indices%auto_inds(auto_ind)%Chl_ind
array_out(:) = array_out(:) + max(c0, this%tracers(tr_ind,:))
end do
case DEFAULT
write(log_message, "(I0,A)") field_ind, " is not a recognized value for field_ind"
call this%StatusLog%log_error(log_message, subname)
end select

end subroutine get_output_for_GCM

!***********************************************************************

subroutine inquire_settings_metadata_by_name(this, varname, id, lname, units, datatype)
subroutine inquire_settings_metadata_by_name(this, varname, id, lname, units, datatype)

class (marbl_interface_class), intent(inout) :: this
character(len=*), intent(in) :: varname
Expand Down Expand Up @@ -990,6 +958,7 @@ subroutine interior_tendency_compute(this)
zooplankton_local = this%zooplankton_local, &
zooplankton_share = this%zooplankton_share, &
saved_state = this%interior_tendency_saved_state, &
output_for_gcm = this%output_for_gcm, &
marbl_timers = this%timers, &
interior_tendency_share = this%interior_tendency_share, &
marbl_particulate_share = this%particulate_share, &
Expand Down Expand Up @@ -1039,7 +1008,7 @@ subroutine surface_flux_compute(this)
marbl_tracer_indices = this%tracer_indices, &
saved_state = this%surface_flux_saved_state, &
saved_state_ind = this%surf_state_ind, &
surface_flux_output = this%surface_flux_output, &
output_for_gcm = this%output_for_gcm, &
surface_flux_internal = this%surface_flux_internal, &
surface_flux_share = this%surface_flux_share, &
surface_flux_diags = this%surface_flux_diags, &
Expand Down
136 changes: 85 additions & 51 deletions src/marbl_interface_public_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,13 +16,14 @@ module marbl_interface_public_types
! to add a new index for it as well.
! * There are no interior tendency outputs at this time, so the type
! and ito_ind will need to be created when the first is added
type, public :: marbl_surface_flux_output_indexing_type
type, public :: marbl_output_for_GCM_indexing_type
integer(int_kind), pointer :: flux_o2_id
integer(int_kind), pointer :: flux_co2_id
integer(int_kind), pointer :: flux_nhx_id
integer(int_kind), pointer :: total_surfChl_id
end type marbl_surface_flux_output_indexing_type
type(marbl_surface_flux_output_indexing_type), public :: sfo_ind
integer(int_kind), pointer :: total_Chl_id
end type marbl_output_for_GCM_indexing_type
type(marbl_output_for_GCM_indexing_type), public :: ofg_ind

!*****************************************************************************

Expand Down Expand Up @@ -123,6 +124,7 @@ module marbl_interface_public_types
character(len=char_len) :: short_name
character(len=char_len) :: long_name
character(len=char_len) :: units
character(len=char_len) :: field_source
character(len=char_len) :: err_message
integer(int_kind), pointer :: id
end type marbl_output_for_GCM_single_register_type
Expand All @@ -145,9 +147,10 @@ module marbl_interface_public_types
! that needs to be passed to the GCM / flux coupler.
! Data must be accessed via the marbl_output_for_GCM_type
! data structure.
character (len=char_len) :: long_name
character (len=char_len) :: short_name
character (len=char_len) :: units
character(len=char_len) :: long_name
character(len=char_len) :: short_name
character(len=char_len) :: units
character(len=char_len) :: field_source
real(r8), allocatable, dimension(:) :: forcing_field_0d
real(r8), allocatable, dimension(:,:) :: forcing_field_1d
contains
Expand Down Expand Up @@ -484,9 +487,11 @@ subroutine marbl_single_output_constructor(this, output_registry, num_elements,
write(log_message, "(3A)") "Adding ", trim(field_name), " to outputs needed by the GCM"
call marbl_status_log%log_noerror(log_message, subname)

this%short_name = output_registry%registered_outputs(m)%short_name
this%long_name = output_registry%registered_outputs(m)%long_name
this%units = output_registry%registered_outputs(m)%units
this%short_name = output_registry%registered_outputs(m)%short_name
this%long_name = output_registry%registered_outputs(m)%long_name
this%units = output_registry%registered_outputs(m)%units
this%field_source = output_registry%registered_outputs(m)%field_source

if (num_levels .eq. 0) then
allocate(this%forcing_field_0d(num_elements))
this%forcing_field_0d = c0
Expand All @@ -495,7 +500,7 @@ subroutine marbl_single_output_constructor(this, output_registry, num_elements,
this%forcing_field_1d = c0
end if

! Set sfo_ind index for field_name
! Set ofg_ind index for field_name (via pointer)
output_registry%registered_outputs(m)%id = id
exit
end if
Expand Down Expand Up @@ -560,9 +565,10 @@ subroutine marbl_output_add(this, output_registry, num_elements, field_name, out

! 2) copy this%outputs_for_GCM into first N-1 elements of new_output
do n=1,old_size
new_output(n)%long_name = this%outputs_for_GCM(n)%long_name
new_output(n)%short_name = this%outputs_for_GCM(n)%short_name
new_output(n)%units = this%outputs_for_GCM(n)%units
new_output(n)%long_name = this%outputs_for_GCM(n)%long_name
new_output(n)%short_name = this%outputs_for_GCM(n)%short_name
new_output(n)%units = this%outputs_for_GCM(n)%units
new_output(n)%field_source = this%outputs_for_GCM(n)%field_source
if (allocated(this%outputs_for_GCM(n)%forcing_field_0d)) then
dim1_loc = size(this%outputs_for_GCM(n)%forcing_field_0d)
allocate(new_output(n)%forcing_field_0d(dim1_loc))
Expand Down Expand Up @@ -817,56 +823,84 @@ end subroutine marbl_timers_deconstructor

subroutine create_registry(this, base_bio_on, conc_flux_units)

use marbl_settings_mod, only : lflux_gas_o2
use marbl_settings_mod, only : lflux_gas_co2
use marbl_settings_mod, only : lcompute_nhx_surface_emis

class(marbl_output_for_GCM_registry_type), intent(out) :: this
logical, intent(in) :: base_bio_on
character(len=*), intent(in) :: conc_flux_units

integer :: m
integer, parameter :: ofg_cnt=5
integer :: ofg_ind_loc

! Defined outputs for the GCM are
! 1. O2 Flux
! 2. CO2 Flux
! 3. NHx Flux
! 4. Surface Chl
allocate(this%registered_outputs(4))
! 5. Total Chl
allocate(this%registered_outputs(ofg_cnt))

! Set error messages to empty strings
do ofg_ind_loc=1,ofg_cnt
this%registered_outputs(ofg_ind_loc)%err_message = ""
end do
ofg_ind_loc = 0

! Register names and units
this%registered_outputs(1)%short_name = "flux_o2"
this%registered_outputs(1)%long_name = "Oxygen Flux"
this%registered_outputs(1)%units = conc_flux_units
allocate(sfo_ind%flux_o2_id, source=0)
this%registered_outputs(1)%id => sfo_ind%flux_o2_id

this%registered_outputs(2)%short_name = "flux_co2"
this%registered_outputs(2)%long_name = "Carbon Dioxide Flux"
this%registered_outputs(2)%units = conc_flux_units
allocate(sfo_ind%flux_co2_id, source=0)
this%registered_outputs(2)%id => sfo_ind%flux_co2_id

this%registered_outputs(3)%short_name = "flux_nhx"
this%registered_outputs(3)%long_name = "NHx Surface Emissions"
this%registered_outputs(3)%units = conc_flux_units
allocate(sfo_ind%flux_nhx_id, source=0)
this%registered_outputs(3)%id => sfo_ind%flux_nhx_id

this%registered_outputs(4)%short_name = "total_surfChl"
this%registered_outputs(4)%long_name = "Total Chlorophyll Concentration"
this%registered_outputs(4)%units = "mg/m^3"
allocate(sfo_ind%total_surfChl_id, source=0)
this%registered_outputs(4)%id => sfo_ind%total_surfChl_id

! Set error messages
this%registered_outputs(1)%err_message = ""
this%registered_outputs(2)%err_message = ""
this%registered_outputs(3)%err_message = ""
this%registered_outputs(4)%err_message = ""
if (.not. base_bio_on) then
! All four outputs require the base biotic tracer module
do m=1,4
write(this%registered_outputs(m)%err_message, "(3A)") "Can not add ", trim(this%registered_outputs(m)%short_name), &
" to outputs without base biotic tracers"
end do
end if
ofg_ind_loc = ofg_ind_loc + 1
this%registered_outputs(ofg_ind_loc)%short_name = "flux_o2"
this%registered_outputs(ofg_ind_loc)%long_name = "Oxygen Flux"
this%registered_outputs(ofg_ind_loc)%units = conc_flux_units
this%registered_outputs(ofg_ind_loc)%field_source = "surface_flux"
allocate(ofg_ind%flux_o2_id, source=0)
this%registered_outputs(ofg_ind_loc)%id => ofg_ind%flux_o2_id
if (.not. (base_bio_on .and. lflux_gas_o2)) &
write(this%registered_outputs(ofg_ind_loc)%err_message, "(A,1X,A)") "Can not add flux_co2 to outputs without", &
"base biotic tracers and lflux_gas_o2"

ofg_ind_loc = ofg_ind_loc + 1
this%registered_outputs(ofg_ind_loc)%short_name = "flux_co2"
this%registered_outputs(ofg_ind_loc)%long_name = "Carbon Dioxide Flux"
this%registered_outputs(ofg_ind_loc)%units = conc_flux_units
this%registered_outputs(ofg_ind_loc)%field_source = "surface_flux"
allocate(ofg_ind%flux_co2_id, source=0)
this%registered_outputs(ofg_ind_loc)%id => ofg_ind%flux_co2_id
if (.not. (base_bio_on .and. lflux_gas_co2)) &
write(this%registered_outputs(ofg_ind_loc)%err_message, "(A,1X,A)") "Can not add flux_co2 to outputs without", &
"base biotic tracers and lflux_gas_co2"

ofg_ind_loc = ofg_ind_loc + 1
this%registered_outputs(ofg_ind_loc)%short_name = "flux_nhx"
this%registered_outputs(ofg_ind_loc)%long_name = "NHx Surface Emissions"
this%registered_outputs(ofg_ind_loc)%units = conc_flux_units
this%registered_outputs(ofg_ind_loc)%field_source = "surface_flux"
allocate(ofg_ind%flux_nhx_id, source=0)
this%registered_outputs(ofg_ind_loc)%id => ofg_ind%flux_nhx_id
if (.not. (base_bio_on .and. lcompute_nhx_surface_emis)) &
write(this%registered_outputs(ofg_ind_loc)%err_message, "(A,1X,A)") "Can not add flux_co2 to outputs without", &
"base biotic tracers and lcompute_nhx_surface_emis"

ofg_ind_loc = ofg_ind_loc + 1
this%registered_outputs(ofg_ind_loc)%short_name = "total_surfChl"
this%registered_outputs(ofg_ind_loc)%long_name = "Total Surface Chlorophyll Concentration"
this%registered_outputs(ofg_ind_loc)%units = "mg/m^3"
this%registered_outputs(ofg_ind_loc)%field_source = "surface_flux"
allocate(ofg_ind%total_surfChl_id, source=0)
this%registered_outputs(ofg_ind_loc)%id => ofg_ind%total_surfChl_id
if (.not. base_bio_on) &
this%registered_outputs(ofg_ind_loc)%err_message = "Can not add total_surfChl to outputs without base biotic tracers"

ofg_ind_loc = ofg_ind_loc + 1
this%registered_outputs(ofg_ind_loc)%short_name = "total_Chl"
this%registered_outputs(ofg_ind_loc)%long_name = "Total Chlorophyll Concentration"
this%registered_outputs(ofg_ind_loc)%units = "mg/m^3"
this%registered_outputs(ofg_ind_loc)%field_source = "interior_tendency"
allocate(ofg_ind%total_Chl_id, source=0)
this%registered_outputs(ofg_ind_loc)%id => ofg_ind%total_Chl_id
if (.not. base_bio_on) &
this%registered_outputs(ofg_ind_loc)%err_message = "Can not add total_Chl to outputs without base biotic tracers"

end subroutine create_registry

Expand Down
Loading

0 comments on commit d572db6

Please sign in to comment.