join.f90 Source File

StringiFor join test.

This File Depends On

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

!-----------------------------------------------------------------------------------------------------------------------------------
implicit none
type(string) :: astring         !< A string.
type(string) :: strings(3)      !< A set of strings.
character(5) :: characters(3)   !< A set of characters.
logical      :: test_passed(11) !< List of passed tests.
integer      :: s               !< Counter.
!-----------------------------------------------------------------------------------------------------------------------------------

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

strings(1) = 'one'
strings(2) = 'two'
strings(3) = 'three'
write(stdout, "(A)") 'Originals:'
do s=1, size(strings)
  write(stdout, "(A)") '+ "'//strings(s)//'"'
enddo

write(stdout, "(A)") 'join (default sep) "'//astring%join(array=strings)//'"'
test_passed(1) = (astring%join(array=strings)//''==strings(1)//strings(2)//strings(3))

write(stdout, "(A)") 'join (sep="-") "'//astring%join(array=strings, sep='-')//'"'
test_passed(2) = (astring%join(array=strings, sep='-')//''==strings(1)//'-'//strings(2)//'-'//strings(3))

call strings(1)%free
strings(2) = 'two'
strings(3) = 'three'
write(stdout, "(A)") 'Originals:'
do s=1, size(strings)
  write(stdout, "(A)") '+ "'//strings(s)//'"'
enddo

write(stdout, "(A)") 'join (sep="-") "'//astring%join(array=strings, sep='-')//'"'
test_passed(3) = (astring%join(array=strings, sep='-')//''==strings(2)//'-'//strings(3))

strings(1) = 'one'
strings(2) = 'two'
call strings(3)%free
write(stdout, "(A)") 'Originals:'
do s=1, size(strings)
  write(stdout, "(A)") '+ "'//strings(s)//'"'
enddo

write(stdout, "(A)") 'join (sep="-") "'//astring%join(array=strings, sep='-')//'"'
test_passed(4) = (astring%join(array=strings, sep='-')//''==strings(1)//'-'//strings(2))

strings(1) = 'one'
call strings(2)%free
strings(3) = 'three'
write(stdout, "(A)") 'Originals:'
do s=1, size(strings)
  write(stdout, "(A)") '+ "'//strings(s)//'"'
enddo

write(stdout, "(A)") 'join (sep="-") "'//astring%join(array=strings, sep='-')//'"'
test_passed(5) = (astring%join(array=strings, sep='-')//''==strings(1)//'-'//strings(3))

characters(1) = 'one'
characters(2) = 'two'
characters(3) = 'three'
write(stdout, "(A)") 'Originals:'
do s=1, size(characters)
  write(stdout, "(A)") '+ "'//characters(s)//'"'
enddo

write(stdout, "(A)") 'join (default sep) "'//astring%join(array=characters)//'"'
test_passed(6) = (astring%join(array=characters)//''==characters(1)//characters(2)//characters(3))

write(stdout, "(A)") 'join (sep="-") "'//astring%join(array=characters, sep='-')//'"'
test_passed(7) = (astring%join(array=characters, sep='-')//''==characters(1)//'-'//characters(2)//'-'//characters(3))

characters(1) = ''
characters(2) = 'two'
characters(3) = 'three'
write(stdout, "(A)") 'Originals:'
do s=1, size(characters)
  write(stdout, "(A)") '+ "'//characters(s)//'"'
enddo

write(stdout, "(A)") 'join (sep="-") "'//astring%join(array=characters, sep='-')//'"'
test_passed(8) = (astring%join(array=characters, sep='-')//''==characters(2)//'-'//characters(3))

characters(1) = 'one'
characters(2) = 'two'
characters(3) = ''
write(stdout, "(A)") 'Originals:'
do s=1, size(characters)
  write(stdout, "(A)") '+ "'//characters(s)//'"'
enddo

write(stdout, "(A)") 'join (sep="-") "'//astring%join(array=characters, sep='-')//'"'
test_passed(9) = (astring%join(array=characters, sep='-')//''==characters(1)//'-'//characters(2))

characters(1) = 'one'
characters(2) = ''
characters(3) = 'three'
write(stdout, "(A)") 'Originals:'
do s=1, size(characters)
  write(stdout, "(A)") '+ "'//characters(s)//'"'
enddo

write(stdout, "(A)") 'join (sep="-") "'//astring%join(array=characters, sep='-')//'"'
test_passed(10) = (astring%join(array=characters, sep='-')//''==characters(1)//'-'//characters(3))

characters(1) = 'one'
characters(2) = 'two'
characters(3) = 'three'
write(stdout, "(A)") 'Originals:'
do s=1, size(characters)
  write(stdout, "(A)") '+ "'//characters(s)//'"'
enddo

astring = '_'
write(stdout, "(A)") 'join (sep by astring) "'//astring%join(array=characters)//'"'
test_passed(11) = (astring%join(array=characters)//''==characters(1)//'_'//characters(2)//'_'//characters(3))

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

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