Neko 1.99.1
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
csv_file.f90
Go to the documentation of this file.
1! Copyright (c) 2020-2024, 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!
36 use vector, only: vector_t
37 use matrix, only: matrix_t
39 use utils, only: neko_error
40 use num_types, only: rp
41 use logger, only: neko_log, log_size
42 use comm
43 implicit none
44
45 type, public, extends(generic_file_t) :: csv_file_t
46 character(len=1024) :: header = ""
47 logical :: header_is_written = .false.
48 contains
50 procedure :: write => csv_file_write
52 procedure :: read => csv_file_read
54 procedure :: set_header => csv_file_set_header
56 procedure :: count_lines => csv_file_count_lines
57 end type csv_file_t
58
59contains
60
65 subroutine csv_file_write(this, data, t)
66 class(csv_file_t), intent(inout) :: this
67 class(*), target, intent(in) :: data
68 real(kind=rp), intent(in), optional :: t
69
70 type(vector_t), pointer :: vec
71 type(matrix_t), pointer :: mat
72
73 nullify(vec)
74 nullify(mat)
75
76 select type (data)
77 type is (vector_t)
78 if (.not. allocated(data%x)) then
79 call neko_error("Vector is not allocated. Use &
80 &vector%init() to associate your array &
81 &with a vector_t object")
82 end if
83 vec => data
84
85 type is (matrix_t)
86 if (.not. allocated(data%x)) then
87 call neko_error("Matrix is not allocated. Use &
88 &matrix%init() to associate your array &
89 &with a matrix_t object")
90 end if
91 mat => data
92
93 class default
94 call neko_error("Invalid data. Expected vector_t or &
95 &matrix_t")
96 end select
97
98 ! Write is performed on rank 0
99 if (pe_rank .eq. 0) then
100
101 call neko_log%message("Writing to " // trim(this%fname))
102 if (associated(vec)) then
103 call csv_file_write_vector(this, vec, t)
104 else if (associated(mat)) then
105 call csv_file_write_matrix(this, mat, t)
106 end if
107
108 end if
109
110 end subroutine csv_file_write
111
120 subroutine csv_file_write_vector(f, data, t)
121 class(csv_file_t), intent(inout) :: f
122 type(vector_t), intent(in) :: data
123 real(kind=rp), intent(in), optional :: t
124 integer :: file_unit, ierr, n
125
126 open(file = trim(f%fname), position = "append", iostat = ierr, &
127 newunit = file_unit)
128 if (ierr .ne. 0) call neko_error("Error while opening " // trim(f%fname))
129
130 ! write header if not empty and if not already written
131 if (f%header .ne. "" .and. .not. f%header_is_written) then
132 write (file_unit, '(A)') trim(f%header)
133 f%header_is_written = .true.
134 end if
135
136 ! Add time at the beginning if specified
137 if (present(t)) write (file_unit, '(g0,",")', advance = "no") t
138
139 n = data%size()
140 write (file_unit, '(*(g0,","))', advance = "no") data%x(1:n-1)
141 write (file_unit,'(g0)') data%x(n)
142
143 close(file_unit)
144
145 end subroutine csv_file_write_vector
146
152 subroutine csv_file_write_matrix(f, data, t)
153 class(csv_file_t), intent(inout) :: f
154 type(matrix_t), intent(in) :: data
155 real(kind=rp), intent(in), optional :: t
156 integer :: file_unit, i, ierr, nc
157
158 open(file = trim(f%fname), position = "append", iostat = ierr, &
159 newunit = file_unit)
160 if (ierr .ne. 0) call neko_error("Error while opening " // trim(f%fname))
161
162 ! write header if not empty and if not already written
163 if (f%header .ne. "" .and. .not. f%header_is_written) then
164 write (file_unit, '(A)') trim(f%header)
165 f%header_is_written = .true.
166 end if
167
168 do i = 1, data%get_nrows()
169 if (present(t)) write (file_unit, '(g0,",")', advance = "no") t
170 nc = data%get_ncols()
171 write (file_unit, '(*(g0,","))', advance = "no") &
172 data%x(i, 1:nc-1)
173 write (file_unit, '(g0)') data%x(i, nc)
174 end do
175
176 close(file_unit)
177
178 end subroutine csv_file_write_matrix
179
183 subroutine csv_file_read(this, data)
184 class(csv_file_t) :: this
185 class(*), target, intent(inout) :: data
186 type(vector_t), pointer :: vec
187 type(matrix_t), pointer :: mat
188
189 call this%check_exists()
190
191 nullify(vec)
192 nullify(mat)
193
194 select type (data)
195 type is (vector_t)
196 vec => data
197 if (.not. allocated(data%x)) then
198 call neko_error("Vector is not allocated. Use &
199 &vector%init() to associate your array &
200 &with a vector_t object")
201 end if
202
203 type is (matrix_t)
204 mat => data
205 if (.not. allocated(data%x)) then
206 call neko_error("Matrix is not allocated. Use &
207 &matrix%init() to associate your array &
208 &with a matrix_t object")
209 end if
210
211
212 class default
213 call neko_error("Invalid data type for csv_file (expected: vector_t, &
214 &matrix_t)")
215 end select
216
217 if (pe_rank .eq. 0) then
218
219 call neko_log%newline()
220 call neko_log%message("Reading csv file " // trim(this%fname))
221 if (associated(vec)) then
222 call csv_file_read_vector(this, vec)
223 else if (associated(mat)) then
224 call csv_file_read_matrix(this, mat)
225 end if
226
227 end if
228
229 end subroutine csv_file_read
230
238 subroutine csv_file_read_vector(f, vec)
239 type(csv_file_t), intent(inout) :: f
240 type(vector_t), intent(inout) :: vec
241 integer :: ierr, file_unit, n_lines
242 character(len=80) :: tmp
243
244 n_lines = f%count_lines()
245
246 open(file = trim(f%fname), status = 'old', newunit = file_unit, &
247 iostat = ierr)
248 if (ierr .ne. 0) call neko_error("Error while opening " // trim(f%fname))
249
250 ! If there is more than 1 line, assume that means there is a header
251 if (n_lines .gt. 1) then
252 read (file_unit, '(A)') tmp
253 f%header = trim(tmp)
254 end if
255
256 read (file_unit,*) vec%x
257 close(unit = file_unit)
258
259
260 end subroutine csv_file_read_vector
261
267 subroutine csv_file_read_matrix(f, mat)
268 type(csv_file_t), intent(inout) :: f
269 type(matrix_t), intent(inout) :: mat
270 integer :: ierr, file_unit, i, n_lines
271 character(len=80) :: tmp
272
273 n_lines = f%count_lines()
274
275 open(file = trim(f%fname), status = 'old', newunit = file_unit, &
276 iostat = ierr)
277 if (ierr .ne. 0) call neko_error("Error while opening " // trim(f%fname))
278
279 ! If the number of lines is larger than the number of rows in the
280 ! matrix, assume that means there is a header
281 if (n_lines .gt. mat%get_nrows()) then
282 read (file_unit, '(A)') tmp
283 f%header = trim(tmp)
284 end if
285
286 do i = 1, mat%get_nrows()
287 read (file_unit,*) mat%x(i,:)
288 end do
289 close(unit = file_unit)
290
291 end subroutine csv_file_read_matrix
292
297 subroutine csv_file_set_header(this, hd)
298 class(csv_file_t), intent(inout) :: this
299 character(len=*), intent(in) :: hd
300
301 this%header = trim(hd)
302
303 end subroutine csv_file_set_header
304
307 function csv_file_count_lines(this) result(n)
308 class(csv_file_t), intent(in) :: this
309
310 integer :: n
311 integer :: ierr, file_unit
312
313 call this%check_exists()
314
315 open(file = trim(this%fname), status = 'old', newunit = file_unit, &
316 iostat = ierr)
317 if (ierr .ne. 0) call neko_error("Error while opening " // trim(this%fname))
318 rewind(file_unit)
319
320 n = 0
321
322 ! Keep reading (ierr = 0) until we reach the end (ierr != 0)
323 do
324 read (file_unit, *, iostat = ierr)
325 if (ierr .ne. 0) exit
326 n = n + 1
327 end do
328 rewind(file_unit)
329 close(unit = file_unit)
330
331 end function csv_file_count_lines
332
333
334end module csv_file
Definition comm.F90:1
integer, public pe_rank
MPI rank.
Definition comm.F90:55
File format for .csv files, used for any read/write operations involving floating point data.
Definition csv_file.f90:35
subroutine csv_file_set_header(this, hd)
Sets the header for a csv file. For example: hd = "u,v,w,p".
Definition csv_file.f90:298
subroutine csv_file_write_matrix(f, data, t)
Writes a matrix_t object to an output file. If the parameter t is present, it will be appended at the...
Definition csv_file.f90:153
subroutine csv_file_write_vector(f, data, t)
Writes a vector_t object to an output file, in a row format. If the parameter t is present,...
Definition csv_file.f90:121
subroutine csv_file_write(this, data, t)
Writes data to an output file.
Definition csv_file.f90:66
subroutine csv_file_read(this, data)
Reads data from an input file.
Definition csv_file.f90:184
subroutine csv_file_read_matrix(f, mat)
Read a matrix from a csv file.
Definition csv_file.f90:268
integer function csv_file_count_lines(this)
Count the number of lines in a file by going through it entirely until the end is reached.
Definition csv_file.f90:308
subroutine csv_file_read_vector(f, vec)
Read a vector (i.e. data on a single row) from a csv file.
Definition csv_file.f90:239
Module for file I/O operations.
Definition file.f90:34
Logging routines.
Definition log.f90:34
type(log_t), public neko_log
Global log stream.
Definition log.f90:70
integer, parameter, public log_size
Definition log.f90:46
Defines a matrix.
Definition matrix.f90:34
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
Utilities.
Definition utils.f90:35
Defines a vector.
Definition vector.f90:34
A generic file handler.