Skip to content

Commit 3b15f03

Browse files
committed
some refactoring and new options.
1 parent 530e802 commit 3b15f03

File tree

5 files changed

+88
-81
lines changed

5 files changed

+88
-81
lines changed

src/kinds_module.f90 renamed to src/csv_kinds.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
!>
33
! Numeric kinds.
44

5-
module kinds_module
5+
module csv_kinds
66

77
use iso_fortran_env, only: real64,int32
88

@@ -11,5 +11,5 @@ module kinds_module
1111
integer,parameter,public :: wp = real64 !! default real kind
1212
integer,parameter,public :: ip = int32 !! default integer kind
1313

14-
end module kinds_module
14+
end module csv_kinds
1515
!*******************************************************************************

src/csv_module.f90

Lines changed: 44 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -6,9 +6,10 @@
66

77
module csv_module
88

9-
use utilities_module
10-
use kinds_module
11-
use iso_fortran_env
9+
use csv_utilities
10+
use csv_kinds
11+
use csv_parameters
12+
use iso_fortran_env, only: error_unit
1213

1314
implicit none
1415

@@ -24,6 +25,9 @@ module csv_module
2425

2526
type,public :: csv_string
2627
!! a cell from a CSV file.
28+
!!
29+
!! This use used to store the data internally
30+
!! in the [[csv_file]] class.
2731
private
2832
character(len=:),allocatable :: str
2933
end type csv_string
@@ -38,7 +42,7 @@ module csv_module
3842

3943
private
4044

41-
logical :: verbose = .true. !! to print error messages
45+
logical :: verbose = .false. !! to print error messages
4246

4347
character(len=1) :: quote = '"' !! quotation character
4448
character(len=1) :: delimiter = ',' !! delimiter character
@@ -128,17 +132,22 @@ subroutine initialize_csv_file(me,quote,delimiter,&
128132
enclose_all_in_quotes,&
129133
logical_true_string,&
130134
logical_false_string,&
135+
chunk_size,&
131136
verbose)
132137

133138
implicit none
134139

