Loading [MathJax]/extensions/tex2jax.js
Neko 0.9.99
A portable framework for high-order spectral element flow simulations
All Classes Namespaces Files Functions Variables Typedefs Enumerator Macros Pages
bc_list.f90
Go to the documentation of this file.
1! Copyright (c) 2024-2025, 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!
34module bc_list
36 use num_types, only : rp
37 use field, only : field_t
38 use device, only : device_get_ptr
39 use utils, only : neko_error
40 use, intrinsic :: iso_c_binding, only : c_ptr
41 use bc, only : bc_t, bc_ptr_t
42 implicit none
43 private
44
47 type, public :: bc_list_t
48 ! The items of the list.
49 class(bc_ptr_t), allocatable, private :: items(:)
51 integer, private :: size_
54 integer, private :: capacity
55 contains
57 procedure, pass(this) :: init => bc_list_init
59 procedure, pass(this) :: free => bc_list_free
60
62 procedure, pass(this) :: append => bc_list_append
64 procedure, pass(this) :: get => bc_list_get
65
67 procedure, pass(this) :: is_empty => bc_list_is_empty
69 procedure, pass(this) :: strong => bc_list_strong
71 procedure :: size => bc_list_size
72
74 generic :: apply => apply_scalar, apply_vector, &
75 apply_scalar_field, apply_vector_field
77 procedure, pass(this) :: apply_scalar => bc_list_apply_scalar_array
79 procedure, pass(this) :: apply_vector => bc_list_apply_vector_array
81 procedure, pass(this) :: apply_scalar_field => bc_list_apply_scalar_field
83 procedure, pass(this) :: apply_vector_field => bc_list_apply_vector_field
84 end type bc_list_t
85
86contains
87
90 subroutine bc_list_init(this, capacity)
91 class(bc_list_t), intent(inout), target :: this
92 integer, optional :: capacity
93 integer :: n
94
95 call this%free()
96
97 n = 1
98 if (present(capacity)) n = capacity
99
100 allocate(this%items(n))
101
102 this%size_ = 0
103 this%capacity = n
104
105 end subroutine bc_list_init
106
110 subroutine bc_list_free(this)
111 class(bc_list_t), intent(inout) :: this
112 integer :: i
113
114 if (allocated(this%items)) then
115 do i = 1, this%size_
116 this%items(i)%ptr => null()
117 end do
118
119 deallocate(this%items)
120 end if
121
122 this%size_ = 0
123 this%capacity = 0
124 end subroutine bc_list_free
125
129 subroutine bc_list_append(this, bc)
130 class(bc_list_t), intent(inout) :: this
131 class(bc_t), intent(inout), target :: bc
132 type(bc_ptr_t), allocatable :: tmp(:)
133
134 if (this%size_ .ge. this%capacity) then
135 this%capacity = this%capacity * 2
136 allocate(tmp(this%capacity))
137 tmp(1:this%size_) = this%items
138 call move_alloc(tmp, this%items)
139 end if
140
141 this%size_ = this%size_ + 1
142 this%items(this%size_)%ptr => bc
143
144 end subroutine bc_list_append
145
149 function bc_list_get(this, i) result(bc)
150 class(bc_list_t), intent(in) :: this
151 class(bc_t), pointer :: bc
152 integer, intent(in) :: i
153
154 if (i .lt. 1 .or. i .gt. this%size_) then
155 call neko_error("Index out of bounds in bc_list_get")
156 end if
157
158 bc => this%items(i)%ptr
159
160 end function bc_list_get
161
169 subroutine bc_list_apply_scalar_array(this, x, n, t, tstep, strong)
170 class(bc_list_t), intent(inout) :: this
171 integer, intent(in) :: n
172 real(kind=rp), intent(inout), dimension(n) :: x
173 real(kind=rp), intent(in), optional :: t
174 integer, intent(in), optional :: tstep
175 logical, intent(in), optional :: strong
176 type(c_ptr) :: x_d
177 integer :: i
178
179
180 if (neko_bcknd_device .eq. 1) then
181 x_d = device_get_ptr(x)
182 if (present(strong)) then
183 if (present(t) .and. present(tstep)) then
184 do i = 1, this%size_
185 call this%items(i)%ptr%apply_scalar_dev(x_d, t, tstep, strong)
186 end do
187 else if (present(t)) then
188 do i = 1, this%size_
189 call this%items(i)%ptr%apply_scalar_dev(x_d, t = t, &
190 strong = strong)
191 end do
192 else if (present(tstep)) then
193 do i = 1, this%size_
194 call this%items(i)%ptr%apply_scalar_dev(x_d, tstep = tstep, &
195 strong = strong)
196 end do
197 else
198 do i = 1, this%size_
199 call this%items(i)%ptr%apply_scalar_dev(x_d)
200 end do
201 end if
202 else
203 if (present(t) .and. present(tstep)) then
204 do i = 1, this%size_
205 call this%items(i)%ptr%apply_scalar_dev(x_d, t = t, &
206 tstep = tstep)
207 end do
208 else if (present(t)) then
209 do i = 1, this%size_
210 call this%items(i)%ptr%apply_scalar_dev(x_d, t = t)
211 end do
212 else if (present(tstep)) then
213 do i = 1, this%size_
214 call this%items(i)%ptr%apply_scalar_dev(x_d, tstep = tstep)
215 end do
216 else
217 do i = 1, this%size_
218 call this%items(i)%ptr%apply_scalar_dev(x_d)
219 end do
220 end if
221 end if
222 else
223 if (present(strong)) then
224 if (present(t) .and. present(tstep)) then
225 do i = 1, this%size_
226 call this%items(i)%ptr%apply_scalar(x, n, t, tstep, strong)
227 end do
228 else if (present(t)) then
229 do i = 1, this%size_
230 call this%items(i)%ptr%apply_scalar(x, n, t = t, strong = strong)
231 end do
232 else if (present(tstep)) then
233 do i = 1, this%size_
234 call this%items(i)%ptr%apply_scalar(x, n, tstep = tstep, &
235 strong = strong)
236 end do
237 else
238 do i = 1, this%size_
239 call this%items(i)%ptr%apply_scalar(x, n, strong = strong)
240 end do
241 end if
242 else
243 if (present(t) .and. present(tstep)) then
244 do i = 1, this%size_
245 call this%items(i)%ptr%apply_scalar(x, n, t = t, tstep = tstep)
246 end do
247 else if (present(t)) then
248 do i = 1, this%size_
249 call this%items(i)%ptr%apply_scalar(x, n, t = t)
250 end do
251 else if (present(tstep)) then
252 do i = 1, this%size_
253 call this%items(i)%ptr%apply_scalar(x, n, tstep = tstep)
254 end do
255 else
256 do i = 1, this%size_
257 call this%items(i)%ptr%apply_scalar(x, n)
258 end do
259 end if
260 end if
261 end if
262 end subroutine bc_list_apply_scalar_array
263
273 subroutine bc_list_apply_vector_array(this, x, y, z, n, t, tstep, strong)
274 class(bc_list_t), intent(inout) :: this
275 integer, intent(in) :: n
276 real(kind=rp), intent(inout), dimension(n) :: x
277 real(kind=rp), intent(inout), dimension(n) :: y
278 real(kind=rp), intent(inout), dimension(n) :: z
279 real(kind=rp), intent(in), optional :: t
280 integer, intent(in), optional :: tstep
281 logical, intent(in), optional :: strong
282
283 type(c_ptr) :: x_d
284 type(c_ptr) :: y_d
285 type(c_ptr) :: z_d
286 integer :: i
287
288 if (neko_bcknd_device .eq. 1) then
289 x_d = device_get_ptr(x)
290 y_d = device_get_ptr(y)
291 z_d = device_get_ptr(z)
292
293 if (present(strong)) then
294 if (present(t) .and. present(tstep)) then
295 do i = 1, this%size_
296 call this%items(i)%ptr%apply_vector_dev(x_d, y_d, z_d, t, &
297 tstep, strong)
298 end do
299 else if (present(t)) then
300 do i = 1, this%size_
301 call this%items(i)%ptr%apply_vector_dev(x_d, y_d, z_d, t = t, &
302 strong = strong)
303 end do
304 else if (present(tstep)) then
305 do i = 1, this%size_
306 call this%items(i)%ptr%apply_vector_dev(x_d, y_d, z_d, &
307 tstep = tstep, strong = strong)
308 end do
309 else
310 do i = 1, this%size_
311 call this%items(i)%ptr%apply_vector_dev(x_d, y_d, z_d, &
312 strong = strong)
313 end do
314 end if
315 else
316 if (present(t) .and. present(tstep)) then
317 do i = 1, this%size_
318 call this%items(i)%ptr%apply_vector_dev(x_d, y_d, z_d, t, &
319 tstep)
320 end do
321 else if (present(t)) then
322 do i = 1, this%size_
323 call this%items(i)%ptr%apply_vector_dev(x_d, y_d, z_d, t = t)
324 end do
325 else if (present(tstep)) then
326 do i = 1, this%size_
327 call this%items(i)%ptr%apply_vector_dev(x_d, y_d, z_d, &
328 tstep = tstep)
329 end do
330 else
331 do i = 1, this%size_
332 call this%items(i)%ptr%apply_vector_dev(x_d, y_d, z_d)
333 end do
334 end if
335 end if
336 else
337 if (present(strong)) then
338 if (present(t) .and. present(tstep)) then
339 do i = 1, this%size_
340 call this%items(i)%ptr%apply_vector(x, y, z, n, t, tstep, strong)
341 end do
342 else if (present(t)) then
343 do i = 1, this%size_
344 call this%items(i)%ptr%apply_vector(x, y, z, n, t = t, &
345 strong = strong)
346 end do
347 else if (present(tstep)) then
348 do i = 1, this%size_
349 call this%items(i)%ptr%apply_vector(x, y, z, n, &
350 tstep = tstep, strong = strong)
351 end do
352 else
353 do i = 1, this%size_
354 call this%items(i)%ptr%apply_vector(x, y, z, n, strong = strong)
355 end do
356 end if
357 else
358 if (present(t) .and. present(tstep)) then
359 do i = 1, this%size_
360 call this%items(i)%ptr%apply_vector(x, y, z, n, t, tstep)
361 end do
362 else if (present(t)) then
363 do i = 1, this%size_
364 call this%items(i)%ptr%apply_vector(x, y, z, n, t = t)
365 end do
366 else if (present(tstep)) then
367 do i = 1, this%size_
368 call this%items(i)%ptr%apply_vector(x, y, z, n, tstep = tstep)
369 end do
370 else
371 do i = 1, this%size_
372 call this%items(i)%ptr%apply_vector(x, y, z, n)
373 end do
374 end if
375 end if
376 end if
377
378 end subroutine bc_list_apply_vector_array
379
386 subroutine bc_list_apply_scalar_field(this, x, t, tstep, strong)
387 class(bc_list_t), intent(inout) :: this
388 type(field_t), intent(inout) :: x
389 real(kind=rp), intent(in), optional :: t
390 integer, intent(in), optional :: tstep
391 logical, intent(in), optional :: strong
392 integer :: i, n
393
394 n = x%size()
395 if (neko_bcknd_device .eq. 1) then
396 if (present(strong)) then
397 if (present(t) .and. present(tstep)) then
398 do i = 1, this%size_
399 call this%items(i)%ptr%apply_scalar_dev(x%x_d, t, tstep, strong)
400 end do
401 else if (present(t)) then
402 do i = 1, this%size_
403 call this%items(i)%ptr%apply_scalar_dev(x%x_d, t = t, &
404 strong = strong)
405 end do
406 else if (present(tstep)) then
407 do i = 1, this%size_
408 call this%items(i)%ptr%apply_scalar_dev(x%x_d, tstep = tstep, &
409 strong = strong)
410 end do
411 else
412 do i = 1, this%size_
413 call this%items(i)%ptr%apply_scalar_dev(x%x_d, strong = strong)
414 end do
415 end if
416 else
417 if (present(t) .and. present(tstep)) then
418 do i = 1, this%size_
419 call this%items(i)%ptr%apply_scalar_dev(x%x_d, t, tstep)
420 end do
421 else if (present(t)) then
422 do i = 1, this%size_
423 call this%items(i)%ptr%apply_scalar_dev(x%x_d, t = t)
424 end do
425 else if (present(tstep)) then
426 do i = 1, this%size_
427 call this%items(i)%ptr%apply_scalar_dev(x%x_d, tstep = tstep)
428 end do
429 else
430 do i = 1, this%size_
431 call this%items(i)%ptr%apply_scalar_dev(x%x_d)
432 end do
433 end if
434 end if
435 else
436 do i = 1, this%size_
437 call this%items(i)%ptr%apply_scalar(x%x, n, t, tstep, strong)
438 end do
439 end if
440 end subroutine bc_list_apply_scalar_field
441
450 subroutine bc_list_apply_vector_field(this, x, y, z, t, tstep, strong)
451 class(bc_list_t), intent(inout) :: this
452 type(field_t), intent(inout) :: x
453 type(field_t), intent(inout) :: y
454 type(field_t), intent(inout) :: z
455 real(kind=rp), intent(in), optional :: t
456 integer, intent(in), optional :: tstep
457 logical, intent(in), optional :: strong
458 integer :: i, n
459 character(len=256) :: msg
460
461 n = x%size()
462
463 ! Ensure all fields are the same size
464 if (y%size() .ne. n .or. z%size() .ne. n) then
465 msg = "Fields x, y, z must have the same size in " // &
466 "bc_list_apply_vector_field"
467 call neko_error(trim(msg))
468 end if
469
470 if (neko_bcknd_device .eq. 1) then
471 if (present(strong)) then
472 if (present(t) .and. present(tstep)) then
473 do i = 1, this%size_
474 call this%items(i)%ptr%apply_vector_dev(x%x_d, y%x_d, z%x_d, &
475 t, tstep, strong)
476 end do
477 else if (present(t)) then
478 do i = 1, this%size_
479 call this%items(i)%ptr%apply_vector_dev(x%x_d, y%x_d, z%x_d, &
480 t = t, strong = strong)
481 end do
482 else if (present(tstep)) then
483 do i = 1, this%size_
484 call this%items(i)%ptr%apply_vector_dev(x%x_d, y%x_d, z%x_d, &
485 tstep = tstep, strong = strong)
486 end do
487 else
488 do i = 1, this%size_
489 call this%items(i)%ptr%apply_vector_dev(x%x_d, y%x_d, z%x_d, &
490 strong = strong)
491 end do
492 end if
493 else
494 if (present(t) .and. present(tstep)) then
495 do i = 1, this%size_
496 call this%items(i)%ptr%apply_vector_dev(x%x_d, y%x_d, z%x_d, &
497 t, tstep)
498 end do
499 else if (present(t)) then
500 do i = 1, this%size_
501 call this%items(i)%ptr%apply_vector_dev(x%x_d, y%x_d, z%x_d, &
502 t = t)
503 end do
504 else if (present(tstep)) then
505 do i = 1, this%size_
506 call this%items(i)%ptr%apply_vector_dev(x%x_d, y%x_d, z%x_d, &
507 tstep = tstep)
508 end do
509 else
510 do i = 1, this%size_
511 call this%items(i)%ptr%apply_vector_dev(x%x_d, y%x_d, z%x_d)
512 end do
513 end if
514 end if
515 else
516 if (present(strong)) then
517 if (present(t) .and. present(tstep)) then
518 do i = 1, this%size_
519 call this%items(i)%ptr%apply_vector(x%x, y%x, z%x, n, t, &
520 tstep, strong)
521 end do
522 else if (present(t)) then
523 do i = 1, this%size_
524 call this%items(i)%ptr%apply_vector(x%x, y%x, z%x, n, &
525 t = t, strong = strong)
526 end do
527 else if (present(tstep)) then
528 do i = 1, this%size_
529 call this%items(i)%ptr%apply_vector(x%x, y%x, z%x, n, &
530 tstep = tstep, strong = strong)
531 end do
532 else
533 do i = 1, this%size_
534 call this%items(i)%ptr%apply_vector(x%x, y%x, z%x, n, &
535 strong = strong)
536 end do
537 end if
538 else
539 if (present(t) .and. present(tstep)) then
540 do i = 1, this%size_
541 call this%items(i)%ptr%apply_vector(x%x, y%x, z%x, n, t, &
542 tstep)
543 end do
544 else if (present(t)) then
545 do i = 1, this%size_
546 call this%items(i)%ptr%apply_vector(x%x, y%x, z%x, n, &
547 t = t)
548 end do
549 else if (present(tstep)) then
550 do i = 1, this%size_
551 call this%items(i)%ptr%apply_vector(x%x, y%x, z%x, n, &
552 tstep = tstep)
553 end do
554 else
555 do i = 1, this%size_
556 call this%items(i)%ptr%apply_vector(x%x, y%x, z%x, n)
557 end do
558 end if
559 end if
560 end if
561
562 end subroutine bc_list_apply_vector_field
563
565 pure function bc_list_strong(this, i) result(strong)
566 class(bc_list_t), intent(in), target :: this
567 integer, intent(in) :: i
568 logical :: strong
569
570 strong = this%items(i)%ptr%strong
571 end function bc_list_strong
572
574 function bc_list_is_empty(this) result(is_empty)
575 class(bc_list_t), intent(in), target :: this
576 logical :: is_empty
577 integer :: i
578
579 is_empty = .true.
580 do i = 1, this%size_
581
582 if (.not. allocated(this%items(i)%ptr%msk)) then
583 call neko_error("bc not finalized, error in bc_list%is_empty")
584 end if
585
586 if (this%items(i)%ptr%msk(0) > 0) is_empty = .false.
587
588 end do
589 end function bc_list_is_empty
590
592 pure function bc_list_size(this) result(size)
593 class(bc_list_t), intent(in), target :: this
594 integer :: size
595
596 size = this%size_
597 end function bc_list_size
598
599end module bc_list
Return the device pointer for an associated Fortran array.
Definition device.F90:95
Defines a list of bc_t.
Definition bc_list.f90:34
pure logical function bc_list_strong(this, i)
Return whether the bc is strong or not.
Definition bc_list.f90:566
class(bc_t) function, pointer bc_list_get(this, i)
Get the item at the given index.
Definition bc_list.f90:150
pure integer function bc_list_size(this)
Return the number of items in the list.
Definition bc_list.f90:593
subroutine bc_list_append(this, bc)
Append a condition to the end of the list.
Definition bc_list.f90:130
subroutine bc_list_apply_vector_array(this, x, y, z, n, t, tstep, strong)
Apply a list of boundary conditions to a vector field.
Definition bc_list.f90:274
subroutine bc_list_init(this, capacity)
Constructor.
Definition bc_list.f90:91
subroutine bc_list_apply_scalar_field(this, x, t, tstep, strong)
Apply a list of boundary conditions to a scalar field.
Definition bc_list.f90:387
subroutine bc_list_apply_vector_field(this, x, y, z, t, tstep, strong)
Apply a list of boundary conditions to a vector field.
Definition bc_list.f90:451
subroutine bc_list_apply_scalar_array(this, x, n, t, tstep, strong)
Apply a list of boundary conditions to a scalar field.
Definition bc_list.f90:170
subroutine bc_list_free(this)
Destructor.
Definition bc_list.f90:111
logical function bc_list_is_empty(this)
Return whether the list is empty.
Definition bc_list.f90:575
Defines a boundary condition.
Definition bc.f90:34
Device abstraction, common interface for various accelerators.
Definition device.F90:34
Defines a field.
Definition field.f90:34
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Utilities.
Definition utils.f90:35
Pointer to a `bc_t`.
Definition bc.f90:121
Base type for a boundary condition.
Definition bc.f90:57
A list of allocatable `bc_t`. Follows the standard interface of lists.
Definition bc_list.f90:47