csv_naive_parser.f90 Source File

StringiFor csv_naive_parser test.

This File Depends On

sourcefile~~csv_naive_parser.f90~~EfferentGraph sourcefile~csv_naive_parser.f90 csv_naive_parser.f90 sourcefile~stringifor.f90 stringifor.F90 sourcefile~stringifor.f90->sourcefile~csv_naive_parser.f90 sourcefile~penf.f90 penf.F90 sourcefile~penf.f90->sourcefile~stringifor.f90 sourcefile~stringifor_string_t.f90 stringifor_string_t.F90 sourcefile~penf.f90->sourcefile~stringifor_string_t.f90 sourcefile~befor64.f90 befor64.F90 sourcefile~penf.f90->sourcefile~befor64.f90 sourcefile~befor64_pack_data_m.f90 befor64_pack_data_m.F90 sourcefile~penf.f90->sourcefile~befor64_pack_data_m.f90 sourcefile~stringifor_string_t.f90->sourcefile~stringifor.f90 sourcefile~penf_b_size.f90 penf_b_size.F90 sourcefile~penf_b_size.f90->sourcefile~penf.f90 sourcefile~penf_stringify.f90 penf_stringify.F90 sourcefile~penf_b_size.f90->sourcefile~penf_stringify.f90 sourcefile~penf_global_parameters_variables.f90 penf_global_parameters_variables.F90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf.f90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_b_size.f90 sourcefile~penf_global_parameters_variables.f90->sourcefile~penf_stringify.f90 sourcefile~penf_stringify.f90->sourcefile~penf.f90 sourcefile~befor64.f90->sourcefile~stringifor_string_t.f90 sourcefile~befor64_pack_data_m.f90->sourcefile~befor64.f90
Help

Source Code


Source Code

!< StringiFor `csv_naive_parser` test.
program csv_naive_parser
!-----------------------------------------------------------------------------------------------------------------------------------
!< StringiFor `csv_naive_parser` test.
!<
!< This is an example of th usefulness of StringiFor.
!-----------------------------------------------------------------------------------------------------------------------------------
use stringifor
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
implicit none
type(string)              :: csv            !< The CSV file as a single stream.
type(string), allocatable :: rows(:)        !< The CSV table rows.
type(string), allocatable :: columns(:)     !< The CSV table columns.
type(string), allocatable :: cells(:,:)     !< The CSV table cells.
type(string)              :: lines(4)       !< The CSV file lines.
type(string)              :: most_expensive !< The most expensive car.
real(R8P)                 :: highest_cost   !< The highest cost.
integer                   :: rows_number    !< The CSV file rows number.
integer                   :: columns_number !< The CSV file columns number.
integer                   :: r              !< Counter.
logical                   :: test_passed(1) !< List of passed tests.
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
test_passed = .false.

! a cars database
lines(1) = 'Year,Make,Model,Description,Price'
lines(2) = '1997,Ford,E350,ac abs moon,3000.00'
lines(3) = '1999,Chevy,Venture "Extended Edition", ,4900.00'
lines(4) = '1999,Chevy,Venture "Extended Edition Very Large", ,5000.00'

! preparing a CSV file test
call write_file(file='file_test_temp.csv', lines=lines)

! parsing the just created CSV file
call csv%read_file(file='file_test_temp.csv')    ! read the CSV file as a single stream
call csv%split(tokens=rows, sep=new_line('a'))   ! get the CSV file rows
rows_number = size(rows, dim=1)                  ! get the CSV file rows number
columns_number = rows(1)%count(',') + 1          ! get the CSV file columns number
allocate(cells(1:columns_number, 1:rows_number)) ! allocate the CSV file cells
do r=1, rows_number                              ! parse all cells
  call rows(r)%split(tokens=columns, sep=',')    ! get current columns
  cells(1:columns_number, r) = columns           ! save current columns into cells
enddo

! eliminating the file
open(newunit=r, file='file_test_temp.csv') ; close(unit=r, status='DELETE')

! now you can do whatever with your parsed data
! print the table in markdown syntax
print "(A)", 'A markdown-formatted table'
print "(A)", ''
print "(A)", '|'//csv%join(array=cells(:, 1), sep='|')//'|'
columns = '----' ! re-use columns for printing separators
print "(A)", '|'//csv%join(array=columns, sep='|')//'|'
do r=2, rows_number
  print "(A)", '|'//csv%join(array=cells(:, r), sep='|')//'|'
