read_file.f90 Source File

StringiFor read_file test.

This File Depends On

sourcefile~~read_file.f90~~EfferentGraph sourcefile~read_file.f90 read_file.f90 sourcefile~stringifor.f90 stringifor.F90 sourcefile~stringifor.f90->sourcefile~read_file.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 `read_file` test.
program read_file
!-----------------------------------------------------------------------------------------------------------------------------------
!< StringiFor `read_file` test.
!-----------------------------------------------------------------------------------------------------------------------------------
use, intrinsic :: iso_fortran_env, only : stdout => output_unit, iostat_end
use stringifor, only : read_file_standalone => read_file, string
!-----------------------------------------------------------------------------------------------------------------------------------

!-----------------------------------------------------------------------------------------------------------------------------------
implicit none
type(string)              :: astring         !< A string.
type(string), allocatable :: strings(:)      !< A set of strings.
type(string)              :: line(3)         !< Another set of string.
integer                   :: iostat          !< IO status code.
character(len=99)         :: iomsg           !< IO status message.
integer                   :: scratch         !< Scratch file unit.
integer                   :: l               !< Counter.
logical                   :: test_passed(16) !< List of passed tests.
!-----------------------------------------------------------------------------------------------------------------------------------

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

line(1) = ' Hello World!   '
line(2) = 'How are you?  '
line(3) = '   All say: "Fine thanks"'

open(newunit=scratch, file='read_file_test.tmp')
write(scratch, "(A)") line(1)%chars()
write(scratch, "(A)") line(2)%chars()
write(scratch, "(A)") line(3)%chars()
close(scratch)

write(stdout, "(A)") "TBP read_file"
call astring%read_file(file='read_file_test.tmp', iostat=iostat, iomsg=iomsg)
if (iostat/=0) write(stdout, "(A)")iomsg
call astring%split(tokens=strings, sep=new_line('a'))
test_passed(1) = (size(strings, dim=1)==size(line, dim=1))
do l=1, size(strings, dim=1)
  test_passed(l+1) = (strings(l)==line(l))
  write(stdout, "(A,L1)") 'line: "'//strings(l)//'", is correct? ', test_passed(l+1)
enddo

write(stdout, "(A)") "Standalone read_file"
call read_file_standalone(file='read_file_test.tmp', lines=strings, iostat=iostat, iomsg=iomsg)
if (iostat/=0) write(stdout, "(A)")iomsg
test_passed(5) = (size(strings, dim=1)==size(line, dim=1))
do l=1, size(strings, dim=1)
  test_passed(l+5) = (strings(l)==line(l))
  write(stdout, "(A,L1)") 'line: "'//strings(l)//'", is correct? ', test_passed(l+5)
enddo

open(newunit=scratch, file='read_file_test.tmp', form='UNFORMATTED', access='STREAM')
write(scratch) line(1)%chars()//new_line('a')
write(scratch) line(2)%chars()//new_line('a')
write(scratch) line(3)%chars()//new_line('a')
close(scratch)

write(stdout, "(A)") "TBP read_file unformatted"
call astring%read_file(file='read_file_test.tmp', form='unformatted', iostat=iostat, iomsg=iomsg)
if (iostat/=0) write(stdout, "(A)")iomsg
call astring%split(tokens=strings, sep=new_line('a'))
test_passed(9) = (size(strings, dim=1)==size(line, dim=1))
do l=1, size(strings, dim=1)
  test_passed(l+9) = (strings(l)==line(l))
  write(stdout, "(A,L1)") 'line: "'//strings(l)//'", is correct? ', test_passed(l+9)
enddo

write(stdout, "(A)") "Standalone read_file unformatted"
call read_file_standalone(file='read_file_test.tmp', lines=strings, form='unformatted', iostat=iostat, iomsg=iomsg)
if (iostat/=0) write(stdout, "(A)")iomsg
test_passed(13) = (size(strings, dim=1)==size(line, dim=1))
do l=1, size(strings, dim=1)
  test_passed(l+13) = (strings(l)==line(l))
  write(stdout, "(A,L1)") 'line: "'//strings(l)//'", is correct? ', test_passed(l+13)
enddo

open(newunit=scratch, file='read_file_test.tmp', form='UNFORMATTED', access='STREAM')
close(scratch, status='DELETE')

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

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