From b49635b5cea4e6acbbf6968ae80faa50ad528d49 Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Mon, 31 May 2021 17:35:43 +0530 Subject: [PATCH 01/16] implemented index function and compute_LPS function --- src/Makefile.manual | 5 ++- src/stdlib_strings.f90 | 86 ++++++++++++++++++++++++++++++++++++++++-- 2 files changed, 85 insertions(+), 6 deletions(-) diff --git a/src/Makefile.manual b/src/Makefile.manual index 28d00a6cc..d15cbd5d9 100644 --- a/src/Makefile.manual +++ b/src/Makefile.manual @@ -126,7 +126,8 @@ stdlib_stats_distribution_PRNG.o: \ stdlib_kinds.o \ stdlib_error.o stdlib_string_type.o: stdlib_ascii.o \ - stdlib_kinds.o + stdlib_kinds.o stdlib_strings.o: stdlib_ascii.o \ - stdlib_string_type.o + stdlib_string_type.o \ + stdlib_optval stdlib_math.o: stdlib_kinds.o diff --git a/src/stdlib_strings.f90 b/src/stdlib_strings.f90 index 158b06588..1ff68162e 100644 --- a/src/stdlib_strings.f90 +++ b/src/stdlib_strings.f90 @@ -4,14 +4,15 @@ !> !> The specification of this module is available [here](../page/specs/stdlib_strings.html). module stdlib_strings - use stdlib_ascii, only : whitespace - use stdlib_string_type, only : string_type, char, verify + use stdlib_ascii, only: whitespace + use stdlib_string_type, only: string_type, char, verify + use stdlib_optval, only: optval implicit none - private + private :: compute_LPS public :: strip, chomp public :: starts_with, ends_with - public :: slice + public :: slice, find !> Remove leading and trailing whitespace characters. @@ -67,6 +68,15 @@ module stdlib_strings module procedure :: slice_char end interface slice + !> Finds the starting index of substring 'pattern' in the input 'string' + !> + !> Version: experimental + interface find + module procedure :: find_string_string + module procedure :: find_string_char + module procedure :: find_char_string + module procedure :: find_char_char + end interface find contains @@ -366,5 +376,73 @@ pure function slice_char(string, first, last, stride) result(sliced_string) end do end function slice_char + pure function find_char_char(string, pattern, occurrence, consider_overlapping) result(res) + character(len=*), intent(in) :: string + character(len=*), intent(in) :: pattern + integer, intent(in), optional :: occurrence + logical, intent(in), optional :: consider_overlapping + integer :: LPS_array(len(pattern)) + integer :: res, i, j, length_string, length_pattern, occurrence_ + logical :: consider_overlapping_ + + consider_overlapping_ = optval(consider_overlapping, .false.) + occurrence_ = max(1, optval(occurrence, 1)) + res = -1 + length_string = len(string) + length_pattern = len(pattern) + + if (length_pattern > 0 .and. length_pattern <= length_string) then + LPS_array = compute_LPS(pattern) + + i = 1 + j = 1 + do while(i <= length_string) + if (string(i:i) == pattern(j:j)) then + if (j == length_pattern) then + occurrence_ = occurrence_ - 1 + if (occurrence_ == 0) then + res = i - length_pattern + 1 + exit + else if (consider_overlapping_) then + i = i - length_pattern + 1 + end if + j = 0 + end if + i = i + 1 + j = j + 1 + else if (j > 1) then + j = LPS_array(j - 1) + 1 + else + i = i + 1 + end if + end do + end if + + end function find_char_char + + pure function compute_LPS(string) result(LPS_array) + character(len=*), intent(in) :: string + integer :: LPS_array(len(string)) + integer :: i, j, length_string + + length_string = len(string) + LPS_array = 0 + + i = 2 + j = 1 + do while (i <= length_string) + if (string(j:j) == string(i:i)) then + LPS_array(i) = j + i = i + 1 + j = j + 1 + else if (j > 1) then + j = LPS_array(j - 1) + 1 + else + i = i + 1 + end if + end do + + end function compute_LPS + end module stdlib_strings From 798e229688b1dd6e0feaf4ba60f2dedf4e7ab7b9 Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Thu, 10 Jun 2021 15:15:18 +0530 Subject: [PATCH 02/16] added comments, improved compute_lps, changed default value of consider_overlapping --- src/stdlib_strings.f90 | 129 +++++++++++++++++++++++++++++------------ 1 file changed, 91 insertions(+), 38 deletions(-) diff --git a/src/stdlib_strings.f90 b/src/stdlib_strings.f90 index 1ff68162e..a1832d262 100644 --- a/src/stdlib_strings.f90 +++ b/src/stdlib_strings.f90 @@ -8,7 +8,7 @@ module stdlib_strings use stdlib_string_type, only: string_type, char, verify use stdlib_optval, only: optval implicit none - private :: compute_LPS + private :: compute_lps public :: strip, chomp public :: starts_with, ends_with @@ -376,73 +376,126 @@ pure function slice_char(string, first, last, stride) result(sliced_string) end do end function slice_char + !> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' + !> in input 'string' + !> Returns an integer + pure function find_string_string(string, pattern, occurrence, consider_overlapping) result(res) + type(string_type), intent(in) :: string + type(string_type), intent(in) :: pattern + integer, intent(in), optional :: occurrence + logical, intent(in), optional :: consider_overlapping + integer :: res + + res = find(char(string), char(pattern), occurrence, consider_overlapping) + + end function find_string_string + + !> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' + !> in input 'string' + !> Returns an integer + pure function find_string_char(string, pattern, occurrence, consider_overlapping) result(res) + type(string_type), intent(in) :: string + character(len=*), intent(in) :: pattern + integer, intent(in), optional :: occurrence + logical, intent(in), optional :: consider_overlapping + integer :: res + + res = find(char(string), pattern, occurrence, consider_overlapping) + + end function find_string_char + + !> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' + !> in input 'string' + !> Returns an integer + pure function find_char_string(string, pattern, occurrence, consider_overlapping) result(res) + character(len=*), intent(in) :: string + type(string_type), intent(in) :: pattern + integer, intent(in), optional :: occurrence + logical, intent(in), optional :: consider_overlapping + integer :: res + + res = find(string, char(pattern), occurrence, consider_overlapping) + + end function find_char_string + + !> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' + !> in input 'string' + !> Returns an integer pure function find_char_char(string, pattern, occurrence, consider_overlapping) result(res) character(len=*), intent(in) :: string character(len=*), intent(in) :: pattern integer, intent(in), optional :: occurrence logical, intent(in), optional :: consider_overlapping - integer :: LPS_array(len(pattern)) - integer :: res, i, j, length_string, length_pattern, occurrence_ + integer :: lps_array(len(pattern)) + integer :: res, s_i, p_i, length_string, length_pattern, occurrence_ logical :: consider_overlapping_ - consider_overlapping_ = optval(consider_overlapping, .false.) - occurrence_ = max(1, optval(occurrence, 1)) - res = -1 + consider_overlapping_ = optval(consider_overlapping, .true.) + occurrence_ = optval(occurrence, 1) + res = 0 length_string = len(string) length_pattern = len(pattern) - if (length_pattern > 0 .and. length_pattern <= length_string) then - LPS_array = compute_LPS(pattern) + if (length_pattern > 0 .and. length_pattern <= length_string & + .and. occurrence_ > 0) then + lps_array = compute_lps(pattern) - i = 1 - j = 1 - do while(i <= length_string) - if (string(i:i) == pattern(j:j)) then - if (j == length_pattern) then + s_i = 1 + p_i = 1 + do while(s_i <= length_string) + if (string(s_i:s_i) == pattern(p_i:p_i)) then + if (p_i == length_pattern) then occurrence_ = occurrence_ - 1 if (occurrence_ == 0) then - res = i - length_pattern + 1 + res = s_i - length_pattern + 1 exit else if (consider_overlapping_) then - i = i - length_pattern + 1 + s_i = s_i - length_pattern + 1 end if - j = 0 + p_i = 0 end if - i = i + 1 - j = j + 1 - else if (j > 1) then - j = LPS_array(j - 1) + 1 + s_i = s_i + 1 + p_i = p_i + 1 + else if (p_i > 1) then + p_i = lps_array(p_i - 1) + 1 else - i = i + 1 + s_i = s_i + 1 end if end do end if end function find_char_char - pure function compute_LPS(string) result(LPS_array) + !> Computes longest prefix suffix for each index of the input 'string' + !> + !> Returns an array of integers + pure function compute_lps(string) result(lps_array) character(len=*), intent(in) :: string - integer :: LPS_array(len(string)) + integer :: lps_array(len(string)) integer :: i, j, length_string length_string = len(string) - LPS_array = 0 - i = 2 - j = 1 - do while (i <= length_string) - if (string(j:j) == string(i:i)) then - LPS_array(i) = j - i = i + 1 - j = j + 1 - else if (j > 1) then - j = LPS_array(j - 1) + 1 - else - i = i + 1 - end if - end do + if (length_string > 0) then + lps_array(1) = 0 + + i = 2 + j = 1 + do while (i <= length_string) + if (string(j:j) == string(i:i)) then + lps_array(i) = j + i = i + 1 + j = j + 1 + else if (j > 1) then + j = lps_array(j - 1) + 1 + else + lps_array(i) = 0 + i = i + 1 + end if + end do + end if - end function compute_LPS + end function compute_lps end module stdlib_strings From e34d05af565fa06173d35ac5680281188a381083 Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Thu, 10 Jun 2021 16:05:25 +0530 Subject: [PATCH 03/16] added unit tests for find function --- src/tests/string/test_string_functions.f90 | 20 +++++++++++++++++--- 1 file changed, 17 insertions(+), 3 deletions(-) diff --git a/src/tests/string/test_string_functions.f90 b/src/tests/string/test_string_functions.f90 index e72b4c162..5bd62ef69 100644 --- a/src/tests/string/test_string_functions.f90 +++ b/src/tests/string/test_string_functions.f90 @@ -4,7 +4,7 @@ module test_string_functions use stdlib_error, only : check use stdlib_string_type, only : string_type, assignment(=), operator(==), & to_lower, to_upper, to_title, to_sentence, reverse - use stdlib_strings, only: slice + use stdlib_strings, only: slice, find use stdlib_optval, only: optval use stdlib_ascii, only : to_string implicit none @@ -56,7 +56,7 @@ subroutine test_reverse_string end subroutine test_reverse_string - subroutine test_slice_string + subroutine test_slice type(string_type) :: test_string test_string = "abcdefghijklmnopqrstuvwxyz" @@ -160,7 +160,20 @@ subroutine test_slice_string call check(slice(test_string) == "", & "Slice, Empty string: no arguments provided") - end subroutine test_slice_string + end subroutine test_slice + + subroutine test_find + type(string_type) :: test_string, test_pattern + test_string = "qwqwqwqwqwqwqw" + test_pattern = "qwq" + call check(find(test_string, test_pattern, 4) == 7) + call check(find(test_string, test_pattern, 3, .false.) == 9) + call check(find(test_string, test_pattern, 7) == 0) + call check(find("qwqwqwqwqwqwqw", test_pattern) == 1) + call check(find(test_string, "qwq", 2) == 3) + call check(find("qwqwqwqwqwqwqw", "qwq", 2, .false.) == 5) + + end subroutine test_find subroutine test_slice_gen character(len=*), parameter :: test = & @@ -300,5 +313,6 @@ program tester call test_reverse_string call test_slice_string call test_slice_gen + call test_find end program tester From 13a9341222f975bfc32585a023c50e526684f4d5 Mon Sep 17 00:00:00 2001 From: Aman Godara <34789087+Aman-Godara@users.noreply.github.com> Date: Sun, 13 Jun 2021 01:07:42 +0530 Subject: [PATCH 04/16] removed explicit private keyword for compute_lps in src/stdlib_strings.f90 Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/stdlib_strings.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/stdlib_strings.f90 b/src/stdlib_strings.f90 index a1832d262..44b5d3b1a 100644 --- a/src/stdlib_strings.f90 +++ b/src/stdlib_strings.f90 @@ -8,7 +8,7 @@ module stdlib_strings use stdlib_string_type, only: string_type, char, verify use stdlib_optval, only: optval implicit none - private :: compute_lps + private public :: strip, chomp public :: starts_with, ends_with From 87e2547e84ae1559b8486b7418dd2ff13ea8406e Mon Sep 17 00:00:00 2001 From: Aman Godara <34789087+Aman-Godara@users.noreply.github.com> Date: Sun, 13 Jun 2021 01:09:14 +0530 Subject: [PATCH 05/16] added leading continuation character (&: ampersand) for readability Co-authored-by: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> --- src/stdlib_strings.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/stdlib_strings.f90 b/src/stdlib_strings.f90 index 44b5d3b1a..d98f68d67 100644 --- a/src/stdlib_strings.f90 +++ b/src/stdlib_strings.f90 @@ -437,7 +437,7 @@ pure function find_char_char(string, pattern, occurrence, consider_overlapping) length_pattern = len(pattern) if (length_pattern > 0 .and. length_pattern <= length_string & - .and. occurrence_ > 0) then + & .and. occurrence_ > 0) then lps_array = compute_lps(pattern) s_i = 1 From 71da64c304ad8f762e074a0f36b144df7e7ea0c1 Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Mon, 14 Jun 2021 17:26:51 +0530 Subject: [PATCH 06/16] added empty string/pattern test cases, corrected test_slice to test_slice_string --- src/tests/string/test_string_functions.f90 | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/tests/string/test_string_functions.f90 b/src/tests/string/test_string_functions.f90 index 5bd62ef69..a4253f75c 100644 --- a/src/tests/string/test_string_functions.f90 +++ b/src/tests/string/test_string_functions.f90 @@ -56,7 +56,7 @@ subroutine test_reverse_string end subroutine test_reverse_string - subroutine test_slice + subroutine test_slice_string type(string_type) :: test_string test_string = "abcdefghijklmnopqrstuvwxyz" @@ -160,7 +160,7 @@ subroutine test_slice call check(slice(test_string) == "", & "Slice, Empty string: no arguments provided") - end subroutine test_slice + end subroutine test_slice_string subroutine test_find type(string_type) :: test_string, test_pattern @@ -172,6 +172,9 @@ subroutine test_find call check(find("qwqwqwqwqwqwqw", test_pattern) == 1) call check(find(test_string, "qwq", 2) == 3) call check(find("qwqwqwqwqwqwqw", "qwq", 2, .false.) == 5) + call check(find("", "") == 0) + call check(find("", test_pattern) == 0) + call check(find(test_string, "") == 0) end subroutine test_find From d855fcd5e8d8bf0aff172796123f66d46e90a7c0 Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Mon, 14 Jun 2021 18:59:44 +0530 Subject: [PATCH 07/16] documented function find --- doc/specs/stdlib_strings.md | 59 +++++++++++++++++++++++++++++++++++++ 1 file changed, 59 insertions(+) diff --git a/doc/specs/stdlib_strings.md b/doc/specs/stdlib_strings.md index c047653b5..8388de01d 100644 --- a/doc/specs/stdlib_strings.md +++ b/doc/specs/stdlib_strings.md @@ -270,3 +270,62 @@ program demo_slice end program demo_slice ``` + + + +### `find` + +#### Description + +Returns the starting index of the `occurrence`th occurrence of the substring `pattern` +in the input string `string`. +Default value of `occurrence` is set to `1`. +If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurences of substring as two different occurrences. +If `occurrence`th occurrence is not found, function returns `0`. + + +#### Syntax + +`string = [[stdlib_strings(module):find(interface)]] (string, pattern, occurrence, consider_overlapping)` + +#### Status + +Experimental + +#### Class + +Pure function + +#### Argument + +- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]] + This argument is intent(in). +- `pattern`: Character scalar or [[stdlib_string_type(module):string_type(type)]] + This argument is intent(in). +- `occurrence`: integer + This argument is intent(in) and optional. +- `consider_overlapping`: logical + This argument is intent(in) and optional. + +#### Result value + +The result is of scalar integer type. + +#### Example + +```fortran +program demo_find + use stdlib_string_type + use stdlib_strings, only : find + implicit none + string_type :: string + + string = "needle in this character-stack" + + print *, find(string, "needle") ! 1 + print *, find(string, "a", 3) ! 28 + print *, find("qwqwqwq", "qwq", 3, .false.) ! 0 + print *, find("qwqwqwq", "qwq", 3, .true.) ! 5 + +end program demo_find +``` \ No newline at end of file From 90b401c9dc19acce945d85b5c028d3e4b025cf5e Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Mon, 14 Jun 2021 19:19:46 +0530 Subject: [PATCH 08/16] fixed typo --- doc/specs/stdlib_strings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/specs/stdlib_strings.md b/doc/specs/stdlib_strings.md index 8388de01d..eb89015f7 100644 --- a/doc/specs/stdlib_strings.md +++ b/doc/specs/stdlib_strings.md @@ -280,7 +280,7 @@ end program demo_slice Returns the starting index of the `occurrence`th occurrence of the substring `pattern` in the input string `string`. Default value of `occurrence` is set to `1`. -If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurences of substring as two different occurrences. +If `consider_overlapping` is not provided or is set to `.true.` the function counts two overlapping occurrences of substring as two different occurrences. If `occurrence`th occurrence is not found, function returns `0`. From f449f269447f52f3c4d1288bad3b83523b5e87ff Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Mon, 14 Jun 2021 22:02:59 +0530 Subject: [PATCH 09/16] added fail messages and put fullstop (.) in documentation --- doc/specs/stdlib_strings.md | 16 ++++++------- src/tests/string/test_string_functions.f90 | 27 ++++++++++++++-------- 2 files changed, 26 insertions(+), 17 deletions(-) diff --git a/doc/specs/stdlib_strings.md b/doc/specs/stdlib_strings.md index eb89015f7..46365a363 100644 --- a/doc/specs/stdlib_strings.md +++ b/doc/specs/stdlib_strings.md @@ -233,13 +233,13 @@ Pure function. #### Argument -- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]] +- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]]. This argument is intent(in). -- `first`: integer +- `first`: integer. This argument is intent(in) and optional. -- `last`: integer +- `last`: integer. This argument is intent(in) and optional. -- `stride`: integer +- `stride`: integer. This argument is intent(in) and optional. #### Result value @@ -298,13 +298,13 @@ Pure function #### Argument -- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]] +- `string`: Character scalar or [[stdlib_string_type(module):string_type(type)]]. This argument is intent(in). -- `pattern`: Character scalar or [[stdlib_string_type(module):string_type(type)]] +- `pattern`: Character scalar or [[stdlib_string_type(module):string_type(type)]]. This argument is intent(in). -- `occurrence`: integer +- `occurrence`: integer. This argument is intent(in) and optional. -- `consider_overlapping`: logical +- `consider_overlapping`: logical. This argument is intent(in) and optional. #### Result value diff --git a/src/tests/string/test_string_functions.f90 b/src/tests/string/test_string_functions.f90 index a4253f75c..9b85aeb5a 100644 --- a/src/tests/string/test_string_functions.f90 +++ b/src/tests/string/test_string_functions.f90 @@ -166,15 +166,24 @@ subroutine test_find type(string_type) :: test_string, test_pattern test_string = "qwqwqwqwqwqwqw" test_pattern = "qwq" - call check(find(test_string, test_pattern, 4) == 7) - call check(find(test_string, test_pattern, 3, .false.) == 9) - call check(find(test_string, test_pattern, 7) == 0) - call check(find("qwqwqwqwqwqwqw", test_pattern) == 1) - call check(find(test_string, "qwq", 2) == 3) - call check(find("qwqwqwqwqwqwqw", "qwq", 2, .false.) == 5) - call check(find("", "") == 0) - call check(find("", test_pattern) == 0) - call check(find(test_string, "") == 0) + call check(find(test_string, test_pattern, 4) == 7, & + & 'Find: test_string, test_pattern, 4') + call check(find(test_string, test_pattern, 3, .false.) == 9, & + & 'Find: test_string, test_pattern, 3') + call check(find(test_string, test_pattern, 7) == 0, & + & 'Find: test_string, test_pattern, 7') + call check(find("qwqwqwqwqwqwqw", test_pattern) == 1, & + & 'Find: "qwqwqwqwqwqwqw", test_pattern') + call check(find(test_string, "qwq", 2) == 3, & + & 'Find: test_string, "qwq", 2') + call check(find("qwqwqwqwqwqwqw", "qwq", 2, .false.) == 5, & + & 'Find: "qwqwqwqwqwqwqw", "qwq", 2, .false.') + call check(find("", "") == 0, & + & 'Find: "", ""') + call check(find("", test_pattern) == 0, & + & 'Find: "", test_pattern') + call check(find(test_string, "") == 0, & + & 'Find: test_string, ""') end subroutine test_find From 76182e20018878822049ba151c8739aaac5b34ca Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Tue, 15 Jun 2021 01:31:12 +0530 Subject: [PATCH 10/16] optimised find function for consider_overlapping is .true. --- src/stdlib_strings.f90 | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/stdlib_strings.f90 b/src/stdlib_strings.f90 index d98f68d67..38adf32e3 100644 --- a/src/stdlib_strings.f90 +++ b/src/stdlib_strings.f90 @@ -450,9 +450,10 @@ pure function find_char_char(string, pattern, occurrence, consider_overlapping) res = s_i - length_pattern + 1 exit else if (consider_overlapping_) then - s_i = s_i - length_pattern + 1 + p_i = lps_array(p_i) + else + p_i = 0 end if - p_i = 0 end if s_i = s_i + 1 p_i = p_i + 1 From c63d065ba0055cea26a4d883abdc18534976049c Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Wed, 16 Jun 2021 17:17:02 +0200 Subject: [PATCH 11/16] Fix manual makefile build --- src/Makefile.manual | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Makefile.manual b/src/Makefile.manual index d15cbd5d9..06a99a472 100644 --- a/src/Makefile.manual +++ b/src/Makefile.manual @@ -129,5 +129,5 @@ stdlib_string_type.o: stdlib_ascii.o \ stdlib_kinds.o stdlib_strings.o: stdlib_ascii.o \ stdlib_string_type.o \ - stdlib_optval + stdlib_optval.o stdlib_math.o: stdlib_kinds.o From 4e923b4af45e66908f43236e84ab7891898d6e85 Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Thu, 17 Jun 2021 16:46:22 +0530 Subject: [PATCH 12/16] made find function elemental, updated test cases and documentation accordingly --- doc/specs/stdlib_strings.md | 13 ++++--- src/stdlib_strings.f90 | 8 ++--- src/tests/string/test_string_functions.f90 | 41 +++++++++++++--------- 3 files changed, 34 insertions(+), 28 deletions(-) diff --git a/doc/specs/stdlib_strings.md b/doc/specs/stdlib_strings.md index 46365a363..87ba68814 100644 --- a/doc/specs/stdlib_strings.md +++ b/doc/specs/stdlib_strings.md @@ -294,7 +294,7 @@ Experimental #### Class -Pure function +Elemental function #### Argument @@ -309,7 +309,7 @@ Pure function #### Result value -The result is of scalar integer type. +The result is a scalar of integer type or integer array of rank equal to the highest rank among all dummy arguments. #### Example @@ -320,12 +320,11 @@ program demo_find implicit none string_type :: string - string = "needle in this character-stack" + string = "needle in the character-stack" - print *, find(string, "needle") ! 1 - print *, find(string, "a", 3) ! 28 - print *, find("qwqwqwq", "qwq", 3, .false.) ! 0 - print *, find("qwqwqwq", "qwq", 3, .true.) ! 5 + print *, find(string, "needle") ! 1 + print *, find(string, ["a", "c"], [3, 2]) ! [27, 20] + print *, find("qwqwqwq", "qwq", 3, [.false., .true.]) ! [0, 5] end program demo_find ``` \ No newline at end of file diff --git a/src/stdlib_strings.f90 b/src/stdlib_strings.f90 index 38adf32e3..366c3ab68 100644 --- a/src/stdlib_strings.f90 +++ b/src/stdlib_strings.f90 @@ -379,7 +379,7 @@ end function slice_char !> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' !> in input 'string' !> Returns an integer - pure function find_string_string(string, pattern, occurrence, consider_overlapping) result(res) + elemental function find_string_string(string, pattern, occurrence, consider_overlapping) result(res) type(string_type), intent(in) :: string type(string_type), intent(in) :: pattern integer, intent(in), optional :: occurrence @@ -393,7 +393,7 @@ end function find_string_string !> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' !> in input 'string' !> Returns an integer - pure function find_string_char(string, pattern, occurrence, consider_overlapping) result(res) + elemental function find_string_char(string, pattern, occurrence, consider_overlapping) result(res) type(string_type), intent(in) :: string character(len=*), intent(in) :: pattern integer, intent(in), optional :: occurrence @@ -407,7 +407,7 @@ end function find_string_char !> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' !> in input 'string' !> Returns an integer - pure function find_char_string(string, pattern, occurrence, consider_overlapping) result(res) + elemental function find_char_string(string, pattern, occurrence, consider_overlapping) result(res) character(len=*), intent(in) :: string type(string_type), intent(in) :: pattern integer, intent(in), optional :: occurrence @@ -421,7 +421,7 @@ end function find_char_string !> Returns the starting index of the 'occurrence'th occurrence of substring 'pattern' !> in input 'string' !> Returns an integer - pure function find_char_char(string, pattern, occurrence, consider_overlapping) result(res) + elemental function find_char_char(string, pattern, occurrence, consider_overlapping) result(res) character(len=*), intent(in) :: string character(len=*), intent(in) :: pattern integer, intent(in), optional :: occurrence diff --git a/src/tests/string/test_string_functions.f90 b/src/tests/string/test_string_functions.f90 index 9b85aeb5a..194c9f1bb 100644 --- a/src/tests/string/test_string_functions.f90 +++ b/src/tests/string/test_string_functions.f90 @@ -163,27 +163,34 @@ subroutine test_slice_string end subroutine test_slice_string subroutine test_find - type(string_type) :: test_string, test_pattern - test_string = "qwqwqwqwqwqwqw" - test_pattern = "qwq" - call check(find(test_string, test_pattern, 4) == 7, & - & 'Find: test_string, test_pattern, 4') - call check(find(test_string, test_pattern, 3, .false.) == 9, & - & 'Find: test_string, test_pattern, 3') - call check(find(test_string, test_pattern, 7) == 0, & - & 'Find: test_string, test_pattern, 7') - call check(find("qwqwqwqwqwqwqw", test_pattern) == 1, & - & 'Find: "qwqwqwqwqwqwqw", test_pattern') - call check(find(test_string, "qwq", 2) == 3, & - & 'Find: test_string, "qwq", 2') + type(string_type) :: test_string_1, test_string_2, test_pattern_1, test_pattern_2 + test_string_1 = "qwqwqwqwqwqwqw" + test_string_2 = "abccbabccbabc" + test_pattern_1 = "qwq" + test_pattern_2 = "abccbabc" + + call check(all(find([test_string_1, test_string_2], test_pattern_1, 4) == [7, 0]), & + & 'Find: [test_string_1, test_string_2], test_pattern_1, 4') + call check(all(find(test_string_1, [test_pattern_1, test_pattern_2], 3, .false.) == [9, 0]), & + & 'Find: test_string_1, [test_pattern_1, test_pattern_2], 3, .false.') + call check(find(test_string_1, test_pattern_1, 7) == 0, & + & 'Find: test_string_1, test_pattern_1, 7') + call check(all(find([test_string_1, test_string_2, test_string_2], [test_pattern_1, & + & test_pattern_2, test_pattern_2], [7, 2, 2], [.true., .false., .true.]) == [0, 0, 6]), & + & 'Find: [test_string_1, test_string_2, test_string_2], [test_pattern_1, & + & test_pattern_2, test_pattern_2], [7, 2, 2], [.true., .false., .true.]') + call check(find("qwqwqwqwqwqwqw", test_pattern_1) == 1, & + & 'Find: "qwqwqwqwqwqwqw", test_pattern_1') + call check(all(find(test_string_1, ["qwq", "wqw"], 2) == [3, 4]), & + & 'Find: test_string_1, ["qwq", "wqw"], 2') call check(find("qwqwqwqwqwqwqw", "qwq", 2, .false.) == 5, & & 'Find: "qwqwqwqwqwqwqw", "qwq", 2, .false.') call check(find("", "") == 0, & & 'Find: "", ""') - call check(find("", test_pattern) == 0, & - & 'Find: "", test_pattern') - call check(find(test_string, "") == 0, & - & 'Find: test_string, ""') + call check(find("", test_pattern_1) == 0, & + & 'Find: "", test_pattern_1') + call check(find(test_string_1, "") == 0, & + & 'Find: test_string_1, ""') end subroutine test_find From 39920925354ea6c1c4fd30479437b08565dec4b1 Mon Sep 17 00:00:00 2001 From: Aman Godara <34789087+Aman-Godara@users.noreply.github.com> Date: Fri, 18 Jun 2021 16:10:32 +0530 Subject: [PATCH 13/16] updated "syntax" to highlight optional arguments as optional Co-authored-by: Jeremie Vandenplas --- doc/specs/stdlib_strings.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/specs/stdlib_strings.md b/doc/specs/stdlib_strings.md index 87ba68814..572326489 100644 --- a/doc/specs/stdlib_strings.md +++ b/doc/specs/stdlib_strings.md @@ -286,7 +286,7 @@ If `occurrence`th occurrence is not found, function returns `0`. #### Syntax -`string = [[stdlib_strings(module):find(interface)]] (string, pattern, occurrence, consider_overlapping)` +`string = [[stdlib_strings(module):find(interface)]] (string, pattern [, occurrence, consider_overlapping])` #### Status @@ -327,4 +327,4 @@ program demo_find print *, find("qwqwqwq", "qwq", 3, [.false., .true.]) ! [0, 5] end program demo_find -``` \ No newline at end of file +``` From a50814490eaa6444ec955084fad3f1bef9edb049 Mon Sep 17 00:00:00 2001 From: Aman Godara <34789087+Aman-Godara@users.noreply.github.com> Date: Fri, 18 Jun 2021 16:13:18 +0530 Subject: [PATCH 14/16] added specifications link comment Co-authored-by: Jeremie Vandenplas --- src/stdlib_strings.f90 | 1 + 1 file changed, 1 insertion(+) diff --git a/src/stdlib_strings.f90 b/src/stdlib_strings.f90 index 366c3ab68..89d5ba020 100644 --- a/src/stdlib_strings.f90 +++ b/src/stdlib_strings.f90 @@ -69,6 +69,7 @@ module stdlib_strings end interface slice !> Finds the starting index of substring 'pattern' in the input 'string' + !> [Specifications](link to the specs - to be completed) !> !> Version: experimental interface find From 768356f648be3c1fda53f38d0c04c693afd0d058 Mon Sep 17 00:00:00 2001 From: Aman Godara <34789087+Aman-Godara@users.noreply.github.com> Date: Fri, 18 Jun 2021 16:17:13 +0530 Subject: [PATCH 15/16] added "only" specifier after "use stdlib_string_type" Co-authored-by: Jeremie Vandenplas --- doc/specs/stdlib_strings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/specs/stdlib_strings.md b/doc/specs/stdlib_strings.md index 572326489..a8458f29c 100644 --- a/doc/specs/stdlib_strings.md +++ b/doc/specs/stdlib_strings.md @@ -315,7 +315,7 @@ The result is a scalar of integer type or integer array of rank equal to the hig ```fortran program demo_find - use stdlib_string_type + use stdlib_string_type, only: string_type, assignment(=) use stdlib_strings, only : find implicit none string_type :: string From d0fea861eeadf026f008aded5a7f0221814d1435 Mon Sep 17 00:00:00 2001 From: Aman-Godara Date: Fri, 18 Jun 2021 16:19:15 +0530 Subject: [PATCH 16/16] added optional specifier in syntax of slice function --- doc/specs/stdlib_strings.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/specs/stdlib_strings.md b/doc/specs/stdlib_strings.md index a8458f29c..19bbf4a59 100644 --- a/doc/specs/stdlib_strings.md +++ b/doc/specs/stdlib_strings.md @@ -221,7 +221,7 @@ and remains active until `last` index is crossed. #### Syntax -`string = [[stdlib_strings(module):slice(interface)]] (string, first, last, stride)` +`string = [[stdlib_strings(module):slice(interface)]] (string [, first, last, stride])` #### Status