Skip to content

Commit 18c15e5

Browse files
committed
logical strings can now be user-specified for writing.
1 parent d33f65f commit 18c15e5

File tree

3 files changed

+42
-17
lines changed

3 files changed

+42
-17
lines changed

src/csv_module.f90

Lines changed: 39 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -51,11 +51,19 @@ module csv_module
5151

5252
!for writing a csv file:
5353
integer :: icol = 0 !! last column written in current row
54-
integer :: iunit = 0 !! file unit for writing
54+
integer :: iunit = 0 !! file unit for writing
5555
logical :: enclose_strings_in_quotes = .true. !! if true, all string cells
5656
!! will be enclosed in quotes.
57-
logical :: enclose_all_in_quotes = .false. !! if true, *all* cells will
58-
!! be enclosed in quotes.
57+
logical :: enclose_all_in_quotes = .false. !! if true, *all* cells will
58+
!! be enclosed in quotes.
59+
character(len=1) :: logical_true_string = 'T' !! when writing a logical `true`
60+
!! value to a CSV file, this
61+
!! is the string to use
62+
!! (default is `T`)
63+
character(len=1) :: logical_false_string = 'F' !! when writing a logical `false`
64+
!! value to a CSV file, this
65+
!! is the string to use
66+
!! (default is `F`)
5967

6068
contains
6169

@@ -118,6 +126,8 @@ module csv_module
118126
subroutine initialize_csv_file(me,quote,delimiter,&
119127
enclose_strings_in_quotes,&
120128
enclose_all_in_quotes,&
129+
logical_true_string,&
130+
logical_false_string,&
121131
verbose)
122132

