Neko 1.99.1
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
source_term_fctry.f90
Go to the documentation of this file.
1! Copyright (c) 2023-2024, The Neko Authors
2! All rights reserved.
3!
4! Redistribution and use in source and binary forms, with or without
5! modification, are permitted provided that the following conditions
6! are met:
7!
8! * Redistributions of source code must retain the above copyright
9! notice, this list of conditions and the following disclaimer.
10!
11! * Redistributions in binary form must reproduce the above
12! copyright notice, this list of conditions and the following
13! disclaimer in the documentation and/or other materials provided
14! with the distribution.
15!
16! * Neither the name of the authors nor the names of its
17! contributors may be used to endorse or promote products derived
18! from this software without specific prior written permission.
19!
20! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31! POSSIBILITY OF SUCH DAMAGE.
32!
33!
35submodule(source_term) source_term_fctry
42 use json_utils, only : json_get
44 implicit none
45
46 ! List of all possible types created by the factory routine
47 character(len=20) :: SOURCE_KNOWN_TYPES(6) = [character(len=20) :: &
48 "constant", &
49 "boussinesq", &
50 "coriolis", &
51 "centrifugal", &
52 "gradient_jump_penalty", &
53 "brinkman"]
54
55contains
56
61 module subroutine source_term_factory(object, json, fields, coef, &
62 variable_name)
63 class(source_term_t), allocatable, intent(inout) :: object
64 type(json_file), intent(inout) :: json
65 type(field_list_t), intent(inout) :: fields
66 type(coef_t), intent(inout) :: coef
67 character(len=*), intent(in) :: variable_name
68 character(len=:), allocatable :: type_name
69 character(len=:), allocatable :: type_string
70
71 call json_get(json, "type", type_name)
72
73 ! Allocate
74 call source_term_allocator(object, type_name)
75
76 ! Initialize
77 call object%init(json, fields, coef, variable_name)
78
79 end subroutine source_term_factory
80
84 module subroutine source_term_allocator(object, type_name)
85 class(source_term_t), allocatable, intent(inout) :: object
86 character(len=:), allocatable, intent(in) :: type_name
87 integer :: i
88
89 select case (trim(type_name))
90 case ("constant")
91 allocate(const_source_term_t::object)
92 case ("boussinesq")
93 allocate(boussinesq_source_term_t::object)
94 case ("coriolis")
95 allocate(coriolis_source_term_t::object)
96 case ("centrifugal")
97 allocate(centrifugal_source_term_t::object)
98 case ("brinkman")
99 allocate(brinkman_source_term_t::object)
100 case ("gradient_jump_penalty")
101 allocate(gradient_jump_penalty_t::object)
102 case default
103 do i = 1, source_term_registry_size
104 if (trim(type_name) .eq. trim(source_term_registry(i)%type_name)) then
105 call source_term_registry(i)%allocator(object)
106 return
107 end if
108 end do
109
110 call neko_type_error("source term", type_name, source_known_types)
111 end select
112 end subroutine source_term_allocator
113
119 module subroutine register_source_term(type_name, allocator)
120 character(len=*), intent(in) :: type_name
121 procedure(source_term_allocate), pointer, intent(in) :: allocator
122 type(allocator_entry), allocatable :: temp(:)
123 integer :: i
124
125 do i = 1, size(source_known_types)
126 if (trim(type_name) .eq. trim(source_known_types(i))) then
127 call neko_type_registration_error("source term", type_name, .true.)
128 end if
129 end do
130
131 do i = 1, source_term_registry_size
132 if (trim(type_name) .eq. trim(source_term_registry(i)%type_name)) then
133 call neko_type_registration_error("source term", type_name, .false.)
134 end if
135 end do
136
137 ! Expand registry
138 if (source_term_registry_size .eq. 0) then
139 allocate(source_term_registry(1))
140 else
141 allocate(temp(source_term_registry_size + 1))
142 temp(1:source_term_registry_size) = source_term_registry
143 call move_alloc(temp, source_term_registry)
144 end if
145
146 source_term_registry_size = source_term_registry_size + 1
147 source_term_registry(source_term_registry_size)%type_name = type_name
148 source_term_registry(source_term_registry_size)%allocator => allocator
149 end subroutine register_source_term
150
151end submodule source_term_fctry
Retrieves a parameter by name or throws an error.
Implements the boussinesq_source_term_t type.
Implements the brinkman_source_term_t type.
Implements the centrifugal_source_term_t type. Maintainer: Adam Peplinski.
Implements the const_source_term_t type.
Implements the coriolis_source_term_t type. Maintainer: Timofey Mukha.
Implements gradient_jump_penalty_t.
Utilities for retrieving parameters from the case files.
Implements the source_term_t type and a wrapper source_term_wrapper_t.
Utilities.
Definition utils.f90:35
subroutine, public neko_type_registration_error(base_type, wrong_type, known)
Definition utils.f90:328
subroutine, public neko_type_error(base_type, wrong_type, known_types)
Reports an error allocating a type for a particular base pointer class.
Definition utils.f90:313
Bouyancy source term accroding to the Boussinesq approximation.
A Brinkman source term. The region and strength are controlled by assigning regions types and brinkma...
This source term adds the centrifugal force.
A constant source term. The strength is specified with the values keyword, which should be an array,...
This source term adds the Coriolis force.