Skip to content

Commit

Permalink
Abort if requesting Chl output without base_bio
Browse files Browse the repository at this point in the history
There are also updates to the driver so that the call_compute_subroutines test
still runs when abio_dic_on = T and base_bio_on = F. I suspect there will be
baseline failures in that case due to changes in the output variables
  • Loading branch information
mnlevy1981 committed Jan 29, 2024
1 parent 420de7f commit c64e5b7
Show file tree
Hide file tree
Showing 4 changed files with 110 additions and 49 deletions.
9 changes: 9 additions & 0 deletions src/marbl_interface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -770,18 +770,27 @@ subroutine add_output_for_GCM(this, num_elements, field_name, output_id, num_lev
! If we introduce this%interior_tendency_output then this function will need
! a field_source argument (either 'surface_flux' or 'interior_tendency')

use marbl_settings_mod, only : base_bio_on

class (marbl_interface_class), intent(inout) :: this
character(len=*), intent(in) :: field_name
integer(int_kind), intent(in) :: num_elements
integer(int_kind), intent(out) :: output_id
integer(int_kind), optional, intent(in) :: num_levels

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

call this%surface_flux_output%add_output(num_elements, &
field_name, &
this%unit_system%conc_flux_units, &
base_bio_on, &
output_id, &
this%StatusLog, &
num_levels)
if (this%StatusLog%labort_marbl) then
call this%StatusLog%log_error_trace('surface_flux_output%add_output()', subname)
return
end if

end subroutine add_output_for_GCM

Expand Down
40 changes: 34 additions & 6 deletions src/marbl_interface_public_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -138,9 +138,9 @@ module marbl_interface_public_types
!*****************************************************************************

type, public :: marbl_output_for_GCM_type
integer :: output_cnt
type(marbl_single_output_type), dimension(:), pointer :: outputs_for_GCM => NULL()
contains
procedure, public :: size => get_marbl_output_for_GCM_cnt
procedure, public :: add_output => marbl_output_add
end type marbl_output_for_GCM_type

Expand Down Expand Up @@ -442,36 +442,43 @@ end subroutine marbl_single_diag_init
!*****************************************************************************

subroutine marbl_single_output_constructor(this, num_elements, num_levels, field_name, id, &
conc_flux_units, marbl_status_log)
conc_flux_units, base_bio_on, marbl_status_log)

class(marbl_single_output_type), intent(out) :: this
character(len=*), intent(in) :: field_name
integer(int_kind), intent(in) :: num_elements
integer(int_kind), intent(in) :: num_levels
integer(int_kind), intent(in) :: id
character(len=*), intent(in) :: conc_flux_units
logical, intent(in) :: base_bio_on
type(marbl_log_type), intent(inout) :: marbl_status_log

character(len=*), parameter :: subname = 'marbl_interface_public_types:marbl_single_output_constructor'
character(len=char_len) :: log_message
logical :: requires_base_bio

