Skip to content

Commit

Permalink
feat(string_t): operator(.csv.), operator(.sv.)
Browse files Browse the repository at this point in the history
This commit adds

1. A unary operator(.csv.) that produces a string_t object
   encapsulating a comma-separated value (CSV) created from
   a. a string_t array or
   b. a character array,
2. A binary operator(.sv.) that produces a string_t object
   encapsulating a comma-separated value (CSV) created from
   left- and right-hand sides, respectively corresponding to
   a. a string_t array and a string_t separator or
   b. a string_t array and a character separator.
   c. a character array and a character separator
   d. a character array and a string_t separator
3. A unit test that verifies the following identities:

  "a,bc,def" == .csv. [string_t("a"), string_t("bc"), string_t("def")]
  "abc,def"  == .csv. ["abc", "def"]

  "do|re|mi" == (string_t(["do", "re", "mi"])         .sv.          "|" )
  "dore|mi"  == (([string_t("dore"), string_t("mi")]) .sv. string_t("|"))
  "do|re|mi" == (         ["do", "re", "mi"]          .sv.          "|" )
  "do|re|mi" == (         ["do", "re", "mi"]          .sv. string_t("|"))

corresponding to cases 1a-b and 2a-d, respectively.
  • Loading branch information
rouson committed Oct 27, 2024
1 parent 3ef050f commit e9253e8
Show file tree
Hide file tree
Showing 4 changed files with 127 additions and 13 deletions.
51 changes: 50 additions & 1 deletion src/julienne/julienne_string_m.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,9 @@ module julienne_string_m
private
public :: string_t
public :: array_of_strings
public :: operator(.cat.) ! element-wise concatenation operator
public :: operator(.cat.) ! element-wise concatenation unary operator
public :: operator(.csv.) ! comma-separated values unary operator
public :: operator(.sv.) ! separated-values binary operator

type, extends(characterizable_t) :: string_t
private
Expand Down Expand Up @@ -84,7 +86,54 @@ pure module function concatenate_elements(strings) result(concatenated_strings)

end interface

interface operator(.csv.)

pure module function strings_with_comma_separator(strings) result(csv)
implicit none
type(string_t), intent(in) :: strings(:)
type(string_t) csv
end function

pure module function characters_with_comma_separator(strings) result(csv)
implicit none
character(len=*), intent(in) :: strings(:)
type(string_t) csv
end function

end interface

interface operator(.sv.)

pure module function strings_with_character_separator(strings, separator) result(sv)
implicit none
type(string_t) , intent(in) :: strings(:)
character(len=*), intent(in) :: separator
type(string_t) sv
end function

pure module function characters_with_character_separator(strings, separator) result(sv)
implicit none
character(len=*), intent(in) :: strings(:), separator
type(string_t) sv
end function

pure module function characters_with_string_separator(strings, separator) result(sv)
implicit none
character(len=*), intent(in) :: strings(:)
type(string_t) , intent(in) :: separator
type(string_t) sv
end function

pure module function strings_with_string_t_separator(strings, separator) result(sv)
implicit none
type(string_t), intent(in) :: strings(:), separator
type(string_t) sv
end function

end interface

interface

pure module function as_character(self) result(raw_string)
implicit none
class(string_t), intent(in) :: self
Expand Down
38 changes: 38 additions & 0 deletions src/julienne/julienne_string_s.f90
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,44 @@
end do
end procedure

module procedure strings_with_comma_separator
csv = strings_with_string_t_separator(strings, string_t(","))
end procedure

module procedure characters_with_comma_separator
csv = strings_with_string_t_separator(string_t(strings), string_t(","))
end procedure

module procedure characters_with_character_separator
sv = strings_with_string_t_separator(string_t(strings), string_t(separator))
end procedure

module procedure characters_with_string_separator
sv = strings_with_string_t_separator(string_t(strings), separator)
end procedure

module procedure strings_with_character_separator
sv = strings_with_string_t_separator(strings, string_t(separator))
end procedure

module procedure strings_with_string_t_separator

integer s

associate(num_elements => size(strings))

sv = ""

do s = 1, num_elements - 1
sv = sv // strings(s) // separator
end do

sv = sv // strings(num_elements)

end associate

end procedure

module procedure array_of_strings
character(len=:), allocatable :: remainder, next_string
integer next_delimiter, string_end
Expand Down
2 changes: 1 addition & 1 deletion src/julienne_m.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module julienne_m
use julienne_file_m, only : file_t
use julienne_github_ci_m, only : github_ci
use julienne_formats_m, only : separated_values, csv
use julienne_string_m, only : string_t, operator(.cat.)
use julienne_string_m, only : string_t, operator(.cat.), operator(.csv.), operator(.sv.)
use julienne_test_m, only : test_t, test_description_substring
use julienne_test_description_m, only : test_description_t, test_function_i
use julienne_test_result_m, only : test_result_t
Expand Down
49 changes: 38 additions & 11 deletions test/string_test.F90
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,22 @@
#include "language-support.F90"

