Skip to content

Commit

Permalink
Merge pull request #14 from apes-suite/feature/identify_relaxation_op…
Browse files Browse the repository at this point in the history
…tions

Feature/identify relaxation options
  • Loading branch information
KannanMasilamani authored May 7, 2024
2 parents 98ba48e + 1fd4e21 commit f482be1
Show file tree
Hide file tree
Showing 38 changed files with 1,066 additions and 722 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,10 @@ physics = {
identify = {
label = '2D',
layout = 'd2q9', -- Stencil
relaxation = 'mrt_generic', -- Collision
relaxation = {
name = 'mrt', -- Collision
variant = 'standard_no_opt', -- a variant of collision
},
kind = 'fluid' -- Physics
}
--! [Scheme identifier]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -166,7 +166,10 @@ physics = {
identify = {
label = '2D',
layout = 'd2q9', -- Stencil
relaxation = 'bgk_improved', -- Collision
relaxation = {
name = 'bgk', -- Collision
variant = 'improved', -- a variant of collision
},
kind = 'fluid' -- Physics
}
--! [Scheme identifier]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -165,7 +165,10 @@ physics = {
identify = {
label = '2D',
layout = 'd2q9', -- Stencil
relaxation = 'bgk_improved', -- Collision
relaxation = {
name = 'bgk', -- Collision
variant = 'improved', -- a variant of collision
},
kind = 'fluid' -- Physics
}
--! [Scheme identifier]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -165,7 +165,10 @@ physics = {
identify = {
label = '2D',
layout = 'd2q9', -- Stencil
relaxation = 'bgk_improved', -- Collision
relaxation = {
name = 'bgk', -- Collision
variant = 'improved', -- a variant of collision
},
kind = 'fluid' -- Physics
}
--! [Scheme identifier]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -166,7 +166,10 @@ physics = {
identify = {
label = '2D',
layout = 'd2q9', -- Stencil
relaxation = 'bgk_improved', -- Collision
relaxation = {
name = 'bgk', -- Collision
variant = 'improved', -- a variant of collision
},
kind = 'fluid' -- Physics
}
--! [Scheme identifier]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -166,7 +166,10 @@ physics = {
identify = {
label = '2D',
layout = 'd2q9', -- Stencil
relaxation = 'bgk_improved', -- Collision
relaxation = {
name = 'bgk', -- Collision
variant = 'improved', -- a variant of collision
},
kind = 'fluid' -- Physics
}
--! [Scheme identifier]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -106,7 +106,10 @@ physics = {
--! [Scheme identifier]
identify = {
kind = 'fluid', -- Physics
relaxation = 'bgk_improved', -- Collision
relaxation = {
name = 'bgk', -- Collision
variant = 'improved', -- a variant of collision
},
layout = 'd3q27' -- Stencil
}
--! [Scheme identifier]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -147,7 +147,10 @@ physics = {
identify = {
label = '3D',
layout = 'd3q19', -- Stencil
relaxation = 'bgk_generic', -- Collision
relaxation = {
name = 'bgk', -- Collision
variant = 'standard_no_opt', -- a variant of collision
},
kind = 'fluid_incompressible' -- Physics
}
--! [Scheme identifier]
Expand Down
12 changes: 6 additions & 6 deletions musubi.lua
Original file line number Diff line number Diff line change
Expand Up @@ -140,12 +140,12 @@ debug = {

-- scheme model for single fluid simulation
identify = {
kind = 'fluid', -- simulation type of this scheme
-- ( fluid, fluid_incomp, passive_scalar, ...)
relaxation = 'bgk', -- relaxation type (bgk, mrt, ...)
-- Scheme layout
-- This describes the stencil to use in the simulation.
layout = 'd3q19'
kind = 'fluid', -- simulation type of this scheme
-- ( fluid, fluid_incomp, passive_scalar, ...)
relaxation = 'bgk', -- relaxation type (bgk, mrt, ...)
-- Scheme layout
-- This describes the stencil to use in the simulation.
layout = 'd3q19'
}

-- field which defines fluid or species
Expand Down
11 changes: 6 additions & 5 deletions source/compute/mus_compute_bgk_module.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ module mus_bgk_module

private

public :: bgk_advRel_generic
public :: mus_advRel_kCFD_rBGK_vStdNoOpt_l
public :: bgk_advRel_flekkoy
public :: bgk_advRel_flekkoy_noFluid

Expand Down Expand Up @@ -256,9 +256,10 @@ contains
!! This subroutine interface must match the abstract interface definition
!! [[kernel]] in scheme/[[mus_scheme_type_module]].f90 in order to be callable
!! via [[mus_scheme_type:compute]] function pointer.
subroutine bgk_advRel_generic( fieldProp, inState, outState, auxField, &
& neigh, nElems, nSolve, level, layout, &
& params, varSys, derVarPos )
subroutine mus_advRel_kCFD_rBGK_vStdNoOpt_l( fieldProp, inState, outState, &
& auxField, neigh, nElems, nSolve,&
& level, layout, params, varSys, &
& derVarPos )
! -------------------------------------------------------------------- !
!> Array of field properties (fluid or species)
type(mus_field_prop_type), intent(in) :: fieldProp(:)
Expand Down Expand Up @@ -337,7 +338,7 @@ contains

end do nodeloop

end subroutine bgk_advRel_generic
end subroutine mus_advRel_kCFD_rBGK_vStdNoOpt_l
! ****************************************************************************** !

end module mus_bgk_module
Expand Down
58 changes: 33 additions & 25 deletions source/compute/mus_compute_d2q9_module.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -70,11 +70,11 @@ module mus_d2q9_module

private

public :: bgk_improved_advRel_d2q9
public :: bgk_advRel_d2q9
public :: mrt_advRel_d2q9
public :: mrt_advRel_d2q9_incomp
public :: bgk_advRel_d2q9_incomp
public :: mus_advRel_kFluid_rBGK_vImproved_lD2Q9
public :: mus_advRel_kFluid_rBGK_vStd_lD2Q9
public :: mus_advRel_kFluid_rMRT_vStd_lD2Q9
public :: mus_advRel_kFluidIncomp_rMRT_vStd_lD2Q9
public :: mus_advRel_kFluidIncomp_rBGK_vStd_lD2Q9
public :: bgk_Regularized_d2q9
public :: bgk_RecursiveRegularized_d2q9
public :: bgk_HybridRecursiveRegularized_d2q9
Expand Down Expand Up @@ -103,9 +103,11 @@ contains
!! This subroutine interface must match the abstract interface definition
!! [[kernel]] in scheme/[[mus_scheme_type_module]].f90 in order to be callable
!! via [[mus_scheme_type;compute]] function pointer.
subroutine bgk_improved_advRel_d2q9( fieldProp, inState, outState, auxField, &
& neigh, nElems, nSolve, level, layout, &
& params, varSys, derVarPos )
subroutine mus_advRel_kFluid_rBGK_vImproved_lD2Q9( fieldProp, inState, &
& outState, auxField, neigh,&
& nElems, nSolve, level, &
& layout, params, varSys, &
& derVarPos )
! -------------------------------------------------------------------- !
!> Array of field properties (fluid or species)
type(mus_field_prop_type), intent(in) :: fieldProp(:)
Expand Down Expand Up @@ -231,7 +233,7 @@ contains
end do nodeloop
!$omp end do nowait

end subroutine bgk_improved_advRel_d2q9
end subroutine mus_advRel_kFluid_rBGK_vImproved_lD2Q9
! **************************************************************************** !

! **************************************************************************** !
Expand All @@ -242,9 +244,10 @@ contains
!! This subroutine interface must match the abstract interface definition
!! [[kernel]] in scheme/[[mus_scheme_type_module]].f90 in order to be callable
!! via [[mus_scheme_type:compute]] function pointer.
subroutine bgk_advRel_d2q9( fieldProp, inState, outState, auxField, &
& neigh, nElems, nSolve, level, layout, &
& params, varSys, derVarPos )
subroutine mus_advRel_kFluid_rBGK_vStd_lD2Q9( fieldProp, inState, outState, &
& auxField, neigh, nElems, &
& nSolve, level, layout, params,&
& varSys, derVarPos )
! -------------------------------------------------------------------- !
!> Array of field properties (fluid or species)
type(mus_field_prop_type), intent(in) :: fieldProp(:)
Expand Down Expand Up @@ -390,7 +393,7 @@ contains
end do nodeloop
!$omp end do nowait

end subroutine bgk_advRel_d2q9
end subroutine mus_advRel_kFluid_rBGK_vStd_lD2Q9
! **************************************************************************** !

! **************************************************************************** !
Expand All @@ -400,9 +403,10 @@ contains
!! This subroutine interface must match the abstract interface definition
!! [[kernel]] in scheme/[[mus_scheme_type_module]].f90 in order to be callable
!! via [[mus_scheme_type:compute]] function pointer.
subroutine mrt_advRel_d2q9( fieldProp, inState, outState, auxField, &
& neigh, nElems, nSolve, level, layout, &
& params, varSys, derVarPos )
subroutine mus_advRel_kFluid_rMRT_vStd_lD2Q9( fieldProp, inState, outState, &
& auxField, neigh, nElems, &
& nSolve, level, layout, params,&
& varSys, derVarPos )
! -------------------------------------------------------------------- !
!> Array of field properties (fluid or species)
type(mus_field_prop_type), intent(in) :: fieldProp(:)
Expand Down Expand Up @@ -546,7 +550,7 @@ contains
enddo nodeloop
!$omp end do nowait

end subroutine mrt_advRel_d2q9
end subroutine mus_advRel_kFluid_rMRT_vStd_lD2Q9
! **************************************************************************** !

! **************************************************************************** !
Expand All @@ -556,9 +560,11 @@ contains
!! This subroutine interface must match the abstract interface definition
!! [[kernel]] in scheme/[[mus_scheme_type_module]].f90 in order to be callable
!! via [[mus_scheme_type:compute]] function pointer.
subroutine mrt_advRel_d2q9_incomp( fieldProp, inState, outState, auxField, &
& neigh, nElems, nSolve, level, layout, &
& params, varSys, derVarPos )
subroutine mus_advRel_kFluidIncomp_rMRT_vStd_lD2Q9( fieldProp, inState, &
& outState, auxField, &
& neigh, nElems, nSolve, &
& level, layout, params, &
& varSys, derVarPos )
! -------------------------------------------------------------------- !
!> Array of field properties (fluid or species)
type(mus_field_prop_type), intent(in) :: fieldProp(:)
Expand Down Expand Up @@ -701,7 +707,7 @@ contains
enddo nodeloop
!$omp end do nowait

end subroutine mrt_advRel_d2q9_incomp
end subroutine mus_advRel_kFluidIncomp_rMRT_vStd_lD2Q9
! **************************************************************************** !

! **************************************************************************** !
Expand All @@ -712,9 +718,11 @@ contains
!! This subroutine interface must match the abstract interface definition
!! [[kernel]] in scheme/[[mus_scheme_type_module]].f90 in order to be callable
!! via [[mus_scheme_type:compute]] function pointer.
subroutine bgk_advRel_d2q9_incomp( fieldProp, inState, outState, auxField, &
& neigh, nElems, nSolve, level, layout, &
& params, varSys, derVarPos )
subroutine mus_advRel_kFluidIncomp_rBGK_vStd_lD2Q9( fieldProp, inState, &
& outState, auxField, &
& neigh, nElems, nSolve, &
& level, layout, params, &
& varSys, derVarPos )
! -------------------------------------------------------------------- !
!> Array of field properties (fluid or species)
type(mus_field_prop_type), intent(in) :: fieldProp(:)
Expand Down Expand Up @@ -827,7 +835,7 @@ contains
end do nodeloop
!$omp end do nowait

end subroutine bgk_advRel_d2q9_incomp
end subroutine mus_advRel_kFluidIncomp_rBGK_vStd_lD2Q9
! **************************************************************************** !

! ****************************************************************************** !
Expand Down
Loading

0 comments on commit f482be1

Please sign in to comment.