requires_base_bio = .false.
select case (trim(field_name))
case("flux_o2")
requires_base_bio = .true.
this%long_name = "Oxygen Flux"
this%short_name = "flux_o2"
this%units = conc_flux_units
sfo_ind%flux_o2_id = id
case("flux_co2")
requires_base_bio = .true.
this%long_name = "Carbon Dioxide Flux"
this%short_name = "flux_co2"
this%units = conc_flux_units
sfo_ind%flux_co2_id = id
case("flux_nhx")
requires_base_bio = .true.
this%long_name = "NHx Surface Emissions"
this%short_name = "flux_nhx"
this%units = conc_flux_units
sfo_ind%flux_nhx_id = id
case("total_surfChl")
requires_base_bio = .true.
this%long_name = "Total Chlorophyll Concentration"
this%short_name = "total_surfChl"
this%units = "mg/m^3"
Expand All @@ -481,6 +488,11 @@ subroutine marbl_single_output_constructor(this, num_elements, num_levels, field
call marbl_status_log%log_error(log_message, subname)
return
end select
if (requires_base_bio .and. (.not. base_bio_on)) then
write(log_message, "(3A)") "Can not add ", trim(field_name), " to outputs without base biotic tracers"
call marbl_status_log%log_error(log_message, subname)
return
end if
write(log_message, "(3A)") "Adding ", trim(field_name), " to outputs needed by the GCM"
call marbl_status_log%log_noerror(log_message, subname)

Expand All @@ -496,8 +508,8 @@ end subroutine marbl_single_output_constructor

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

subroutine marbl_output_add(this, num_elements, field_name, conc_flux_units, output_id, &
marbl_status_log, num_levels)
subroutine marbl_output_add(this, num_elements, field_name, conc_flux_units, base_bio_on, &
output_id, marbl_status_log, num_levels)

! MARBL uses pointers to create an extensible allocatable array. The output
! fields (part of the intent(out) of this routine) are stored in
Expand All @@ -517,6 +529,7 @@ subroutine marbl_output_add(this, num_elements, field_name, conc_flux_units, out
character(len=*), intent(in) :: field_name
integer(int_kind), intent(in) :: num_elements
character(len=*), intent(in) :: conc_flux_units
logical, intent(in) :: base_bio_on
integer(int_kind), intent(out) :: output_id
type(marbl_log_type), intent(inout) :: marbl_status_log
integer(int_kind), optional, intent(in) :: num_levels
Expand Down Expand Up @@ -564,8 +577,8 @@ subroutine marbl_output_add(this, num_elements, field_name, conc_flux_units, out
end do

! 3) newest surface flux output (field_name) is Nth element of new_output
call new_output(output_id)%construct(num_elements, num_levels_loc, field_name, &
output_id, conc_flux_units, marbl_status_log)
call new_output(output_id)%construct(num_elements, num_levels_loc, field_name, output_id, &
conc_flux_units, base_bio_on, marbl_status_log)
if (marbl_status_log%labort_marbl) then
call marbl_status_log%log_error_trace('new_output%construct()', subname)
return
Expand All @@ -584,6 +597,21 @@ end subroutine marbl_output_add

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

function get_marbl_output_for_GCM_cnt(this)

class (marbl_output_for_GCM_type), intent(in) :: this
integer :: get_marbl_output_for_GCM_cnt

if (associated(this%outputs_for_GCM)) then
get_marbl_output_for_GCM_cnt = size(this%outputs_for_GCM)
else
get_marbl_output_for_GCM_cnt = 0
end if

end function get_marbl_output_for_GCM_cnt

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

subroutine marbl_diagnostics_constructor(this, num_elements, num_levels)

class(marbl_diagnostics_type), intent(out) :: this
Expand Down
47 changes: 31 additions & 16 deletions tests/driver_src/marbl_call_compute_subroutines_drv.F90
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@ subroutine test(marbl_instances, hist_file, unit_system_opt, driver_status_log)

integer :: num_levels, num_cols, num_tracers, m, n, col_id_loc, col_id, num_PAR_subcols
integer :: sfo_cnt, flux_co2_id, total_surfChl_id, output_id
logical :: base_bio_on
type(grid_data_type) :: grid_data

! 1. Open necessary netCDF files
Expand Down Expand Up @@ -92,6 +93,7 @@ subroutine test(marbl_instances, hist_file, unit_system_opt, driver_status_log)
return
end if
end do
call marbl_instances(1)%get_setting('base_bio_on', base_bio_on)

! --------------------------------------------------------------------------

Expand All @@ -100,19 +102,31 @@ subroutine test(marbl_instances, hist_file, unit_system_opt, driver_status_log)
! (a) Fields returned from surface_flux_compute()
sfo_cnt = 0

sfo_cnt = sfo_cnt+1
do n=1, size(marbl_instances)
call marbl_instances(n)%add_output_for_GCM(num_elements=col_cnt(n), &
field_name="flux_co2", &
output_id=flux_co2_id)
end do
if (base_bio_on) then
sfo_cnt = sfo_cnt+1
do n=1, size(marbl_instances)
call marbl_instances(n)%add_output_for_GCM(num_elements=col_cnt(n), &
field_name="flux_co2", &
output_id=flux_co2_id)
if (marbl_instances(n)%StatusLog%labort_marbl) then
call marbl_instances(n)%StatusLog%log_error_trace('marbl%add_output_for_GCM(flux_co2)', subname)
return
end if
end do
end if

sfo_cnt = sfo_cnt+1
do n=1, size(marbl_instances)
call marbl_instances(n)%add_output_for_GCM(num_elements=col_cnt(n), &
field_name="total_surfChl", &
output_id=total_surfChl_id)
end do
if (base_bio_on) then
sfo_cnt = sfo_cnt+1
do n=1, size(marbl_instances)
call marbl_instances(n)%add_output_for_GCM(num_elements=col_cnt(n), &
field_name="total_surfChl", &
output_id=total_surfChl_id)
if (marbl_instances(n)%StatusLog%labort_marbl) then
call marbl_instances(n)%StatusLog%log_error_trace('marbl%add_output_for_GCM(total_surfChl)', subname)
return
end if
end do
end if

allocate(surface_flux_output(num_cols, sfo_cnt))
allocate(total_Chl(num_levels, num_cols))
Expand Down Expand Up @@ -157,7 +171,7 @@ subroutine test(marbl_instances, hist_file, unit_system_opt, driver_status_log)
end do

! (d) netCDF calls to create history file (dimensions are defined but data is not written)
call marbl_io_define_history(marbl_instances, col_cnt, unit_system_opt, driver_status_log)
call marbl_io_define_history(marbl_instances, col_cnt, unit_system_opt, base_bio_on, driver_status_log)
if (driver_status_log%labort_marbl) then
call driver_status_log%log_error_trace('marbl_io_define_history', subname)
return
Expand Down Expand Up @@ -231,7 +245,7 @@ subroutine test(marbl_instances, hist_file, unit_system_opt, driver_status_log)
! Note: passing col_start and col_cnt => surface flux diagnostic buffer
call marbl_io_copy_into_diag_buffer(col_start(n), col_cnt(n), marbl_instances(n))
surface_fluxes((col_start(n)+1):(col_start(n)+col_cnt(n)),:) = marbl_instances(n)%surface_fluxes(:,:)
do output_id = 1, size(marbl_instances(n)%surface_flux_output%outputs_for_GCM)
do output_id = 1, marbl_instances(n)%surface_flux_output%size()
surface_flux_output((col_start(n)+1):(col_start(n)+col_cnt(n)),output_id) = &
marbl_instances(n)%surface_flux_output%outputs_for_GCM(output_id)%forcing_field_0d(:)
end do
Expand Down Expand Up @@ -290,7 +304,8 @@ subroutine test(marbl_instances, hist_file, unit_system_opt, driver_status_log)
! Note: passing just col_id => interior tendency diagnostic buffer
call marbl_io_copy_into_diag_buffer(col_id, marbl_instances(n))
interior_tendencies(:,:,col_id) = marbl_instances(n)%interior_tendencies(:,:)
call marbl_instances(n)%get_output_for_GCM(output_for_GCM_iopt_total_Chl_3d, total_Chl(:,col_id))
if (base_bio_on) &
call marbl_instances(n)%get_output_for_GCM(output_for_GCM_iopt_total_Chl_3d, total_Chl(:,col_id))
end do ! column
end do ! instance

Expand All @@ -299,7 +314,7 @@ subroutine test(marbl_instances, hist_file, unit_system_opt, driver_status_log)
! 8. Output netCDF
call marbl_io_write_history(marbl_instances(1), surface_fluxes, interior_tendencies, &
surface_flux_output, total_Chl, tracer_initial_vals, &
active_level_cnt, driver_status_log)
active_level_cnt, base_bio_on, driver_status_log)
if (driver_status_log%labort_marbl) then
call driver_status_log%log_error_trace('marbl_io_write_history', subname)
return
Expand Down
63 changes: 36 additions & 27 deletions tests/driver_src/marbl_io_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -687,14 +687,15 @@ end subroutine marbl_io_read_tracers

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

subroutine marbl_io_define_history(marbl_instances, col_cnt, unit_system_opt, driver_status_log)
subroutine marbl_io_define_history(marbl_instances, col_cnt, unit_system_opt, base_bio_on, driver_status_log)

use marbl_netcdf_mod, only : marbl_netcdf_def_dim
use marbl_netcdf_mod, only : marbl_netcdf_enddef

type(marbl_interface_class), dimension(:), intent(in) :: marbl_instances
integer, dimension(:), intent(in) :: col_cnt
character(len=*), intent(in) :: unit_system_opt
logical, intent(in) :: base_bio_on
type(marbl_log_type), intent(inout) :: driver_status_log

character(len=*), parameter :: subname = 'marbl_netcdf_mod:marbl_io_define_history'
Expand Down Expand Up @@ -803,7 +804,7 @@ subroutine marbl_io_define_history(marbl_instances, col_cnt, unit_system_opt, dr
end do

! Output from surface_flux_compute() for GCM to use
do n=1, size(marbl_instances(1)%surface_flux_output%outputs_for_GCM)
do n=1, marbl_instances(1)%surface_flux_output%size()
write(varname, "(2A)") "output_for_GCM_", &
trim(marbl_instances(1)%surface_flux_output%outputs_for_GCM(n)%short_name)
long_name = marbl_instances(1)%surface_flux_output%outputs_for_GCM(n)%long_name
Expand All @@ -817,16 +818,18 @@ subroutine marbl_io_define_history(marbl_instances, col_cnt, unit_system_opt, dr
end if
end do

! We will request total_Chl_3d from the model
varname = "output_for_GCM_total_Chl"
long_name = "Total Chlorophyll Concentration"
units = "mg/m^3"
call marbl_netcdf_def_var(ncid_out, varname, 'double', (/dimid_num_levels, dimid_num_cols/), &
long_name, units, driver_status_log, ldef_fillval=.true.)
if (driver_status_log%labort_marbl) then
write(log_message, "(3A)") 'marbl_netcdf_def_var(', varname, ')'
call driver_status_log%log_error_trace(log_message, subname)
return
if (base_bio_on) then
! We will request total_Chl_3d from the model
varname = "output_for_GCM_total_Chl"
long_name = "Total Chlorophyll Concentration"
units = "mg/m^3"
call marbl_netcdf_def_var(ncid_out, varname, 'double', (/dimid_num_levels, dimid_num_cols/), &
long_name, units, driver_status_log, ldef_fillval=.true.)
if (driver_status_log%labort_marbl) then
write(log_message, "(3A)") 'marbl_netcdf_def_var(', varname, ')'
call driver_status_log%log_error_trace(log_message, subname)
return
end if
end if

! Exit define mode
Expand Down Expand Up @@ -888,7 +891,7 @@ end subroutine marbl_io_copy_into_diag_buffer_interior

subroutine marbl_io_write_history(marbl_instance, surface_fluxes, interior_tendencies, &
surface_flux_output, total_Chl, tracer_initial_vals, &
active_level_cnt, driver_status_log)
active_level_cnt, base_bio_on, driver_status_log)

type(marbl_interface_class), intent(in) :: marbl_instance
real(r8), dimension(:,:), intent(in) :: surface_fluxes ! num_cols x num_tracers
Expand All @@ -897,6 +900,7 @@ subroutine marbl_io_write_history(marbl_instance, surface_fluxes, interior_tende
real(r8), dimension(:,:), intent(in) :: total_Chl ! num_levels x num_cols
real(r8), dimension(:,:,:), intent(in) :: tracer_initial_vals ! num_tracers x num_levels x num_cols
integer, dimension(:), intent(in) :: active_level_cnt
logical, intent(in) :: base_bio_on
type(marbl_log_type), intent(inout) :: driver_status_log

character(len=*), parameter :: subname = 'marbl_netcdf_mod:marbl_io_write_history'
Expand All @@ -911,6 +915,7 @@ subroutine marbl_io_write_history(marbl_instance, surface_fluxes, interior_tende
call driver_status_log%log_error_trace('marbl_netcdf_inq_varid(zt)', subname)
return
end if

call marbl_netcdf_put_var(ncid_out, varid, marbl_instance%domain%zt, driver_status_log)
if (driver_status_log%labort_marbl) then
call driver_status_log%log_error_trace('marbl_netcdf_put_var(zt)', subname)
Expand All @@ -922,6 +927,7 @@ subroutine marbl_io_write_history(marbl_instance, surface_fluxes, interior_tende
call driver_status_log%log_error_trace('marbl_netcdf_inq_varid(zw)', subname)
return
end if

call marbl_netcdf_put_var(ncid_out, varid, marbl_instance%domain%zw, driver_status_log)
if (driver_status_log%labort_marbl) then
call driver_status_log%log_error_trace('marbl_netcdf_put_var(zw)', subname)
Expand All @@ -931,14 +937,15 @@ subroutine marbl_io_write_history(marbl_instance, surface_fluxes, interior_tende
do col_id=1, size(bot_depth)
bot_depth(col_id) = marbl_instance%domain%zw(active_level_cnt(col_id))
end do

! 2) Surface and Interior diagnostics
call write_diag_buffer_to_nc(surface_flux_diag_buffer, active_level_cnt, driver_status_log)
! FIXME #176: changing active_level_cnt to num_levels (km instead of kmt) will populate levels below
! active_level_cnt with nonsensical values
call write_diag_buffer_to_nc(interior_tendency_diag_buffer, active_level_cnt, &
driver_status_log, bot_depth=bot_depth)

! 4) Tracer surface fluxes, tendencies, and initial conditions
! 3) Tracer surface fluxes, tendencies, and initial conditions
do n=1, size(marbl_instance%tracer_metadata)
! Surface fluxes
call get_surface_flux_desc_from_metadata(marbl_instance%tracer_metadata(n), varname)
Expand Down Expand Up @@ -988,8 +995,8 @@ subroutine marbl_io_write_history(marbl_instance, surface_fluxes, interior_tende

end do

! 5) Output for GCM to use
do n=1, size(marbl_instance%surface_flux_output%outputs_for_GCM)
! 4) Output for GCM to use
do n=1, marbl_instance%surface_flux_output%size()
write(varname, "(2A)") "output_for_GCM_", &
trim(marbl_instance%surface_flux_output%outputs_for_GCM(n)%short_name)
call marbl_netcdf_inq_varid(ncid_out, varname, varid, driver_status_log)
Expand All @@ -1006,17 +1013,19 @@ subroutine marbl_io_write_history(marbl_instance, surface_fluxes, interior_tende
end if
end do

call marbl_netcdf_inq_varid(ncid_out, "output_for_GCM_total_Chl", varid, driver_status_log)
if (driver_status_log%labort_marbl) then
write(log_message, "(3A)") 'marbl_netcdf_inq_varid(', trim(varname), ')'
call driver_status_log%log_error_trace(log_message, subname)
return
end if
call marbl_netcdf_put_var(ncid_out, varid, total_Chl(:, :), active_level_cnt, driver_status_log)
if (driver_status_log%labort_marbl) then
write(log_message, "(3A)") 'marbl_netcdf_put_var(', trim(varname), ')'
call driver_status_log%log_error_trace(log_message, subname)
return
if (base_bio_on) then
call marbl_netcdf_inq_varid(ncid_out, "output_for_GCM_total_Chl", varid, driver_status_log)
if (driver_status_log%labort_marbl) then
write(log_message, "(3A)") 'marbl_netcdf_inq_varid(', trim(varname), ')'
call driver_status_log%log_error_trace(log_message, subname)
return
end if
call marbl_netcdf_put_var(ncid_out, varid, total_Chl(:, :), active_level_cnt, driver_status_log)
if (driver_status_log%labort_marbl) then
write(log_message, "(3A)") 'marbl_netcdf_put_var(', trim(varname), ')'
call driver_status_log%log_error_trace(log_message, subname)
return
end if
end if

end subroutine marbl_io_write_history
Expand Down

0 comments on commit c64e5b7

Please sign in to comment.