enddo
print "(A)", ''
! find the most expensive car
print "(A)", 'Searching for the most expensive car'
most_expensive = 'unknown'
highest_cost = -1._R8P
do r=2, rows_number
  if (cells(5, r)%to_number(kind=1._R8P)>=highest_cost) then
    highest_cost = cells(5, r)%to_number(kind=1._R8P)
    most_expensive = csv%join(array=[cells(2, r), cells(3, r)], sep=' ')
  endif
enddo
test_passed(1) = most_expensive//'' == 'Chevy Venture "Extended Edition Very Large"'
print "(A,L1)", 'The most expensive car is : '//most_expensive//', is correct? ', test_passed(1)

print "(A,L1)", new_line('a')//'Are all tests passed? ', all(test_passed)
stop
!-----------------------------------------------------------------------------------------------------------------------------------
endprogram csv_naive_parser

assignments.f90 basename_dir.f90 befor64.F90 befor64.F90 befor64_pack_data_m.F90 befor64_pack_data_m.F90 camelcase.f90 capitalize.f90 compact_real.f90 compact_real.f90 compact_real.f90 concatenation.f90 csv_naive_parser.f90 decode.f90 encode.f90 equal.f90 escape.f90 extension.f90 fill.f90 free.f90 fury.f90 fury_mixed_kinds.F90 fury_qreal128.F90 fury_qreal32.F90 fury_qreal64.F90 fury_system_abstract128.F90 fury_system_abstract32.F90 fury_system_abstract64.F90 fury_system_si128.F90 fury_system_si32.F90 fury_system_si64.F90 fury_test_bolt32.f90 fury_test_bolt64.f90 fury_test_qreal_add.f90 fury_test_qreal_add_aliases_failure.f90 fury_test_qreal_add_failure.f90 fury_test_qreal_add_mixed.f90 fury_test_qreal_add_mixed_failure.f90 fury_test_qreal_aliases.f90 fury_test_qreal_assign.f90 fury_test_qreal_conversions_complex.f90 fury_test_qreal_conversions_si.f90 fury_test_qreal_conversions_simple.f90 fury_test_qreal_div.f90 fury_test_qreal_div_mixed.f90 fury_test_qreal_eq.f90 fury_test_qreal_eq_mixed.f90 fury_test_qreal_mul.f90 fury_test_qreal_mul_mixed.f90 fury_test_qreal_not_eq.f90 fury_test_qreal_not_eq_mixed.f90 fury_test_qreal_pow.f90 fury_test_qreal_sub.f90 fury_test_qreal_sub_failure.f90 fury_test_qreal_sub_mixed.f90 fury_test_qreal_sub_mixed_failure.f90 fury_test_system_si.f90 fury_test_uom_add.f90 fury_test_uom_add_failure.f90 fury_test_uom_aliases.f90 fury_test_uom_assign.f90 fury_test_uom_assign_failure.f90 fury_test_uom_div.f90 fury_test_uom_mul.f90 fury_test_uom_parse_failure.f90 fury_test_uom_pow.f90 fury_test_uom_sub.f90 fury_test_uom_sub_failure.f90 fury_uom128.F90 fury_uom32.F90 fury_uom64.F90 fury_uom_converter.F90 fury_uom_reference128.F90 fury_uom_reference32.F90 fury_uom_reference64.F90 fury_uom_symbol128.F90 fury_uom_symbol32.F90 fury_uom_symbol64.F90 greater_equal_than.f90 greater_than.f90 insert.f90 io_basic.F90 io_listdirected.F90 is_digit.f90 is_integer.f90 is_number.f90 is_real.f90 join.f90 lower_equal_than.f90 lower_than.f90 not_equal.f90 partition.f90 penf.F90 penf.F90 penf.F90 penf.F90 penf.F90 penf_b_size.F90 penf_global_parameters_variables.F90 penf_stringify.F90 read_file.f90 read_line.f90 read_lines.f90 replace.f90 reverse.f90 sadjustlr.f90 scount.f90 search.f90 sindex.f90 slen.f90 slice.f90 snakecase.f90 split.f90 srepeat.f90 sscan.f90 start_end.f90 startcase.f90 strim.f90 stringifor.F90 stringifor_string_t.F90 strip.f90 sverify.f90 swapcase.f90 test_all.F90 test_all.f90 test_all.f90 Test_Driver.f90 to_number.f90 unescape.f90 unique.f90 upper_lower.f90 write_file.f90 write_lines.f90