Neko 1.99.2
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
field.f90
Go to the documentation of this file.
1! Copyright (c) 2018-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 field
37 use num_types, only : rp, c_rp
39 use math, only : add2, copy, cadd, cfill
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) :: copy_from => field_copy_from
68 procedure, pass(this) :: free => field_free
70 procedure, pass(this) :: size => field_size
72 generic :: init => init_external_dof, init_internal_dof
74 generic :: assignment(=) => assign_field, assign_scalar
78 generic :: add => add_field, add_scalar
79 end type field_t
80
82 type, public :: field_ptr_t
83 type(field_t), pointer :: ptr => null()
84 end type field_ptr_t
85
86contains
87
89 subroutine field_init_internal_dof(this, msh, space, fld_name)
90 class(field_t), intent(inout) :: this
91 type(mesh_t), target, intent(in) :: msh
92 type(space_t), target, intent(in) :: space
93 character(len=*), optional :: fld_name
94
95 call this%free()
96
97 this%Xh => space
98 this%msh => msh
99
100 allocate(this%dof)
101 call this%dof%init(this%msh, this%Xh)
102 this%internal_dofmap = .true.
103
104 if (present(fld_name)) then
105 call this%init_common(fld_name)
106 else
107 call this%init_common()
108 end if
109
110 end subroutine field_init_internal_dof
111
113 subroutine field_init_external_dof(this, dof, fld_name)
114 class(field_t), intent(inout) :: this
115 type(dofmap_t), target, intent(in) :: dof
116 character(len=*), optional :: fld_name
117
118 call this%free()
119
120 this%dof => dof
121 this%Xh => dof%Xh
122 this%msh => dof%msh
123
124 if (present(fld_name)) then
125 call this%init_common(fld_name)
126 else
127 call this%init_common()
128 end if
129
130 end subroutine field_init_external_dof
131
133 subroutine field_init_common(this, fld_name)
134 class(field_t), intent(inout) :: this
135 character(len=*), optional :: fld_name
136 integer :: ierr
137 integer :: n
138
139 associate(lx => this%Xh%lx, ly => this%Xh%ly, &
140 lz => this%Xh%lz, nelv => this%msh%nelv)
141
142 if (.not. allocated(this%x)) then
143 allocate(this%x(lx, ly, lz, nelv), stat = ierr)
144 this%x = 0.0_rp
145 end if
146
147 if (present(fld_name)) then
148 this%name = fld_name
149 else
150 this%name = "Field"
151 end if
152
153 if (neko_bcknd_device .eq. 1) then
154 n = lx * ly * lz * nelv
155 call device_map(this%x, this%x_d, n)
156 block
157 real(c_rp) :: rp_dummy
158 integer(c_size_t) :: s
159 s = c_sizeof(rp_dummy) * n
160 call device_memset(this%x_d, 0, s, sync = .true.)
161 end block
162 end if
163 end associate
164
165 end subroutine field_init_common
166
168 subroutine field_free(this)
169 class(field_t), intent(inout) :: this
170
171 this%name = ""
172 if (allocated(this%x)) then
173 deallocate(this%x)
174 end if
175
176 if (this%internal_dofmap) then
177 deallocate(this%dof)
178 this%internal_dofmap = .false.
179 end if
180
181 nullify(this%msh)
182 nullify(this%Xh)
183 nullify(this%dof)
184
185 if (c_associated(this%x_d)) then
186 call device_free(this%x_d)
187 end if
188
189 end subroutine field_free
190
195 subroutine field_copy_from(this, memdir, sync)
196 class(field_t), intent(inout) :: this
197 integer, intent(in) :: memdir
198 logical, intent(in) :: sync
199
200 if (neko_bcknd_device .eq. 1) then
201 call device_memcpy(this%x, this%x_d, this%size(), memdir, sync)
202 end if
203
204 end subroutine field_copy_from
205
206
210 subroutine field_assign_field(this, g)
211 class(field_t), intent(inout) :: this
212 type(field_t), intent(in) :: g
213
214 if (allocated(this%x)) then
215 if (.not. associated(this%Xh, g%Xh)) then
216 call this%free()
217 end if
218 end if
219
220 this%Xh => g%Xh
221 this%msh => g%msh
222 if (len_trim(this%name) == 0) then
223 this%name = g%name
224 end if
225
226 if (.not. g%internal_dofmap) then
227 this%dof => g%dof
228 else
229 if (this%internal_dofmap) then
230 call this%dof%free()
231 else
232 allocate(this%dof)
233 this%internal_dofmap = .true.
234 end if
235 call this%dof%init(this%msh, this%Xh)
236 end if
237
238 if (.not. allocated(this%x)) then
239
240 allocate(this%x(this%Xh%lx, this%Xh%ly, this%Xh%lz, this%msh%nelv))
241
242 if (neko_bcknd_device .eq. 1) then
243 call device_map(this%x, this%x_d, this%size())
244 end if
245
246 end if
247
248 if (neko_bcknd_device .eq. 1) then
249 call device_copy(this%x_d, g%x_d, this%size())
250 else
251 call copy(this%x, g%x, this%dof%size())
252 end if
253
254 end subroutine field_assign_field
255
257 subroutine field_assign_scalar(this, a)
258 class(field_t), intent(inout) :: this
259 real(kind=rp), intent(in) :: a
260 integer :: i, j, k, l
261
262 if (neko_bcknd_device .eq. 1) then
263 call device_cfill(this%x_d, a, this%size())
264 else
265 call cfill(this%x, a, this%size())
266 end if
267
268 end subroutine field_assign_scalar
269
273 subroutine field_add_field(this, g)
274 class(field_t), intent(inout) :: this
275 type(field_t), intent(in) :: g
276
277 if (neko_bcknd_device .eq. 1) then
278 call device_add2(this%x_d, g%x_d, this%size())
279 else
280 call add2(this%x, g%x, this%size())
281 end if
282
283 end subroutine field_add_field
284
285
288 subroutine field_add_scalar(this, a)
289 class(field_t), intent(inout) :: this
290 real(kind=rp), intent(in) :: a
291
292 if (neko_bcknd_device .eq. 1) then
293 call device_cadd(this%x_d, a, this%size())
294 else
295 call cadd(this%x, a, this%size())
296 end if
297
298 end subroutine field_add_scalar
299
301 pure function field_size(this) result(size)
302 class(field_t), intent(in) :: this
303 integer :: size
304
305 size = this%dof%size()
306 end function field_size
307
308end module field
Map a Fortran array to a device (allocate and associate)
Definition device.F90:77
Copy data between host and device (or device and device)
Definition device.F90:71
subroutine, public device_add2(a_d, b_d, n, strm)
Vector addition .
subroutine, public device_copy(a_d, b_d, n, strm)
Copy a vector .
subroutine, public device_cfill(a_d, c, n, strm)
Set all elements to a constant c .
Device abstraction, common interface for various accelerators.
Definition device.F90:34
subroutine, public device_free(x_d)
Deallocate memory on the device.
Definition device.F90:219
subroutine, public device_memset(x_d, v, s, sync, strm)
Set memory on the device to a value.
Definition device.F90:238
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:274
pure integer function field_size(this)
Return the size of the field based on the underlying dofmap.
Definition field.f90:302
subroutine field_assign_field(this, g)
Assignment .
Definition field.f90:211
subroutine field_add_scalar(this, a)
Add .
Definition field.f90:289
subroutine field_copy_from(this, memdir, sync)
Easy way to copy between host and device.
Definition field.f90:196
subroutine field_assign_scalar(this, a)
Assignment .
Definition field.f90:258
subroutine field_init_common(this, fld_name)
Initialize a field this.
Definition field.f90:134
subroutine field_init_external_dof(this, dof, fld_name)
Initialize a field this on the mesh msh using an internal dofmap.
Definition field.f90:114
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:90
subroutine field_free(this)
Deallocate a field f.
Definition field.f90:169
Definition math.f90:60
subroutine, public cadd(a, s, n)
Add a scalar to vector .
Definition math.f90:462
subroutine, public add2(a, b, n)
Vector addition .
Definition math.f90:726
subroutine, public cfill(a, c, n)
Set all elements to a constant c .
Definition math.f90:487
subroutine, public copy(a, b, n)
Copy a vector .
Definition math.f90:249
Defines a mesh.
Definition mesh.f90:34
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public c_rp
Definition num_types.f90:13
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:82
The function space for the SEM solution fields.
Definition space.f90:63