135140
class(csv_file),intent(out) :: me
136141
character(len=1),intent(in),optional :: quote !! note: can only be one character
142+
!! (Default is `"`)
137143
character(len=1),intent(in),optional :: delimiter !! note: can only be one character
144+
!! (Default is `,`)
138145
logical,intent(in),optional :: enclose_strings_in_quotes !! if true, all string cells
139146
!! will be enclosed in quotes.
147+
!! (Default is True)
140148
logical,intent(in),optional :: enclose_all_in_quotes !! if true, *all* cells will
141149
!! be enclosed in quotes.
150+
!! (Default is False)
142151
character(len=1),intent(in),optional :: logical_true_string !! when writing a logical `true`
143152
!! value to a CSV file, this
144153
!! is the string to use
@@ -147,7 +156,10 @@ subroutine initialize_csv_file(me,quote,delimiter,&
147156
!! value to a CSV file, this
148157
!! is the string to use
149158
!! (default is `F`)
150-
logical,intent(in),optional :: verbose
159+
integer,intent(in),optional :: chunk_size !! factor for expanding vectors
160+
!! (default is 100)
161+
logical,intent(in),optional :: verbose !! print error messages to the
162+
!! console (default is False)
151163

152164
if (present(quote)) me%quote = quote
153165
if (present(delimiter)) me%delimiter = delimiter
@@ -160,6 +172,10 @@ subroutine initialize_csv_file(me,quote,delimiter,&
160172
if (present(logical_false_string)) &
161173
me%logical_false_string = logical_false_string
162174
if (present(verbose)) me%verbose = verbose
175+
if (present(chunk_size)) me%chunk_size = chunk_size
176+
177+
! override:
178+
if (me%enclose_all_in_quotes) me%enclose_strings_in_quotes = .true.
163179

164180
end subroutine initialize_csv_file
165181
!*****************************************************************************************
@@ -299,21 +315,17 @@ end subroutine read_csv_file
299315

300316
!*****************************************************************************************
301317
!>
302-
! Open a CSV file for writing
318+
! Open a CSV file for writing.
319+
!
320+
! Use `initialize` to set options for the CSV file.
303321

304-
subroutine open_csv_file(me,filename,&
305-
n_cols,&
306-
enclose_strings_in_quotes,&
307-
enclose_all_in_quotes,&
308-
status_ok)
322+
subroutine open_csv_file(me,filename,n_cols,status_ok)
309323

310324
implicit none
311325

312326
class(csv_file),intent(inout) :: me
313327
character(len=*),intent(in) :: filename !! the CSV file to open
314328
integer,intent(in) :: n_cols !! number of columns in the file
315-
logical,intent(in),optional :: enclose_strings_in_quotes !! default is true
316-
logical,intent(in),optional :: enclose_all_in_quotes !! default is false
317329
logical,intent(out) :: status_ok !! status flag
318330

319331
integer :: istat !! open `iostat` flag
@@ -322,18 +334,6 @@ subroutine open_csv_file(me,filename,&
322334

323335
me%n_cols = n_cols
324336

325-
if (present(enclose_strings_in_quotes)) then
326-
me%enclose_strings_in_quotes = enclose_strings_in_quotes
327-
else
328-
me%enclose_strings_in_quotes = .true.
329-
end if
330-
if (present(enclose_all_in_quotes)) then
331-
me%enclose_all_in_quotes = enclose_all_in_quotes
332-
else
333-
me%enclose_all_in_quotes = .false.
334-
end if
335-
if (me%enclose_all_in_quotes) me%enclose_strings_in_quotes = .true. ! override
336-
337337
open(newunit=me%iunit,file=filename,status='REPLACE',iostat=istat)
338338
if (istat==0) then
339339
status_ok = .true.
@@ -367,25 +367,27 @@ end subroutine close_csv_file
367367
!*****************************************************************************************
368368
!>
369369
! Add a cell to a CSV file.
370+
!
371+
!@todo Need to check the `istat` values for errors.
370372

371373
subroutine add_cell(me,val,int_fmt,real_fmt,trim_str)
372374

373375
implicit none
374376

375377
class(csv_file),intent(inout) :: me
376378
class(*),intent(in) :: val !! the value to add
377-
character(len=*),intent(in),optional :: int_fmt !! format string for integers
378-
character(len=*),intent(in),optional :: real_fmt !! format string for reals
379-
logical,intent(in),optional :: trim_str !! to trim the string
379+
character(len=*),intent(in),optional :: int_fmt !! if `val` is an integer, use
380+
!! this format string.
381+
character(len=*),intent(in),optional :: real_fmt !! if `val` is a real, use
382+
!! this format string.
383+
logical,intent(in),optional :: trim_str !! if `val` is a string, then trim it.
380384

381385
integer :: istat !! write `iostat` flag
382386
character(len=:),allocatable :: ifmt !! actual format string to use for integers
383387
character(len=:),allocatable :: rfmt !! actual format string to use for reals
384388
logical :: trimstr !! if the strings are to be trimmed
385-
character(len=max_real_str_len) :: real_val
386-
character(len=max_integer_str_len) :: int_val
387-
388-
!TODO need to check the istat values for errors
389+
character(len=max_real_str_len) :: real_val !! for writing a real value
390+
character(len=max_integer_str_len) :: int_val !! for writing an integer value
389391

390392
! make sure the row isn't already finished
391393
if (me%icol<me%n_cols) then
@@ -479,9 +481,11 @@ subroutine add_vector(me,val,int_fmt,real_fmt,trim_str)
479481

480482
class(csv_file),intent(inout) :: me
481483
class(*),dimension(:),intent(in) :: val !! the values to add
482-
character(len=*),intent(in),optional :: int_fmt !! format string for integers
483-
character(len=*),intent(in),optional :: real_fmt !! format string for reals
484-
logical,intent(in),optional :: trim_str !! to trim the string
484+
character(len=*),intent(in),optional :: int_fmt !! if `val` is an integer, use
485+
!! this format string.
486+
character(len=*),intent(in),optional :: real_fmt !! if `val` is a real, use
487+
!! this format string.
488+
logical,intent(in),optional :: trim_str !! if `val` is a string, then trim it.
485489

486490
integer :: i !! counter
487491

@@ -504,9 +508,11 @@ subroutine add_matrix(me,val,int_fmt,real_fmt,trim_str)
504508

505509
class(csv_file),intent(inout) :: me
506510
class(*),dimension(:,:),intent(in) :: val !! the values to add
507-
character(len=*),intent(in),optional :: int_fmt !! format string for integers
508-
character(len=*),intent(in),optional :: real_fmt !! format string for reals
509-
logical,intent(in),optional :: trim_str !! to trim the string
511+
character(len=*),intent(in),optional :: int_fmt !! if `val` is an integer, use
512+
!! this format string.
513+
character(len=*),intent(in),optional :: real_fmt !! if `val` is a real, use
514+
!! this format string.
515+
logical,intent(in),optional :: trim_str !! if `val` is a string, then trim it.
510516

511517
integer :: i !! counter
512518

src/csv_parameters.f90

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
!*******************************************************************************
2+
!>
3+
! Various parameters.
4+
5+
module csv_parameters
6+
7+
use csv_kinds
8+
9+
private
10+
11+
integer(ip),parameter,public :: max_real_str_len = 27 !! maximum string length of a real number
12+
character(len=*),parameter,public :: default_real_fmt = '(E27.17E4)'
13+
!! default real number format statement (for writing real values to strings and files).
14+
15+
integer(ip),parameter,public :: max_integer_str_len = 256 !! maximum string length of an integer.
16+
character(len=*),parameter,public :: default_int_fmt = '(I256)'
17+
!! default integer number format statement (for writing real values to strings and files).
18+
19+
end module csv_parameters
20+
!*******************************************************************************

src/utilities_module.f90 renamed to src/csv_utilities.f90

Lines changed: 4 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -3,34 +3,15 @@
33
!
44
! Utility routines.
55

6-
module utilities_module
6+
module csv_utilities
77

8-
use kinds_module
8+
use csv_kinds
9+
use csv_parameters
910

1011
private
1112

1213
integer,parameter :: max_size_for_insertion_sort = 20 !! max size for using insertion sort.
1314

14-
character(len=*),parameter,public :: default_real_fmt = '(E27.17E4)'
15-
!! default real number format statement (for writing real values to strings and files).
16-
character(len=*),parameter,public :: default_int_fmt = '(I256)'
17-
!! minimum width format for integers
18-
integer(ip),parameter :: rp_safety_factor = 1_ip
19-
integer(ip),parameter :: rp_addl_safety = 2_ip
20-
integer(ip),parameter :: real_precision = rp_safety_factor*precision(1.0_wp) + &
21-
rp_addl_safety
22-
integer(ip),parameter :: maxexp = maxexponent(1.0_wp)
23-
integer(ip),parameter :: minexp = minexponent(1.0_wp)
24-
integer(ip),parameter :: real_exponent_digits = floor( 1 + log10( &
25-
real(max(maxexp,abs(maxexp)),&
26-
kind=wp) ) )
27-
integer(ip),parameter,public :: max_real_str_len = real_precision + real_exponent_digits + 6
28-
!! maximum string length of a real number
29-
!! `6 = sign + leading 0 + decimal + 'E' + exponent sign + 1 extra`
30-
integer(ip),parameter,public :: max_integer_str_len = 256 !! maximum string length of an integer.
31-
!! This is totally arbitrary (any way
32-
!! to get the compiler to tell us this?)
33-
3415
character(len=*),parameter :: upper = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' !! uppercase characters
3516
character(len=*),parameter :: lower = 'abcdefghijklmnopqrstuvwxyz' !! lowercase characters
3617

@@ -277,5 +258,5 @@ end function lowercase_string
277258
!*******************************************************************************
278259

279260
!*******************************************************************************
280-
end module utilities_module
261+
end module csv_utilities
281262
!*******************************************************************************

src/tests/csv_test.f90

Lines changed: 18 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@
77
program csv_test
88

99
use csv_module
10-
use kinds_module
10+
use iso_fortran_env, only: wp => real64
1111

1212
implicit none
1313

@@ -16,12 +16,9 @@ program csv_test
1616
integer :: i !! counter
1717
character(len=30),dimension(:),allocatable :: header !! the header
1818
character(len=30),dimension(:,:),allocatable :: csv_data !! the data from the file as strings
19-
20-
real(wp),dimension(:),allocatable :: x
21-
!real(wp),dimension(:),allocatable :: y
22-
!real(wp),dimension(:),allocatable :: z
23-
logical :: status_ok
24-
integer,dimension(:),allocatable :: itypes
19+
real(wp),dimension(:),allocatable :: x !! for getting a real vector from a csv file
20+
logical :: status_ok !! error flag
21+
integer,dimension(:),allocatable :: itypes !! array of variable types in the file
2522

2623
! read the file:
2724
call f%read('../files/test.csv',header_row=1,status_ok=status_ok)
@@ -49,21 +46,24 @@ program csv_test
4946
write(*,*) ''
5047
write(*,*) 'age:'
5148
call f%get(3,x,status_ok)
52-
write(*,'(F27.16,1x)',advance='NO') x
49+
write(*,'(F6.3,1x)',advance='NO') x
5350
write(*,*) ''
5451

5552
! now test creating a CSV:
53+
call f2%initialize(enclose_strings_in_quotes=.false.,verbose=.true.)
5654
call f2%open('test2.csv',n_cols=4,status_ok=status_ok)
57-
call f2%add(['x','y','z','t']) ! add header as vector
58-
call f2%next_row()
59-
call f2%add(1.0_wp) ! add as scalars
60-
call f2%add(2.0_wp)
61-
call f2%add(3.0_wp)
62-
call f2%add(.true.)
63-
call f2%next_row()
64-
call f2%add([4.0_wp,5.0_wp,6.0_wp]) ! add as vectors
65-
call f2%add(.false.)
66-
call f2%next_row()
55+
if (status_ok) then
56+
call f2%add(['x','y','z','t']) ! add header as vector
57+
call f2%next_row()
58+
call f2%add(1.0_wp) ! add as scalars
59+
call f2%add(2.0_wp)
60+
call f2%add(3.0_wp)
61+
call f2%add(.true.)
62+
call f2%next_row()
63+
call f2%add([4.0_wp,5.0_wp,6.0_wp]) ! add as vectors
64+
call f2%add(.false.)
65+
call f2%next_row()
66+
end if
6767
call f2%close(status_ok)
6868

6969
end program csv_test

0 commit comments

Comments
 (0)