Skip to content
Closed
Show file tree
Hide file tree
Changes from 1 commit
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
104 changes: 52 additions & 52 deletions src/common/m_boundary_common.fpp

Large diffs are not rendered by default.

8 changes: 4 additions & 4 deletions src/common/m_chemistry.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ contains
! conservative variables.

type(scalar_field), intent(inout) :: q_T_sf
type(scalar_field), dimension(eqn_idx%sys_size), intent(in) :: q_cons_vf
type(scalar_field), dimension(sys_size), intent(in) :: q_cons_vf
type(int_bounds_info), dimension(1:3), intent(in) :: bounds

integer :: x, y, z, eqn
Expand Down Expand Up @@ -62,7 +62,7 @@ contains
subroutine s_compute_T_from_primitives(q_T_sf, q_prim_vf, bounds)

type(scalar_field), intent(inout) :: q_T_sf
type(scalar_field), dimension(eqn_idx%sys_size), intent(in) :: q_prim_vf
type(scalar_field), dimension(sys_size), intent(in) :: q_prim_vf
type(int_bounds_info), dimension(1:3), intent(in) :: bounds

integer :: x, y, z, i
Expand All @@ -87,9 +87,9 @@ contains

subroutine s_compute_chemistry_reaction_flux(rhs_vf, q_cons_qp, q_T_sf, q_prim_qp, bounds)

type(scalar_field), dimension(eqn_idx%sys_size), intent(inout) :: rhs_vf
type(scalar_field), dimension(sys_size), intent(inout) :: rhs_vf
type(scalar_field), intent(inout) :: q_T_sf
type(scalar_field), dimension(eqn_idx%sys_size), intent(inout) :: q_cons_qp, q_prim_qp
type(scalar_field), dimension(sys_size), intent(inout) :: q_cons_qp, q_prim_qp
type(int_bounds_info), dimension(1:3), intent(in) :: bounds

integer :: x, y, z
Expand Down
62 changes: 31 additions & 31 deletions src/common/m_derived_types.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -108,37 +108,6 @@ module m_derived_types

end type int_bounds_info

!> @name Annotations of the structure of the state and flux vectors in terms of the
!! size and the configuration of the system of equations to which they belong
!> @{
type system_of_equations
integer :: eqn_idx%sys_size !< Number of unknowns in system of eqns.
type(int_bounds_info) :: cont !< Indexes of first & last continuity eqns.
type(int_bounds_info) :: mom !< Indexes of first & last momentum eqns.
integer :: E !< Index of energy equation
integer :: n !< Index of number density
type(int_bounds_info) :: adv !< Indexes of first & last advection eqns.
type(int_bounds_info) :: internalEnergies !< Indexes of first & last internal energy eqns.
type(bub_bounds_info) :: bub !< Indexes of first & last bubble variable eqns.
integer :: alf !< Index of void fraction
integer :: gamma !< Index of specific heat ratio func. eqn.
integer :: pi_inf !< Index of liquid stiffness func. eqn.
type(int_bounds_info) :: B !< Indexes of first and last magnetic field eqns.
type(int_bounds_info) :: stress !< Indexes of first and last shear stress eqns.
type(int_bounds_info) :: xi !< Indexes of first and last reference map eqns.
integer :: eqn_idx%b_size !< Number of elements in the symmetric b tensor, plus one
integer :: eqn_idx%tensor_size !< Number of elements in the full tensor plus one
type(int_bounds_info) :: species !< Indexes of first & last concentration eqns.
integer :: c !< Index of color function
integer :: damage !< Index of damage state variable (D) for continuum damage model
integer, dimension(3) :: dir
real(wp), dimension(3) :: dir_flg
integer, dimension(3) :: dir_tau !!used for hypoelasticity=true
integer, dimension(2) :: Re_size
integer, allocatable, dimension(:, :) :: Re
end type system_of_equations
!> @}

type bc_patch_parameters
integer :: geometry
integer :: type
Expand Down Expand Up @@ -166,6 +135,37 @@ module m_derived_types
integer, dimension(:, :), allocatable :: moms !< Moment indices for qbmm
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Interestingly, this derived type appears never to be used. git blame says I added it years ago.

integer, dimension(:, :, :), allocatable :: fullmom !< Moment indices for qbmm
end type bub_bounds_info


!> @name Annotations of the structure of the state and flux vectors in terms of the
!! size and the configuration of the system of equations to which they belong
!> @{
type system_of_equations
type(int_bounds_info) :: cont !< Indexes of first & last continuity eqns.
type(int_bounds_info) :: mom !< Indexes of first & last momentum eqns.
integer :: E !< Index of energy equation
integer :: n !< Index of number density
type(int_bounds_info) :: adv !< Indexes of first & last advection eqns.
type(int_bounds_info) :: internalEnergies !< Indexes of first & last internal energy eqns.
type(bub_bounds_info) :: bub !< Indexes of first & last bubble variable eqns.
integer :: alf !< Index of void fraction
integer :: gamma !< Index of specific heat ratio func. eqn.
integer :: pi_inf !< Index of liquid stiffness func. eqn.
type(int_bounds_info) :: B !< Indexes of first and last magnetic field eqns.
type(int_bounds_info) :: stress !< Indexes of first and last shear stress eqns.
type(int_bounds_info) :: xi !< Indexes of first and last reference map eqns.
integer :: b_size !< Number of elements in the symmetric b tensor, plus one
integer :: tensor_size !< Number of elements in the full tensor plus one
type(int_bounds_info) :: species !< Indexes of first & last concentration eqns.
integer :: c !< Index of color function
integer :: damage !< Index of damage state variable (D) for continuum damage model
integer, dimension(3) :: dir
real(wp), dimension(3) :: dir_flg
integer, dimension(3) :: dir_tau !!used for hypoelasticity=true
integer, dimension(2) :: Re_size
integer, allocatable, dimension(:, :) :: Re
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

you may need to be careful with this on GPU cases (especially Frontier/Cray). i forget exactly how we deal with cases where we have an allocatable in a derived type but i would look for other examples of the code that do this. also, isn't Re a real and not an integer? and why is its size unknown at compile time?

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I kinda omitted _idx from all variables listed. It was Re_idx and I just copied the declaration into under system_of_equations type.

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

yep this works

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

have a look at

type(source_spatial_type), dimension(:), allocatable :: source_spatials !< Data of non-zero source grid points for each source
to see how derived types that have allocatables in them are handled. that said, you only have one allocatable in the type. i suggest removing it and "putting back" the old Re_idx. this should make life much simpler as a stepping stone. notice that basically all of the other types that are used do not have allocatables in them. they require special treatment.

end type system_of_equations
!> @}

!> Defines parameters for a Model Patch
type ic_model_parameters
Expand Down
Loading