Skip to content

Commit

Permalink
Lots of small fixes from code review
Browse files Browse the repository at this point in the history
1. Better comments in create_registry
2. The registry error message is now prepended with the field name in
   add_output_for_GCM()
3. create_registry can use base_bio_on, doesn't need it as an intent(in)
4. better comment in add_output_for_GCM (logs an error message, doesn't return
   one)
5. If ofg_ind is a target, components of output_for_gcm_type don't need to be
   pointers (registry%id => ofg_ind%* works)

Still have a few slightly bigger changes to make in the next commit
  • Loading branch information
mnlevy1981 committed Feb 15, 2024
1 parent b6b2f5a commit 89cf5b9
Show file tree
Hide file tree
Showing 4 changed files with 30 additions and 35 deletions.
11 changes: 5 additions & 6 deletions src/marbl_interface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@ module marbl_interface

use marbl_kinds_mod, only : r8, log_kind, int_kind, log_kind, char_len

use marbl_settings_mod, only : base_bio_on
use marbl_settings_mod, only : unit_system_type
use marbl_settings_mod, only : zooplankton_cnt
use marbl_settings_mod, only : marbl_settings_type
Expand Down Expand Up @@ -306,7 +305,7 @@ subroutine init(this, &
! Register variables for add_output()
!-----------------------------------------------------------------------

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

!--------------------------------------------------------------------
! call constructors and allocate memory
Expand Down Expand Up @@ -777,9 +776,8 @@ end function get_settings_var_cnt
!***********************************************************************

subroutine add_output_for_GCM(this, num_elements, field_name, output_id, field_source, num_levels)
! Check the registry to see if field_name is provided from surface_flux_compute()
! or interior_tendency_compute(); add it to the proper output_for_GCM type, or
! return a useful error message
! Check the registry to see if field_name is provided from surface_flux_compute() or interior_tendency_compute()
! add it to the proper output_for_GCM type, or log a useful error message

class (marbl_interface_class), intent(inout) :: this
character(len=*), intent(in) :: field_name
Expand All @@ -799,7 +797,8 @@ subroutine add_output_for_GCM(this, num_elements, field_name, output_id, field_s
if (trim(field_name) == trim(this%output_for_gcm_registry%registered_outputs(m)%short_name)) then
! err_message will be populated if this field is unavailable in current configuration
if (len_trim(this%output_for_gcm_registry%registered_outputs(m)%err_message) > 0) then
call this%StatusLog%log_error(this%output_for_gcm_registry%registered_outputs(m)%err_message, subname)
write(log_message, "(A,1X,A)") trim(field_name), trim(this%output_for_gcm_registry%registered_outputs(m)%err_message)
call this%StatusLog%log_error(log_message, subname)
return
end if
exit
Expand Down
42 changes: 20 additions & 22 deletions src/marbl_interface_public_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,13 @@ module marbl_interface_public_types
! * 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_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
integer(int_kind), pointer :: total_Chl_id
integer(int_kind) :: flux_o2_id = 0
integer(int_kind) :: flux_co2_id = 0
integer(int_kind) :: flux_nhx_id = 0
integer(int_kind) :: total_surfChl_id = 0
integer(int_kind) :: total_Chl_id = 0
end type marbl_output_for_GCM_indexing_type
type(marbl_output_for_GCM_indexing_type), public :: ofg_ind
type(marbl_output_for_GCM_indexing_type), target, public :: ofg_ind

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

Expand Down Expand Up @@ -783,14 +783,14 @@ end subroutine marbl_timers_deconstructor

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

subroutine create_registry(this, base_bio_on, conc_flux_units)
subroutine create_registry(this, conc_flux_units)

use marbl_settings_mod, only : base_bio_on
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, parameter :: ofg_cnt=5
Expand All @@ -810,59 +810,57 @@ subroutine create_registry(this, base_bio_on, conc_flux_units)
end do
ofg_ind_loc = 0

! Register names and units
! Register names and units of all outputs that can be provided to GCM

! Oxygen Flux
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_o2 to outputs without", &
"base biotic tracers and lflux_gas_o2"
this%registered_outputs(ofg_ind_loc)%err_message = "requires base biotic tracers and lflux_gas_o2"

! Carbon Dioxide Flux
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"
this%registered_outputs(ofg_ind_loc)%err_message = "requires base biotic tracers and lflux_gas_co2"

! NHx Surface Emissions
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"
this%registered_outputs(ofg_ind_loc)%err_message = "requires base biotic tracers and lcompute_nhx_surface_emis"

! Surface Chlorophyll
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"
this%registered_outputs(ofg_ind_loc)%err_message = "requires base biotic tracers"

! Full Depth Chlorophyll
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"
this%registered_outputs(ofg_ind_loc)%err_message = "requires base biotic tracers"

end subroutine create_registry

Expand Down
2 changes: 1 addition & 1 deletion src/marbl_settings_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2243,7 +2243,7 @@ subroutine set_unit_system(this, unit_system, marbl_status_log)
character(len=*), intent(in) :: unit_system
type(marbl_log_type), intent(inout) :: marbl_status_log

character(len=*), parameter :: subname = 'marbl_interface_private_types:set_unit_system'
character(len=*), parameter :: subname = 'marbl_settings_mod:set_unit_system'
character(len=char_len) :: log_message

! If requested unit system is same as current unit system, just return
Expand Down
10 changes: 4 additions & 6 deletions tests/driver_src/marbl_call_compute_subroutines_drv.F90
Original file line number Diff line number Diff line change
Expand Up @@ -349,12 +349,10 @@ 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(:,:)
if (base_bio_on) then
do output_id = 1, marbl_instances(n)%interior_tendency_output%size()
interior_tendency_output(:,col_id, output_id) = &
marbl_instances(n)%interior_tendency_output%outputs_for_GCM(output_id)%forcing_field_1d(1,:)
end do
end if
do output_id = 1, marbl_instances(n)%interior_tendency_output%size()
interior_tendency_output(:,col_id, output_id) = &
marbl_instances(n)%interior_tendency_output%outputs_for_GCM(output_id)%forcing_field_1d(1,:)
end do
end do ! column
end do ! instance

Expand Down

0 comments on commit 89cf5b9

Please sign in to comment.