42 character(len=25) :: EULER_KNOWN_BCS(7) = [character(len=25) :: &
58 module subroutine density_bc_factory(object, scheme, json, coef,
user)
59 class(bc_t),
pointer,
intent(inout) :: object
60 type(fluid_scheme_compressible_euler_t),
intent(in) :: scheme
61 type(json_file),
intent(inout) :: json
62 type(coef_t),
intent(in) :: coef
63 type(user_t),
intent(in) :: user
64 character(len=:),
allocatable :: type
66 integer,
allocatable :: zone_indices(:)
68 call json_get(json,
"type", type)
70 select case (trim(type))
71 case (
"density_value")
74 do i = 1,
size(euler_known_bcs)
75 if (trim(type) .eq. trim(euler_known_bcs(i)))
return
77 call neko_type_error(
"compressible_euler boundary conditions",
type, &
81 call json_get(json,
"zone_indices", zone_indices)
82 call object%init(coef, json)
84 do i = 1,
size(zone_indices)
85 call object%mark_zone(coef%msh%labeled_zones(zone_indices(i)))
87 call object%finalize()
88 end subroutine density_bc_factory
96 module subroutine pressure_bc_factory(object, scheme, json, coef,
user)
97 class(bc_t),
pointer,
intent(inout) :: object
98 type(fluid_scheme_compressible_euler_t),
intent(inout) :: scheme
99 type(json_file),
intent(inout) :: json
100 type(coef_t),
intent(in) :: coef
101 type(user_t),
intent(in) :: user
102 character(len=:),
allocatable :: type
104 integer,
allocatable :: zone_indices(:)
106 call json_get(json,
"type", type)
108 select case (trim(type))
109 case (
"outflow",
"normal_outflow")
111 case (
"pressure_value")
114 do i = 1,
size(euler_known_bcs)
115 if (trim(type) .eq. trim(euler_known_bcs(i)))
return
117 call neko_type_error(
"compressible_euler boundary conditions",
type, &
121 call json_get(json,
"zone_indices", zone_indices)
122 call object%init(coef, json)
124 do i = 1,
size(zone_indices)
125 call object%mark_zone(coef%msh%labeled_zones(zone_indices(i)))
127 call object%finalize()
131 do i = 1,
size(zone_indices)
132 do j = 1, scheme%msh%nelv
133 do k = 1, 2 * scheme%msh%gdim
134 if (scheme%msh%facet_type(k,j) .eq. -zone_indices(i))
then
135 scheme%msh%facet_type(k, j) = 1
140 end subroutine pressure_bc_factory
148 module subroutine velocity_bc_factory(object, scheme, json, coef,
user)
149 class(bc_t),
pointer,
intent(inout) :: object
150 type(fluid_scheme_compressible_euler_t),
intent(in) :: scheme
151 type(json_file),
intent(inout) :: json
152 type(coef_t),
intent(in) :: coef
153 type(user_t),
intent(in) :: user
154 character(len=:),
allocatable :: type
156 integer,
allocatable :: zone_indices(:)
158 call json_get(json,
"type", type)
160 select case (trim(type))
165 case (
"velocity_value")
168 do i = 1,
size(euler_known_bcs)
169 if (trim(type) .eq. trim(euler_known_bcs(i)))
return
171 call neko_type_error(
"compressible_euler boundary conditions",
type, &
175 call json_get(json,
"zone_indices", zone_indices)
176 call object%init(coef, json)
177 do i = 1,
size(zone_indices)
178 call object%mark_zone(coef%msh%labeled_zones(zone_indices(i)))
180 call object%finalize()
182 end subroutine velocity_bc_factory
184end submodule euler_bc_fctry
Defines a dirichlet boundary condition.
Defines inflow dirichlet conditions.
Mixed Dirichlet-Neumann axis aligned symmetry plane.
Defines a zero-valued Dirichlet boundary condition.
Generic Dirichlet boundary condition on .
Dirichlet condition for inlet (vector valued)
Mixed Dirichlet-Neumann symmetry plane condition.
Zero-valued Dirichlet boundary condition. Used for no-slip walls, but also for various auxillary cond...