Neko 1.99.1
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
buffer_4d.F90
Go to the documentation of this file.
1! Copyright (c) 2024, Gregor Weiss (HLRS)
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!
35 use num_types, only : dp, sp, i8, rp
36 use vector, only : vector_t
37#ifdef HAVE_ADIOS2_FORTRAN
38 use adios2
39#endif
41 implicit none
42
43 type, extends(buffer_t) :: buffer_4d_t
44 integer(kind=i8), dimension(4) :: shape_dims, start_dims, count_dims
45 real(kind=dp), private, allocatable :: data_dp(:,:,:,:)
46 real(kind=sp), private, allocatable :: data_sp(:,:,:,:)
47 contains
48 procedure :: init => buffer_4d_init
49 procedure :: fill => buffer_4d_fill
50#ifdef HAVE_ADIOS2_FORTRAN
51 procedure :: define => buffer_4d_define
52 procedure :: inquire => buffer_4d_inquire
53 procedure :: write => buffer_4d_write
54 procedure :: read => buffer_4d_read
55#endif
56 procedure :: copy => buffer_4d_copy
57 end type buffer_4d_t
58
59contains
60
61 subroutine buffer_4d_init(this, precision, gdim, glb_nelv, offset_el, nelv, &
62 lx, ly, lz)
63 class(buffer_4d_t), intent(inout) :: this
64 logical, intent(in) :: precision
65 integer, intent(in) :: gdim, glb_nelv, offset_el, nelv, lx, ly, lz
66 integer :: lxyz
67
68 lxyz = lx*ly*lz
69
70 call buffer_set_precision(this, precision)
71
72 if (this%dp_precision) then
73 if (allocated(this%data_dp)) then
74 deallocate(this%data_dp)
75 end if
76 allocate(this%data_dp(nelv, lx, ly, lz))
77 else
78 if (allocated(this%data_sp)) then
79 deallocate(this%data_sp)
80 end if
81 allocate(this%data_sp(nelv, lx, ly, lz))
82 end if
83
84 this%shape_dims = [int(glb_nelv, i8), int(lx, i8), int(ly, i8), int(lz, i8)]
85 this%start_dims = [int(offset_el, i8), int(0, i8), int(0, i8), int(0, i8)]
86 this%count_dims = [int(nelv, i8), int(lx, i8), int(ly, i8), int(lz, i8)]
87
88 end subroutine buffer_4d_init
89
90 subroutine buffer_4d_fill(this, x, n)
91 class(buffer_4d_t), intent(inout) :: this
92 integer, intent(inout) :: n
93 real(kind=rp), intent(inout) :: x(n)
94 integer :: i, j, k, l, nelv, lx, ly, lz, index
95
96 nelv = this%count_dims(1)
97 lx = this%count_dims(2)
98 ly = this%count_dims(3)
99 lz = this%count_dims(4)
100
101 if (this%dp_precision) then
102 do i = 1, nelv
103 do j = 1, lz
104 do k = 1, ly
105 do l = 1, lx
106 index = (l-1) + lx*(k-1) + lx*ly*(j-1) + lx*ly*lz*(i-1) + 1
107 this%data_dp(i,l,k,j) = real(x(index), dp)
108 end do
109 end do
110 end do
111 end do
112 else
113 do i = 1, nelv
114 do j = 1, lz
115 do k = 1, ly
116 do l = 1, lx
117 index = (l-1) + lx*(k-1) + lx*ly*(j-1) + lx*ly*lz*(i-1) + 1
118 this%data_sp(i,l,k,j) = real(x(index), sp)
119 end do
120 end do
121 end do
122 end do
123 end if
124
125 end subroutine buffer_4d_fill
126
127#ifdef HAVE_ADIOS2_FORTRAN
128
129 subroutine buffer_4d_define(this, variable, io, variable_name, ierr)
130 class(buffer_4d_t), intent(inout) :: this
131 type(adios2_variable), intent(inout) :: variable
132 type(adios2_io), intent(inout) :: io
133 character(len=*), intent(in) :: variable_name
134 integer, intent(inout) :: ierr
135 integer :: adios2_type
136
137 if (this%dp_precision) then
138 adios2_type = adios2_type_dp
139 else
140 adios2_type = adios2_type_real
141 end if
142
143 call adios2_inquire_variable(variable, io, trim(variable_name), ierr)
144 if (.not.variable%valid) then
146 call adios2_define_variable(variable, io, variable_name, adios2_type, &
147 size(this%shape_dims), this%shape_dims, this%start_dims, &
148 this%count_dims, .false., ierr)
149 else
150 call adios2_set_selection(variable, size(this%start_dims), &
151 this%start_dims, this%count_dims, ierr)
152 end if
153
154 end subroutine buffer_4d_define
155
156 subroutine buffer_4d_inquire(this, variable, io, variable_name, ierr)
157 class(buffer_4d_t), intent(inout) :: this
158 type(adios2_variable), intent(inout) :: variable
159 type(adios2_io), intent(inout) :: io
160 character(len=*), intent(in) :: variable_name
161 integer, intent(inout) :: ierr
162
163 call adios2_inquire_variable(variable, io, trim(variable_name), ierr)
164 if (variable%valid) then
165 call adios2_set_selection(variable, size(this%start_dims), &
166 this%start_dims, this%count_dims, ierr)
167 end if
168
169 end subroutine buffer_4d_inquire
170
171 subroutine buffer_4d_write(this, engine, variable, ierr)
172 class(buffer_4d_t), intent(inout) :: this
173 type(adios2_engine), intent(in) :: engine
174 type(adios2_variable), intent(in) :: variable
175 integer, intent(inout) :: ierr
176
177 if (this%dp_precision) then
178 call adios2_put(engine, variable, this%data_dp, adios2_mode_sync, ierr)
179 else
180 call adios2_put(engine, variable, this%data_sp, adios2_mode_sync, ierr)
181 end if
182
183 end subroutine buffer_4d_write
184
185 subroutine buffer_4d_read(this, engine, variable, ierr)
186 class(buffer_4d_t), intent(inout) :: this
187 type(adios2_engine), intent(in) :: engine
188 type(adios2_variable), intent(in) :: variable
189 integer, intent(inout) :: ierr
190
191 if (this%dp_precision) then
192 call adios2_get(engine, variable, this%data_dp, adios2_mode_sync, ierr)
193 else
194 call adios2_get(engine, variable, this%data_sp, adios2_mode_sync, ierr)
195 end if
196
197 end subroutine buffer_4d_read
198
199#endif
200
201 subroutine buffer_4d_copy(this, x)
202 class(buffer_4d_t), intent(inout) :: this
203 type(vector_t), intent(inout) :: x
204 integer :: i, j, k, l, nelv, lx, ly, lz, index
205
206 nelv = this%count_dims(1)
207 lx = this%count_dims(2)
208 ly = this%count_dims(3)
209 lz = this%count_dims(4)
210
211 if (this%dp_precision) then
212 do i = 1, nelv
213 do j = 1, lz
214 do k = 1, ly
215 do l = 1, lx
216 index = (l-1) + lx*(k-1) + lx*ly*(j-1) + lx*ly*lz*(i-1) + 1
217 x%x(index) = this%data_dp(i,l,k,j)
218 end do
219 end do
220 end do
221 end do
222 else
223 do i = 1, nelv
224 do j = 1, lz
225 do k = 1, ly
226 do l = 1, lx
227 index = (l-1) + lx*(k-1) + lx*ly*(j-1) + lx*ly*lz*(i-1) + 1
228 x%x(index) = this%data_sp(i,l,k,j)
229 end do
230 end do
231 end do
232 end do
233 end if
234
235 end subroutine buffer_4d_copy
236
237end module buffer_4d
double real
Generic buffer that is extended with buffers of varying rank.
Definition buffer_4d.F90:34
subroutine buffer_4d_copy(this, x)
subroutine buffer_4d_fill(this, x, n)
Definition buffer_4d.F90:91
subroutine buffer_4d_init(this, precision, gdim, glb_nelv, offset_el, nelv, lx, ly, lz)
Definition buffer_4d.F90:63
Generic buffer that is extended with buffers of varying rank.
Definition buffer.F90:34
subroutine buffer_set_precision(this, precision)
Definition buffer.F90:112
integer, parameter, public i8
Definition num_types.f90:7
integer, parameter, public dp
Definition num_types.f90:9
integer, parameter, public sp
Definition num_types.f90:8
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Defines a vector.
Definition vector.f90:34