Skip to content

Commit

Permalink
Move array dims inside autotroph_local
Browse files Browse the repository at this point in the history
Added a constructor to the type to allocate memory, and also moved the
local variable from marbl_interior_tendency_compute() to
marbl_interface_class. Similar to 69384dd and e2ff90a.
  • Loading branch information
mnlevy1981 committed Sep 6, 2018
1 parent e2ff90a commit 5105a79
Show file tree
Hide file tree
Showing 6 changed files with 147 additions and 86 deletions.
36 changes: 19 additions & 17 deletions src/marbl_ciso_interior_tendency_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,13 +19,13 @@ module marbl_ciso_interior_tendency_mod
use marbl_interface_public_types, only : marbl_diagnostics_type
use marbl_interface_public_types, only : marbl_domain_type

use marbl_interface_private_types, only : autotroph_local_type
use marbl_interface_private_types, only : column_sinking_particle_type
use marbl_interface_private_types, only : marbl_interior_tendency_share_type
use marbl_interface_private_types, only : marbl_particulate_share_type
use marbl_interface_private_types, only : marbl_tracer_index_type
use marbl_interface_private_types, only : autotroph_secondary_species_type

use marbl_pft_mod, only : autotroph_local_type
use marbl_pft_mod, only : marbl_zooplankton_share_type

