51 character(len=25) :: EULER_KNOWN_BCS(7) = [character(len=25) :: &
67 module subroutine density_bc_factory(object, scheme, json, coef, user)
68 class(bc_t),
pointer,
intent(inout) :: object
69 type(fluid_scheme_compressible_euler_t),
intent(in) :: scheme
70 type(json_file),
intent(inout) :: json
71 type(coef_t),
intent(in) :: coef
72 type(user_t),
intent(in) :: user
73 character(len=:),
allocatable :: type
75 integer,
allocatable :: zone_indices(:)
77 call json_get(json,
"type", type)
79 select case (trim(type))
80 case (
"density_value")
83 do i = 1,
size(euler_known_bcs)
84 if (trim(type) .eq. trim(euler_known_bcs(i)))
return
90 call json_get(json,
"zone_indices", zone_indices)
91 call object%init(coef, json)
93 do i = 1,
size(zone_indices)
94 call object%mark_zone(coef%msh%labeled_zones(zone_indices(i)))
96 call object%finalize()
97 end subroutine density_bc_factory
105 module subroutine pressure_bc_factory(object, scheme, json, coef, user)
106 class(bc_t),
pointer,
intent(inout) :: object
107 type(fluid_scheme_compressible_euler_t),
intent(in) :: scheme
108 type(json_file),
intent(inout) :: json
109 type(coef_t),
intent(in) :: coef
110 type(user_t),
intent(in) :: user
111 character(len=:),
allocatable :: type
113 integer,
allocatable :: zone_indices(:)
115 call json_get(json,
"type", type)
117 select case (trim(type))
118 case (
"outflow",
"normal_outflow")
119 allocate(zero_dirichlet_t::object)
120 case (
"pressure_value")
123 do i = 1,
size(euler_known_bcs)
124 if (trim(type) .eq. trim(euler_known_bcs(i)))
return
130 call json_get(json,
"zone_indices", zone_indices)
131 call object%init(coef, json)
133 do i = 1,
size(zone_indices)
134 call object%mark_zone(coef%msh%labeled_zones(zone_indices(i)))
136 call object%finalize()
140 do i = 1,
size(zone_indices)
141 do j = 1, scheme%msh%nelv
142 do k = 1, 2 * scheme%msh%gdim
143 if (scheme%msh%facet_type(k,j) .eq. -zone_indices(i))
then
144 scheme%msh%facet_type(k, j) = 1
149 end subroutine pressure_bc_factory
157 module subroutine velocity_bc_factory(object, scheme, json, coef, user)
158 class(bc_t),
pointer,
intent(inout) :: object
159 type(fluid_scheme_compressible_euler_t),
intent(in) :: scheme
160 type(json_file),
intent(inout) :: json
161 type(coef_t),
intent(in) :: coef
162 type(user_t),
intent(in) :: user
163 character(len=:),
allocatable :: type
165 integer,
allocatable :: zone_indices(:)
167 call json_get(json,
"type", type)
169 select case (trim(type))
173 allocate(zero_dirichlet_t::object)
174 case (
"velocity_value")
177 do i = 1,
size(euler_known_bcs)
178 if (trim(type) .eq. trim(euler_known_bcs(i)))
return
184 call json_get(json,
"zone_indices", zone_indices)
185 call object%init(coef, json)
186 do i = 1,
size(zone_indices)
187 call object%mark_zone(coef%msh%labeled_zones(zone_indices(i)))
189 call object%finalize()
191 end subroutine velocity_bc_factory
193end submodule euler_bc_fctry
Abstract interface defining a user defined inflow condition (pointwise)
Defines a Blasius profile dirichlet condition.
Defines a dirichlet boundary condition.
Defines a dong outflow condition.
Defines inflow dirichlet conditions.
Defines user dirichlet condition for a scalar field.
Defines inflow dirichlet conditions.
Dirichlet condition on axis aligned plane in the non normal direction.
Mixed Dirichlet-Neumann axis aligned symmetry plane.
Interfaces for user interaction with NEKO.
Defines inflow dirichlet conditions.
subroutine, public neko_type_error(base_type, wrong_type, known_types)
Reports an error allocating a type for a particular base pointer class.
Blasius profile for inlet (vector valued).
Generic Dirichlet boundary condition on .
Dong outflow condition Follows "A Convective-like Energy-Stable Open Boundary Condition for Simulati...
User defined dirichlet condition, for which the user can work with an entire field....
Extension of the user defined dirichlet condition field_dirichlet
Dirichlet condition for inlet (vector valued)
Dirichlet condition in non normal direction of a plane.
Mixed Dirichlet-Neumann symmetry plane condition.
A type collecting all the overridable user routines.
User defined dirichlet condition for velocity.