module string_test_m
use julienne_m, only : test_t, test_result_t, string_t, operator(.cat.), test_description_t, test_description_substring
use assert_m, only : assert

use julienne_m, only : &
test_t &
,test_result_t &
,test_description_t &
,test_description_substring &
,string_t &
,operator(.cat.) &
,operator(.csv.) &
,operator(.sv.)

#if ! HAVE_PROCEDURE_ACTUAL_FOR_POINTER_DUMMY
use julienne_m, only : test_function_i
#endif

implicit none

private
Expand Down Expand Up @@ -77,7 +89,9 @@ function results() result(test_results)
test_description_t &
(string_t('extracting a file name extension'), extracts_file_name_extension), &
test_description_t &
(string_t('constructing a bracketed string'), brackets_strings) &
(string_t('constructing a bracketed string'), brackets_strings), &
test_description_t &
(string_t('constructing (comma-)separated values from character or string_t arrays'), constructs_separated_values) &
]
#else
! Work around missing Fortran 2008 feature: associating a procedure actual argument with a procedure pointer dummy argument:
Expand All @@ -89,8 +103,8 @@ function results() result(test_results)
! Remove code that exposes a gfortran compiler bug:
! extracts_string_array_ptr, &
extracts_character_ptr, extracts_double_precision_value_ptr, extracts_dp_array_value_ptr, &
bracket_a_string

bracket_a_string, constructs_separated_values
check_allocation_ptr => check_allocation
supports_equivalence_ptr => supports_equivalence_operator
supports_non_equivalence_ptr => supports_non_equivalence_operator
Expand All @@ -115,6 +129,7 @@ function results() result(test_results)
extracts_file_base_ptr => extracts_file_base_name
extracts_file_name_ptr => extracts_file_name_extension
brackets_strings_ptr => brackets_strings
constructs_separated_values_ptr => constructs_separated_values

test_descriptions = [ &
test_description_t( &
Expand Down Expand Up @@ -148,7 +163,8 @@ function results() result(test_results)
test_description_t(string_t("extracting an integer value from a colon-separated key/value pair"), extracts_integer_ptr), &
test_description_t(string_t('extracting a file base name'), extracts_file_base_ptr), &
test_description_t(string_t('extracting a file name extension'), extracts_file_name_ptr), &
test_description_t(string_t('constructing a bracketed string'), brackets_strings) &
test_description_t(string_t('constructing a bracketed string'), brackets_strings_ptr),&
test_description_t(string_t('constructing (comma-)separated values from string_t arrays'), constructs_separated_values_ptr) &
]
#endif
test_descriptions = pack(test_descriptions, &
Expand Down Expand Up @@ -520,18 +536,29 @@ function brackets_strings() result(passed)
logical passed

associate( &
scalar => string_t("abcdefg"), &
array => [string_t("do"), string_t("ray"), string_t("me")] &
scalar => string_t("do re mi"), &
array => [string_t("do"), string_t("re"), string_t("mi")] &
)
associate( &
brackets_a_scalar => scalar%bracket() == string_t("[abcdefg]") &
,defaults_to_square => all(array%bracket() == [string_t("[do]"), string_t("[ray]"), string_t("[me]")]) &
,defaults_closing_to_opening => all(array%bracket('"') == [string_t('"do"'), string_t('"ray"'), string_t('"me"')]) &
,handles_both_args_present => all(array%bracket("{","}") == [string_t('{do}'), string_t('{ray}'), string_t('{me}')]) &
brackets_a_scalar => scalar%bracket() == string_t("[do re mi]") &
,defaults_to_square => all(array%bracket() == [string_t("[do]"), string_t("[re]"), string_t("[mi]")]) &
,defaults_closing_to_opening => all(array%bracket('"') == [string_t('"do"'), string_t('"re"'), string_t('"mi"')]) &
,handles_both_args_present => all(array%bracket("{","}") == [string_t('{do}'), string_t('{re}'), string_t('{mi}')]) &
)
passed = brackets_a_scalar .and. defaults_to_square .and. defaults_closing_to_opening .and. handles_both_args_present
end associate
end associate
end function

function constructs_separated_values() result(passed)
logical passed
passed = &
"a,bc,def" == .csv. [string_t("a"), string_t("bc"), string_t("def")] &
.and. "abc,def" == .csv. ["abc", "def"] &
.and. "do|re|mi" == (string_t(["do", "re", "mi"]) .sv. "|" ) &
.and. "dore|mi" == (([string_t("dore"), string_t("mi")]) .sv. string_t("|")) &
.and. "do|re|mi" == ( ["do", "re", "mi"] .sv. "|" ) &
.and. "do|re|mi" == ( ["do", "re", "mi"] .sv. string_t("|"))
end function

end module string_test_m

0 comments on commit e9253e8

Please sign in to comment.