123133
implicit none
@@ -129,6 +139,14 @@ subroutine initialize_csv_file(me,quote,delimiter,&
129139
!! will be enclosed in quotes.
130140
logical,intent(in),optional :: enclose_all_in_quotes !! if true, *all* cells will
131141
!! be enclosed in quotes.
142+
character(len=1),intent(in),optional :: logical_true_string !! when writing a logical `true`
143+
!! value to a CSV file, this
144+
!! is the string to use
145+
!! (default is `T`)
146+
character(len=1),intent(in),optional :: logical_false_string !! when writing a logical `false`
147+
!! value to a CSV file, this
148+
!! is the string to use
149+
!! (default is `F`)
132150
logical,intent(in),optional :: verbose
133151

134152
if (present(quote)) me%quote = quote
@@ -137,6 +155,10 @@ subroutine initialize_csv_file(me,quote,delimiter,&
137155
me%enclose_strings_in_quotes = enclose_strings_in_quotes
138156
if (present(enclose_all_in_quotes)) &
139157
me%enclose_all_in_quotes = enclose_all_in_quotes
158+
if (present(logical_true_string)) &
159+
me%logical_true_string = logical_true_string
160+
if (present(logical_false_string)) &
161+
me%logical_false_string = logical_false_string
140162
if (present(verbose)) me%verbose = verbose
141163

142164
end subroutine initialize_csv_file
@@ -176,6 +198,9 @@ subroutine read_csv_file(me,filename,header_row,skip_rows,status_ok)
176198
integer,intent(in),optional :: header_row !! the header row
177199
integer,dimension(:),intent(in),optional :: skip_rows !! rows to skip
178200

201+
type(csv_string),dimension(:),allocatable :: row_data !! a tokenized row
202+
integer,dimension(:),allocatable :: rows_to_skip !! the actual rows to skip
203+
character(len=:),allocatable :: line !! a line from the file
179204
integer :: i !! counter
180205
integer :: j !! counter
181206
integer :: irow !! row counter
@@ -184,11 +209,10 @@ subroutine read_csv_file(me,filename,header_row,skip_rows,status_ok)
184209
integer :: n_cols !! number of columns in the file (and output data matrix)
185210
integer :: istat !! open status flag
186211
integer :: iunit !! open file unit
187-
integer,dimension(:),allocatable :: rows_to_skip !! the actual rows to skip
188-
logical :: arrays_allocated !! if the arrays in the class have been allocated
189-
type(csv_string),dimension(:),allocatable :: row_data !! a tokenized row
190-
character(len=:),allocatable :: line !! a line from the file
191-
integer :: iheader !! row number of header row (0 if no header specified)
212+
logical :: arrays_allocated !! if the arrays in the
213+
!! class have been allocated
214+
integer :: iheader !! row number of header row
215+
!! (0 if no header specified)
192216

193217
call me%destroy()
194218
arrays_allocated = .false.
@@ -264,7 +288,8 @@ subroutine read_csv_file(me,filename,header_row,skip_rows,status_ok)
264288
status_ok = .true.
265289

266290
else
267-
if (me%verbose) write(error_unit,'(A)') 'Error opening file: '//trim(filename)
291+
if (me%verbose) write(error_unit,'(A)') &
292+
'Error opening file: '//trim(filename)
268293
status_ok = .false.
269294
end if
270295

@@ -354,7 +379,7 @@ subroutine add_cell(me,val,int_fmt,real_fmt,trim_str)
354379

355380
integer :: istat !! write `iostat` flag
356381
character(len=:),allocatable :: ifmt !! actual format string to use for integers
357-
character(len=:),allocatable :: rfmt !! actual format string to use for REALS
382+
character(len=:),allocatable :: rfmt !! actual format string to use for reals
358383
logical :: trimstr !! if the strings are to be trimmed
359384
character(len=max_real_str_len) :: real_val
360385
character(len=max_integer_str_len) :: int_val
@@ -389,9 +414,9 @@ subroutine add_cell(me,val,int_fmt,real_fmt,trim_str)
389414
write(me%iunit,fmt='(A)',advance='NO',iostat=istat) trim(adjustl(real_val))
390415
type is (logical)
391416
if (val) then
392-
write(me%iunit,fmt='(A)',advance='NO',iostat=istat) 'T' !TODO make these user-defined strings
417+
write(me%iunit,fmt='(A)',advance='NO',iostat=istat) me%logical_true_string
393418
else
394-
write(me%iunit,fmt='(A)',advance='NO',iostat=istat) 'F'
419+
write(me%iunit,fmt='(A)',advance='NO',iostat=istat) me%logical_false_string
395420
end if
396421
type is (character(len=*))
397422
if (me%enclose_strings_in_quotes .and. .not. me%enclose_all_in_quotes) &
@@ -709,7 +734,7 @@ pure elemental subroutine to_logical(str,val,status_ok)
709734
if ( any(tmp==true_str) ) then
710735
val = .true.
711736
status_ok = .true.
712-
elseif ( any(tmp==false_str) ) then
737+
else if ( any(tmp==false_str) ) then
713738
val = .false.
714739
status_ok = .true.
715740
else
@@ -1121,7 +1146,7 @@ subroutine read_line_from_file(me,iunit,line)
11211146
! add the last block of text before the end of record
11221147
if (nread>0) line = line//buffer(1:nread)
11231148
exit
1124-
elseif (istat==0) then ! all the characters were read
1149+
else if (istat==0) then ! all the characters were read
11251150
line = line//buffer ! add this block of text to the string
11261151
else ! some kind of error
11271152
error stop 'Read error.'

src/tests/csv_test.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,8 +18,8 @@ program csv_test
1818
character(len=30),dimension(:,:),allocatable :: csv_data !! the data from the file as strings
1919

2020
real(wp),dimension(:),allocatable :: x
21-
real(wp),dimension(:),allocatable :: y
22-
real(wp),dimension(:),allocatable :: z
21+
!real(wp),dimension(:),allocatable :: y
22+
!real(wp),dimension(:),allocatable :: z
2323
logical :: status_ok
2424
integer,dimension(:),allocatable :: itypes
2525

src/utilities_module.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -170,7 +170,7 @@ recursive subroutine quicksort(ilow,ihigh)
170170
end do
171171
end do
172172

173-
elseif ( ihigh-ilow>max_size_for_insertion_sort ) then
173+
else if ( ihigh-ilow>max_size_for_insertion_sort ) then
174174

175175
! do the normal quicksort:
176176
call partition(ilow,ihigh,ipivot)

0 commit comments

Comments
 (0)