37#ifdef HAVE_ADIOS2_FORTRAN
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(:)
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
61 subroutine buffer_1d_init(this, precision, gdim, glb_nelv, offset_el, nelv, &
64 logical,
intent(in) :: precision
65 integer,
intent(in) :: gdim, glb_nelv, offset_el, nelv, lx, ly, lz
72 if (this%dp_precision)
then
73 if (
allocated(this%data_dp))
then
74 deallocate(this%data_dp)
76 allocate(this%data_dp(gdim*nelv*lxyz))
78 if (
allocated(this%data_sp))
then
79 deallocate(this%data_sp)
81 allocate(this%data_sp(gdim*nelv*lxyz))
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))
92 integer,
intent(inout) :: n
93 real(kind=
rp),
intent(inout) :: x(n)
96 if (this%dp_precision)
then
98 this%data_dp(i) =
real(x(i),
dp)
102 this%data_sp(i) =
real(x(i),
sp)
108#ifdef HAVE_ADIOS2_FORTRAN
110 subroutine buffer_1d_define(this, variable, io, variable_name, ierr)
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
118 if (this%dp_precision)
then
119 adios2_type = adios2_type_dp
121 adios2_type = adios2_type_real
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)
131 call adios2_set_selection(variable,
size(this%start_dims), &
132 this%start_dims, this%count_dims, ierr)
135 end subroutine buffer_1d_define
137 subroutine buffer_1d_inquire(this, variable, io, variable_name, ierr)
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
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)
150 end subroutine buffer_1d_inquire
152 subroutine buffer_1d_write(this, engine, variable, ierr)
154 type(adios2_engine),
intent(in) :: engine
155 type(adios2_variable),
intent(in) :: variable
156 integer,
intent(inout) :: ierr
158 if (this%dp_precision)
then
159 call adios2_put(engine, variable, this%data_dp, adios2_mode_sync, ierr)
161 call adios2_put(engine, variable, this%data_sp, adios2_mode_sync, ierr)
164 end subroutine buffer_1d_write
166 subroutine buffer_1d_read(this, engine, variable, ierr)
168 type(adios2_engine),
intent(in) :: engine
169 type(adios2_variable),
intent(in) :: variable
170 integer,
intent(inout) :: ierr
172 if (this%dp_precision)
then
173 call adios2_get(engine, variable, this%data_dp, adios2_mode_sync, ierr)
175 call adios2_get(engine, variable, this%data_sp, adios2_mode_sync, ierr)
178 end subroutine buffer_1d_read
189 if (this%dp_precision)
then
191 x%x(i) = this%data_dp(i)
195 x%x(i) = this%data_sp(i)
Generic buffer that is extended with buffers of varying rank.
subroutine buffer_1d_copy(this, x)
subroutine buffer_1d_init(this, precision, gdim, glb_nelv, offset_el, nelv, lx, ly, lz)
subroutine buffer_1d_fill(this, x, n)
Generic buffer that is extended with buffers of varying rank.
subroutine buffer_set_precision(this, precision)
integer, parameter, public i8
integer, parameter, public dp
integer, parameter, public sp
integer, parameter, public rp
Global precision used in computations.