Neko  0.8.99
A portable framework for high-order spectral element flow simulations
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 !
35 module csv_file
36  use vector, only: vector_t
37  use matrix, only: matrix_t
38  use generic_file, only: generic_file_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 
59 contains
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
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  write (file_unit, '(*(g0,","))', advance = "no") data%x(1:data%n-1)
140  write (file_unit,'(g0)') data%x(data%n)
141 
142  close(file_unit)
143 
144  end subroutine csv_file_write_vector
145 
151  subroutine csv_file_write_matrix(f, data, t)
152  class(csv_file_t), intent(inout) :: f
153  type(matrix_t), intent(in) :: data
154  real(kind=rp), intent(in), optional :: t
155  integer :: file_unit, i, ierr
156 
157  open(file = trim(f%fname), position = "append", iostat = ierr, &
158  newunit = file_unit)
159  if (ierr .ne. 0) call neko_error("Error while opening " // trim(f%fname))
160 
161  ! write header if not empty and if not already written
162  if (f%header .ne. "" .and. .not. f%header_is_written) then
163  write (file_unit, '(A)') trim(f%header)
164  f%header_is_written = .true.
165  end if
166 
167  do i = 1, data%nrows
168  if (present(t)) write (file_unit, '(g0,",")', advance = "no") t
169  write (file_unit, '(*(g0,","))', advance = "no") &
170  data%x(i, 1:data%ncols-1)
171  write (file_unit, '(g0)') data%x(i, data%ncols)
172  end do
173 
174  close(file_unit)
175 
176  end subroutine csv_file_write_matrix
177 
181  subroutine csv_file_read(this, data)
182  class(csv_file_t) :: this
183  class(*), target, intent(inout) :: data
184  type(vector_t), pointer :: vec
185  type(matrix_t), pointer :: mat
186 
187  call this%check_exists()
188 
189  nullify(vec)
190  nullify(mat)
191 
192  select type (data)
193  type is (vector_t)
194  vec => data
195  if (.not. allocated(data%x)) then
196  call neko_error("Vector is not allocated. Use &
197 &vector%init() to associate your array &
198 &with a vector_t object")
199  end if
200 
201  type is (matrix_t)
202  mat => data
203  if (.not. allocated(data%x)) then
204  call neko_error("Matrix is not allocated. Use &
205 &matrix%init() to associate your array &
206 &with a matrix_t object")
207  end if
208 
209 
210  class default
211  call neko_error("Invalid data type for csv_file (expected: vector_t, &
212 &matrix_t)")
213  end select
214 
215  if (pe_rank .eq. 0) then
216 
217  call neko_log%newline()
218  call neko_log%message("Reading csv file " // trim(this%fname))
219  if (associated(vec)) then
220  call csv_file_read_vector(this, vec)
221  else if (associated(mat)) then
222  call csv_file_read_matrix(this, mat)
223  end if
224 
225  end if
226 
227  end subroutine csv_file_read
228 
236  subroutine csv_file_read_vector(f, vec)
237  type(csv_file_t), intent(inout) :: f
238  type(vector_t), intent(inout) :: vec
239  integer :: ierr, file_unit, n_lines
240  character(len=80) :: tmp
241 
242  n_lines = f%count_lines()
243 
244  open(file = trim(f%fname), status = 'old', newunit = file_unit, &
245  iostat = ierr)
246  if (ierr .ne. 0) call neko_error("Error while opening " // trim(f%fname))
247 
248  ! If there is more than 1 line, assume that means there is a header
249  if (n_lines .gt. 1) then
250  read (file_unit, '(A)') tmp
251  f%header = trim(tmp)
252  end if
253 
254  read (file_unit,*) vec%x
255  close(unit = file_unit)
256 
257 
258  end subroutine csv_file_read_vector
259 
265  subroutine csv_file_read_matrix(f, mat)
266  type(csv_file_t), intent(inout) :: f
267  type(matrix_t), intent(inout) :: mat
268  integer :: ierr, file_unit, i, n_lines
269  character(len=80) :: tmp
270 
271  n_lines = f%count_lines()
272 
273  open(file = trim(f%fname), status = 'old', newunit = file_unit, &
274  iostat = ierr)
275  if (ierr .ne. 0) call neko_error("Error while opening " // trim(f%fname))
276 
277  ! If the number of lines is larger than the number of rows in the
278  ! matrix, assume that means there is a header
279  if (n_lines .gt. mat%nrows) then
280  read (file_unit, '(A)') tmp
281  f%header = trim(tmp)
282  end if
283 
284  do i = 1, mat%nrows
285  read (file_unit,*) mat%x(i,:)
286  end do
287  close(unit = file_unit)
288 
289  end subroutine csv_file_read_matrix
290 
295  subroutine csv_file_set_header(this, hd)
296  class(csv_file_t), intent(inout) :: this
297  character(len=*), intent(in) :: hd
298 
299  this%header = trim(hd)
300 
301  end subroutine csv_file_set_header
302 
305  function csv_file_count_lines(this) result(n)
306  class(csv_file_t), intent(in) :: this
307 
308  integer :: n
309  integer :: ierr, file_unit
310 
311  open(file = trim(this%fname), status = 'old', newunit = file_unit)
312  rewind(file_unit)
313 
314  n = 0
315 
316  ! Keep reading (ierr = 0) until we reach the end (ierr != 0)
317  do
318  read (file_unit, *, iostat = ierr)
319  if (ierr .ne. 0) exit
320  n = n + 1
321  end do
322  rewind(file_unit)
323  close(unit = file_unit)
324 
325  end function csv_file_count_lines
326 
327 
328 end module csv_file
Definition: comm.F90:1
integer pe_rank
MPI rank.
Definition: comm.F90:26
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:296
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:152
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:182
subroutine csv_file_read_matrix(f, mat)
Read a matrix from a csv file.
Definition: csv_file.f90:266
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:306
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:237
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:61
integer, parameter, public log_size
Definition: log.f90:40
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.