implicit none
Expand Down Expand Up @@ -76,7 +76,7 @@ subroutine marbl_ciso_interior_tendency_compute( &
type(marbl_zooplankton_share_type), intent(in) :: marbl_zooplankton_share(:)
type(marbl_particulate_share_type), intent(in) :: marbl_particulate_share
real (r8), intent(in) :: tracer_local(:,:)
type(autotroph_local_type), intent(in) :: autotroph_local(:,:)
type(autotroph_local_type), intent(in) :: autotroph_local
type(autotroph_secondary_species_type), intent(in) :: autotroph_secondary_species
real (r8), intent(in) :: temperature(:)
type(marbl_tracer_index_type), intent(in) :: marbl_tracer_indices
Expand Down Expand Up @@ -303,18 +303,18 @@ subroutine marbl_ciso_interior_tendency_compute( &
end if

do auto_ind = 1, autotroph_cnt
if (autotroph_local(auto_ind,k)%C > c0) then
R13C_autotroph(auto_ind,k) = autotroph_local(auto_ind,k)%C13 / autotroph_local(auto_ind,k)%C
R14C_autotroph(auto_ind,k) = autotroph_local(auto_ind,k)%C14 / autotroph_local(auto_ind,k)%C
if (autotroph_local%C(auto_ind,k) > c0) then
R13C_autotroph(auto_ind,k) = autotroph_local%C13(auto_ind,k) / autotroph_local%C(auto_ind,k)
R14C_autotroph(auto_ind,k) = autotroph_local%C14(auto_ind,k) / autotroph_local%C(auto_ind,k)
else
R13C_autotroph(auto_ind,k) = c0
R14C_autotroph(auto_ind,k) = c0
end if

if (marbl_tracer_indices%auto_inds(auto_ind)%CaCO3_ind > 0) then
if (autotroph_local(auto_ind,k)%CaCO3 > c0) then
R13C_autotrophCaCO3(auto_ind,k) = autotroph_local(auto_ind,k)%Ca13CO3 / autotroph_local(auto_ind,k)%CaCO3
R14C_autotrophCaCO3(auto_ind,k) = autotroph_local(auto_ind,k)%Ca14CO3 / autotroph_local(auto_ind,k)%CaCO3
if (autotroph_local%CaCO3(auto_ind,k) > c0) then
R13C_autotrophCaCO3(auto_ind,k) = autotroph_local%Ca13CO3(auto_ind,k) / autotroph_local%CaCO3(auto_ind,k)
R14C_autotrophCaCO3(auto_ind,k) = autotroph_local%Ca14CO3(auto_ind,k) / autotroph_local%CaCO3(auto_ind,k)
else
R13C_autotrophCaCO3(auto_ind,k) = c0
R14C_autotrophCaCO3(auto_ind,k) = c0
Expand Down Expand Up @@ -579,9 +579,9 @@ subroutine marbl_ciso_interior_tendency_compute( &

n = marbl_tracer_indices%auto_inds(auto_ind)%C14_ind
interior_tendencies(n,k) = photo14C(auto_ind,k) - work1 * R14C_autotroph(auto_ind,k) - &
c14_lambda_inv_sec * autotroph_local(auto_ind,k)%C14
c14_lambda_inv_sec * autotroph_local%C14(auto_ind,k)

decay_14Ctot(k) = decay_14Ctot(k) + c14_lambda_inv_sec * autotroph_local(auto_ind,k)%C14
decay_14Ctot(k) = decay_14Ctot(k) + c14_lambda_inv_sec * autotroph_local%C14(auto_ind,k)

n = marbl_tracer_indices%auto_inds(auto_ind)%Ca13CO3_ind
if (n > 0) then
Expand All @@ -593,9 +593,9 @@ subroutine marbl_ciso_interior_tendency_compute( &
if (n > 0) then
interior_tendencies(n,k) = Ca14CO3_PROD(auto_ind,k) - QCaCO3(auto_ind,k) &
* work1 * R14C_autotrophCaCO3(auto_ind,k) &
- c14_lambda_inv_sec * autotroph_local(auto_ind,k)%Ca14CO3
- c14_lambda_inv_sec * autotroph_local%Ca14CO3(auto_ind,k)

decay_14Ctot(k) = decay_14Ctot(k) + c14_lambda_inv_sec * autotroph_local(auto_ind,k)%Ca14CO3
decay_14Ctot(k) = decay_14Ctot(k) + c14_lambda_inv_sec * autotroph_local%Ca14CO3(auto_ind,k)
endif
end do

Expand Down Expand Up @@ -730,23 +730,25 @@ end subroutine marbl_ciso_interior_tendency_compute

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

subroutine marbl_ciso_interior_tendency_autotroph_set_to_zero(autotroph_tracer_indices, autotroph_local)
subroutine marbl_ciso_interior_tendency_autotroph_set_to_zero(autotroph_tracer_indices, auto_ind, k, autotroph_local)

use marbl_interface_private_types, only : marbl_living_tracer_index_type

type(marbl_living_tracer_index_type), intent(in) :: autotroph_tracer_indices
integer, intent(in) :: auto_ind
integer, intent(in) :: k
type(autotroph_local_type), intent(inout) :: autotroph_local

if (.not. ciso_on) return

autotroph_local%C13 = c0
autotroph_local%C14 = c0
autotroph_local%C13(auto_ind,k) = c0
autotroph_local%C14(auto_ind,k) = c0

if (autotroph_tracer_indices%Ca13CO3_ind > 0) then
autotroph_local%Ca13CO3 = c0
autotroph_local%Ca13CO3(auto_ind,k) = c0
end if
if (autotroph_tracer_indices%Ca14CO3_ind > 0) then
autotroph_local%Ca14CO3 = c0
autotroph_local%Ca14CO3(auto_ind,k) = c0
end if

end subroutine marbl_ciso_interior_tendency_autotroph_set_to_zero
Expand Down
9 changes: 4 additions & 5 deletions src/marbl_diagnostics_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ module marbl_diagnostics_mod
use marbl_interface_private_types, only : dissolved_organic_matter_type
use marbl_interface_private_types, only : column_sinking_particle_type
use marbl_interface_private_types, only : marbl_PAR_type
use marbl_interface_private_types, only : autotroph_local_type
use marbl_interface_private_types, only : autotroph_secondary_species_type
use marbl_interface_private_types, only : zooplankton_secondary_species_type
use marbl_interface_private_types, only : marbl_particulate_share_type
Expand All @@ -31,8 +32,6 @@ module marbl_diagnostics_mod
use marbl_interface_public_types, only : marbl_saved_state_type
use marbl_interface_public_types, only : marbl_diagnostics_type

use marbl_pft_mod, only : autotroph_local_type

use marbl_logging, only : marbl_log_type
use marbl_logging, only : marbl_logging_add_diagnostics_error

Expand Down Expand Up @@ -2988,7 +2987,7 @@ subroutine marbl_diagnostics_interior_tendency_compute ( &

type(marbl_tracer_index_type) , intent(in) :: marbl_tracer_indices
type (carbonate_type) , intent(in) :: carbonate(domain%km)
type (autotroph_local_type) , intent(in) :: autotroph_local(autotroph_cnt, domain%km)
type (autotroph_local_type) , intent(in) :: autotroph_local
type (autotroph_secondary_species_type) , intent(in) :: autotroph_secondary_species
type (zooplankton_secondary_species_type) , intent(in) :: zooplankton_secondary_species
type (dissolved_organic_matter_type) , intent(in) :: dissolved_organic_matter(domain%km)
Expand Down Expand Up @@ -3414,7 +3413,7 @@ subroutine store_diagnostics_autotrophs(marbl_domain, &
autotroph_local, autotroph_secondary_species, marbl_interior_diags)

type(marbl_domain_type) , intent(in) :: marbl_domain
type(autotroph_local_type) , intent(in) :: autotroph_local(:,:) ! autotroph_cnt, km
type(autotroph_local_type) , intent(in) :: autotroph_local
type(autotroph_secondary_species_type) , intent(in) :: autotroph_secondary_species
type(marbl_diagnostics_type) , intent(inout) :: marbl_interior_diags

Expand Down Expand Up @@ -3448,7 +3447,7 @@ subroutine store_diagnostics_autotrophs(marbl_domain, &

do n = 1, autotroph_cnt
! compute biomass weighted average of limitation terms over 0..100m
autotrophC_weight(:) = autotroph_local(n,:)%C
autotrophC_weight(:) = autotroph_local%C(n,:)
call marbl_diagnostics_share_compute_vertical_integrals(autotrophC_weight, delta_z, kmt, &
near_surface_integral=autotrophC_zint_100m)

Expand Down
6 changes: 6 additions & 0 deletions src/marbl_interface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module marbl_interface
use marbl_interface_private_types, only : marbl_interior_tendency_saved_state_indexing_type
use marbl_interface_private_types, only : marbl_PAR_type
use marbl_interface_private_types, only : autotroph_secondary_species_type
use marbl_interface_private_types, only : autotroph_local_type
use marbl_interface_private_types, only : zooplankton_secondary_species_type
use marbl_interface_private_types, only : marbl_particulate_share_type
use marbl_interface_private_types, only : marbl_surface_flux_share_type
Expand Down Expand Up @@ -108,6 +109,7 @@ module marbl_interface
! private data
type(marbl_PAR_type), private :: PAR
type(autotroph_secondary_species_type), private :: autotroph_secondary_species
type(autotroph_local_type), private :: autotroph_local
type(zooplankton_secondary_species_type), private :: zooplankton_secondary_species
type(marbl_particulate_share_type), private :: particulate_share
type(marbl_surface_flux_share_type), private :: surface_flux_share
Expand Down Expand Up @@ -188,6 +190,7 @@ subroutine init(this, &
use marbl_settings_mod, only : marbl_settings_set_all_derived
use marbl_settings_mod, only : marbl_settings_consistency_check
use marbl_settings_mod, only : autotroph_cnt
use marbl_settings_mod, only : ciso_on
use marbl_diagnostics_mod, only : marbl_diagnostics_init
use marbl_saved_state_mod, only : marbl_saved_state_init

Expand Down Expand Up @@ -265,6 +268,7 @@ subroutine init(this, &

call this%PAR%construct(num_levels, num_PAR_subcols)
call this%autotroph_secondary_species%construct(autotroph_cnt, num_levels)
call this%autotroph_local%construct(ciso_on, autotroph_cnt, num_levels)
call this%zooplankton_secondary_species%construct(zooplankton_cnt, num_levels)

!-----------------------------------------------------------------------
Expand Down Expand Up @@ -855,6 +859,7 @@ subroutine interior_tendency_compute(this)
marbl_timer_indices = this%timer_ids, &
PAR = this%PAR, &
autotroph_secondary_species = this%autotroph_secondary_species, &
autotroph_local = this%autotroph_local, &
zooplankton_secondary_species = this%zooplankton_secondary_species, &
saved_state = this%interior_tendency_saved_state, &
marbl_timers = this%timers, &
Expand Down Expand Up @@ -1006,6 +1011,7 @@ subroutine shutdown(this)
call this%particulate_share%destruct()
call this%PAR%destruct()
call this%autotroph_secondary_species%destruct()
call this%autotroph_local%destruct()
call this%zooplankton_secondary_species%destruct()
call this%domain%destruct()

Expand Down
66 changes: 66 additions & 0 deletions src/marbl_interface_private_types.F90
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,24 @@ module marbl_interface_private_types
procedure, public :: destruct => autotroph_secondary_species_destructor
end type autotroph_secondary_species_type

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

type, public :: autotroph_local_type
real(r8), allocatable :: Chl(:,:) ! local copy of model autotroph Chl
real(r8), allocatable :: C(:,:) ! local copy of model autotroph C
real(r8), allocatable :: P(:,:) ! local copy of model autotroph P
real(r8), allocatable :: Fe(:,:) ! local copy of model autotroph Fe
real(r8), allocatable :: Si(:,:) ! local copy of model autotroph Si
real(r8), allocatable :: CaCO3(:,:) ! local copy of model autotroph CaCO3
real(r8), allocatable :: C13(:,:) ! local copy of model autotroph C13
real(r8), allocatable :: C14(:,:) ! local copy of model autotroph C14
real(r8), allocatable :: Ca13CO3(:,:) ! local copy of model autotroph Ca13CO3
real(r8), allocatable :: Ca14CO3(:,:) ! local copy of model autotroph Ca14CO3
contains
procedure, public :: construct => autotroph_local_constructor
procedure, public :: destruct => autotroph_local_destructor
end type autotroph_local_type

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

type, public :: zooplankton_secondary_species_type
Expand Down Expand Up @@ -967,6 +985,54 @@ end subroutine autotroph_secondary_species_destructor

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

subroutine autotroph_local_constructor(self, ciso_on, autotroph_cnt, km)

class(autotroph_local_type), intent(inout) :: self
logical, intent(in) :: ciso_on
integer, intent(in) :: autotroph_cnt
integer, intent(in) :: km

allocate(self%Chl(autotroph_cnt, km))
allocate(self%C(autotroph_cnt, km))
allocate(self%P(autotroph_cnt, km))
allocate(self%Fe(autotroph_cnt, km))
allocate(self%Si(autotroph_cnt, km))
allocate(self%CaCO3(autotroph_cnt, km))
if (ciso_on) then
allocate(self%C13(autotroph_cnt, km))
allocate(self%C14(autotroph_cnt, km))
allocate(self%Ca13CO3(autotroph_cnt, km))
allocate(self%Ca14CO3(autotroph_cnt, km))
else
allocate(self%C13(0,0))
allocate(self%C14(0,0))
allocate(self%Ca13CO3(0,0))
allocate(self%Ca14CO3(0,0))
end if

end subroutine autotroph_local_constructor

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

subroutine autotroph_local_destructor(self)

class(autotroph_local_type), intent(inout) :: self

deallocate(self%Chl)
deallocate(self%C)
deallocate(self%P)
deallocate(self%Fe)
deallocate(self%Si)
deallocate(self%CaCO3)
deallocate(self%C13)
deallocate(self%C14)
deallocate(self%Ca13CO3)
deallocate(self%Ca14CO3)

end subroutine autotroph_local_destructor

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

subroutine zooplankton_secondary_species_constructor(self, zooplankton_cnt, km)

class(zooplankton_secondary_species_type), intent(inout) :: self
Expand Down
Loading

0 comments on commit 5105a79

Please sign in to comment.