Neko 1.99.1
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
buffer_1d.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_1d_t
44 integer(kind=i8), dimension(1) :: 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_1d_init
49 procedure :: fill => buffer_1d_fill
50#ifdef HAVE_ADIOS2_FORTRAN
51 procedure :: define => buffer_1d_define
52 procedure :: inquire => buffer_1d_inquire
53 procedure :: write => buffer_1d_write
54 procedure :: read => buffer_1d_read
55#endif
56 procedure :: copy => buffer_1d_copy
57 end type buffer_1d_t
58
59contains
60
61 subroutine buffer_1d_init(this, precision, gdim, glb_nelv, offset_el, nelv, &
62 lx, ly, lz)
63 class(buffer_1d_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(gdim*nelv*lxyz))
77 else
78 if (allocated(this%data_sp)) then
79 deallocate(this%data_sp)
80 end if
81 allocate(this%data_sp(gdim*nelv*lxyz))
82 end if
83
84 this%shape_dims = (int(glb_nelv, i8) * int(lxyz, i8))
85 this%start_dims = (int(offset_el, i8) * int(lxyz, i8))
86 this%count_dims = (int(nelv, i8) * int(lxyz, i8))
87
88 end subroutine buffer_1d_init
89
90 subroutine buffer_1d_fill(this, x, n)
91 class(buffer_1d_t), intent(inout) :: this
92 integer, intent(inout) :: n
93 real(kind=rp), intent(inout) :: x(n)
94 integer :: i
95
96 if (this%dp_precision) then
97 do i = 1, n
98 this%data_dp(i) = real(x(i), dp)
99 end do
100 else
101 do i = 1, n
102 this%data_sp(i) = real(x(i), sp)
103 end do
104 end if
105
106 end subroutine buffer_1d_fill
107
108#ifdef HAVE_ADIOS2_FORTRAN
109
110 subroutine buffer_1d_define(this, variable, io, variable_name, ierr)
111 class(buffer_1d_t), intent(inout) :: this
112 type(adios2_variable), intent(inout) :: variable
113 type(adios2_io), intent(inout) :: io
114 character(len=*), intent(in) :: variable_name
115 integer, intent(inout) :: ierr
116 integer :: adios2_type
117
118 if (this%dp_precision) then
119 adios2_type = adios2_type_dp
120 else
121 adios2_type = adios2_type_real
122 end if
123
124 call adios2_inquire_variable(variable, io, trim(variable_name), ierr)
125 if (.not.variable%valid) then
127 call adios2_define_variable(variable, io, variable_name, adios2_type, &
128 size(this%shape_dims), this%shape_dims, this%start_dims, &
129 this%count_dims, .false., ierr)
130 else
131 call adios2_set_selection(variable, size(this%start_dims), &
132 this%start_dims, this%count_dims, ierr)
133 end if
134
135 end subroutine buffer_1d_define
136
137 subroutine buffer_1d_inquire(this, variable, io, variable_name, ierr)
138 class(buffer_1d_t), intent(inout) :: this
139 type(adios2_variable), intent(inout) :: variable
140 type(adios2_io), intent(inout) :: io
141 character(len=*), intent(in) :: variable_name
142 integer, intent(inout) :: ierr
143
144 call adios2_inquire_variable(variable, io, trim(variable_name), ierr)
145 if (variable%valid) then
146 call adios2_set_selection(variable, size(this%start_dims), &
147 this%start_dims, this%count_dims, ierr)
148 end if
149
150 end subroutine buffer_1d_inquire
151
152 subroutine buffer_1d_write(this, engine, variable, ierr)
153 class(buffer_1d_t), intent(inout) :: this
154 type(adios2_engine), intent(in) :: engine
155 type(adios2_variable), intent(in) :: variable
156 integer, intent(inout) :: ierr
157
158 if (this%dp_precision) then
159 call adios2_put(engine, variable, this%data_dp, adios2_mode_sync, ierr)
160 else
161 call adios2_put(engine, variable, this%data_sp, adios2_mode_sync, ierr)
162 end if
163
164 end subroutine buffer_1d_write
165
166 subroutine buffer_1d_read(this, engine, variable, ierr)
167 class(buffer_1d_t), intent(inout) :: this
168 type(adios2_engine), intent(in) :: engine
169 type(adios2_variable), intent(in) :: variable
170 integer, intent(inout) :: ierr
171
172 if (this%dp_precision) then
173 call adios2_get(engine, variable, this%data_dp, adios2_mode_sync, ierr)
174 else
175 call adios2_get(engine, variable, this%data_sp, adios2_mode_sync, ierr)
176 end if
177
178 end subroutine buffer_1d_read
179
180#endif
181
182 subroutine buffer_1d_copy(this, x)
183 class(buffer_1d_t), intent(inout) :: this
184 type(vector_t), intent(inout) :: x
185 integer :: n, i
186
187 n = x%size()
188
189 if (this%dp_precision) then
190 do i = 1, n
191 x%x(i) = this%data_dp(i)
192 end do
193 else
194 do i = 1, n
195 x%x(i) = this%data_sp(i)
196 end do
197 end if
198
199 end subroutine buffer_1d_copy
200
201end module buffer_1d
double real
Generic buffer that is extended with buffers of varying rank.
Definition buffer_1d.F90:34
subroutine buffer_1d_copy(this, x)
subroutine buffer_1d_init(this, precision, gdim, glb_nelv, offset_el, nelv, lx, ly, lz)
Definition buffer_1d.F90:63
subroutine buffer_1d_fill(this, x, n)
Definition buffer_1d.F90:91
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