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
field.f90
Go to the documentation of this file.
1! Copyright (c) 2018-2023, 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 field
36 use device_math
37 use num_types, only : rp
38 use device
39 use math, only : add2, copy, cadd
40 use mesh, only : mesh_t
41 use space, only : space_t, operator(.ne.)
42 use dofmap, only : dofmap_t
43 use, intrinsic :: iso_c_binding
44 implicit none
45 private
46
47 type, public :: field_t
48 real(kind=rp), allocatable :: x(:,:,:,:)
49
50 type(space_t), pointer :: xh
51 type(mesh_t), pointer :: msh
52 type(dofmap_t), pointer :: dof
53
54 logical :: internal_dofmap = .false.
55 character(len=80) :: name
56 type(c_ptr) :: x_d = c_null_ptr
57 contains
58 procedure, private, pass(this) :: init_common => field_init_common
59 procedure, private, pass(this) :: init_external_dof => &
61 procedure, private, pass(this) :: init_internal_dof => &
63 procedure, private, pass(this) :: assign_field => field_assign_field
64 procedure, private, pass(this) :: assign_scalar => field_assign_scalar
65 procedure, private, pass(this) :: add_field => field_add_field
66 procedure, private, pass(this) :: add_scalar => field_add_scalar
67 procedure, pass(this) :: free => field_free
69 procedure, pass(this) :: size => field_size
71 generic :: init => init_external_dof, init_internal_dof
73 generic :: assignment(=) => assign_field, assign_scalar
77 generic :: add => add_field, add_scalar
78 end type field_t
79
81 type, public :: field_ptr_t
82 type(field_t), pointer :: ptr => null()
83 end type field_ptr_t
84
85contains
86
88 subroutine field_init_internal_dof(this, msh, space, fld_name)
89 class(field_t), intent(inout) :: this
90 type(mesh_t), target, intent(in) :: msh
91 type(space_t), target, intent(in) :: space
92 character(len=*), optional :: fld_name
93
94 call this%free()
95
96 this%Xh => space
97 this%msh => msh
98
99 allocate(this%dof)
100 call this%dof%init(this%msh, this%Xh)
101 this%internal_dofmap = .true.
102
103 if (present(fld_name)) then
104 call this%init_common(fld_name)
105 else
106 call this%init_common()
107 end if
108
109 end subroutine field_init_internal_dof
110
112 subroutine field_init_external_dof(this, dof, fld_name)
113 class(field_t), intent(inout) :: this
114 type(dofmap_t), target, intent(in) :: dof
115 character(len=*), optional :: fld_name
116
117 call this%free()
118
119 this%dof => dof
120 this%Xh => dof%Xh
121 this%msh => dof%msh
122
123 if (present(fld_name)) then
124 call this%init_common(fld_name)
125 else
126 call this%init_common()
127 end if
128
129 end subroutine field_init_external_dof
130
132 subroutine field_init_common(this, fld_name)
133 class(field_t), intent(inout) :: this
134 character(len=*), optional :: fld_name
135 integer :: ierr
136 integer :: n
137
138 associate(lx => this%Xh%lx, ly => this%Xh%ly, &
139 lz => this%Xh%lz, nelv => this%msh%nelv)
140
141 if (.not. allocated(this%x)) then
142 allocate(this%x(lx, ly, lz, nelv), stat = ierr)
143 this%x = 0.0_rp
144 end if
145
146 if (present(fld_name)) then
147 this%name = fld_name
148 else
149 this%name = "Field"
150 end if
151
152 if (neko_bcknd_device .eq. 1) then
153 n = lx * ly * lz * nelv
154 call device_map(this%x, this%x_d, n)
155 end if
156 end associate
157
158 end subroutine field_init_common
159
161 subroutine field_free(this)
162 class(field_t), intent(inout) :: this
163
164 if (allocated(this%x)) then
165 deallocate(this%x)
166 end if
167
168 if (this%internal_dofmap) then
169 deallocate(this%dof)
170 this%internal_dofmap = .false.
171 end if
172
173 nullify(this%msh)
174 nullify(this%Xh)
175 nullify(this%dof)
176
177 if (c_associated(this%x_d)) then
178 call device_free(this%x_d)
179 end if
180
181 end subroutine field_free
182
186 subroutine field_assign_field(this, g)
187 class(field_t), intent(inout) :: this
188 type(field_t), intent(in) :: g
189
190 if (allocated(this%x)) then
191 if (this%Xh .ne. g%Xh) then
192 call this%free()
193 end if
194 end if
195
196 this%Xh => g%Xh
197 this%msh => g%msh
198 this%dof => g%dof
199
200
201 this%Xh%lx = g%Xh%lx
202 this%Xh%ly = g%Xh%ly
203 this%Xh%lz = g%Xh%lz
204
205 if (.not. allocated(this%x)) then
206
207 allocate(this%x(this%Xh%lx, this%Xh%ly, this%Xh%lz, this%msh%nelv))
208
209 if (neko_bcknd_device .eq. 1) then
210 call device_map(this%x, this%x_d, this%size())
211 end if
212
213 end if
214
215 if (neko_bcknd_device .eq. 1) then
216 call device_copy(this%x_d, g%x_d, this%size())
217 else
218 call copy(this%x, g%x, this%dof%size())
219 end if
220
221 end subroutine field_assign_field
222
224 subroutine field_assign_scalar(this, a)
225 class(field_t), intent(inout) :: this
226 real(kind=rp), intent(in) :: a
227 integer :: i, j, k, l
228
229 if (neko_bcknd_device .eq. 1) then
230 call device_cfill(this%x_d, a, this%size())
231 else
232 do i = 1, this%msh%nelv
233 do l = 1, this%Xh%lz
234 do k = 1, this%Xh%ly
235 do j = 1, this%Xh%lx
236 this%x(j, k, l, i) = a
237 end do
238 end do
239 end do
240 end do
241 end if
242
243 end subroutine field_assign_scalar
244
248 subroutine field_add_field(this, g)
249 class(field_t), intent(inout) :: this
250 type(field_t), intent(in) :: g
251
252 if (neko_bcknd_device .eq. 1) then
253 call device_add2(this%x_d, g%x_d, this%size())
254 else
255 call add2(this%x, g%x, this%size())
256 end if
257
258 end subroutine field_add_field
259
260
263 subroutine field_add_scalar(this, a)
264 class(field_t), intent(inout) :: this
265 real(kind=rp), intent(in) :: a
266
267 if (neko_bcknd_device .eq. 1) then
268 call device_cadd(this%x_d, a, this%size())
269 else
270 call cadd(this%x, a, this%size())
271 end if
272
273 end subroutine field_add_scalar
274
276 pure function field_size(this) result(size)
277 class(field_t), intent(in) :: this
278 integer :: size
279
280 size = this%dof%size()
281 end function field_size
282
283end module field
284
Map a Fortran array to a device (allocate and associate)
Definition device.F90:71
Device abstraction, common interface for various accelerators.
Definition device.F90:34
Defines a mapping of the degrees of freedom.
Definition dofmap.f90:35
Defines a field.
Definition field.f90:34
subroutine field_add_field(this, g)
Add .
Definition field.f90:249
pure integer function field_size(this)
Return the size of the field based on the underlying dofmap.
Definition field.f90:277
subroutine field_assign_field(this, g)
Assignment .
Definition field.f90:187
subroutine field_add_scalar(this, a)
Add .
Definition field.f90:264
subroutine field_assign_scalar(this, a)
Assignment .
Definition field.f90:225
subroutine field_init_common(this, fld_name)
Initialize a field this.
Definition field.f90:133
subroutine field_init_external_dof(this, dof, fld_name)
Initialize a field this on the mesh msh using an internal dofmap.
Definition field.f90:113
subroutine field_init_internal_dof(this, msh, space, fld_name)
Initialize a field this on the mesh msh using an internal dofmap.
Definition field.f90:89
subroutine field_free(this)
Deallocate a field f.
Definition field.f90:162
Definition math.f90:60
subroutine, public cadd(a, s, n)
Add a scalar to vector .
Definition math.f90:322
subroutine, public add2(a, b, n)
Vector addition .
Definition math.f90:586
subroutine, public copy(a, b, n)
Copy a vector .
Definition math.f90:238
Defines a mesh.
Definition mesh.f90:34
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Defines a function space.
Definition space.f90:34
field_ptr_t, To easily obtain a pointer to a field
Definition field.f90:81
The function space for the SEM solution fields.
Definition space.f90:62