diff --git a/doc/specs/stdlib_ascii.md b/doc/specs/stdlib_ascii.md index d38fe87bf..d80ae62ea 100644 --- a/doc/specs/stdlib_ascii.md +++ b/doc/specs/stdlib_ascii.md @@ -92,7 +92,7 @@ program demo_to_upper implicit none print'(a)', to_upper("hello!") ! returns "HELLO!" end program demo_to_upper -``` +``` ### `to_title` @@ -102,9 +102,12 @@ Experimental #### Description -Returns a capitalized version of an input character variable. -The first alphabetical character is transformed to uppercase unless it follows a numeral. -The rest of the character sequence is transformed to lowercase. +Returns the titlecase version of the input character variable. +Title case: First character of every word in the sentence is converted to +uppercase and the rest of the characters are converted to lowercase. +A word is a contiguous sequence of character(s) which consists of alphabetical +character(s) and numeral(s) only and doesn't exclude any alphabetical character +or numeral present next to either of its 2 ends. #### Syntax @@ -128,11 +131,52 @@ The result is an intrinsic character type of the same length as `string`. program demo_to_title use stdlib_ascii, only : to_title implicit none - print*, to_title("hello!") ! returns "Hello!" + print*, to_title("hello there!") ! returns "Hello There!" print*, to_title("'enquoted'") ! returns "'Enquoted'" print*, to_title("1st") ! returns "1st" end program demo_to_title -``` +``` + +### `to_sentence` + +#### Status + +Experimental + +#### Description + +Returns the sentencecase version of the input character variable. +The first alphabetical character of the sequence is transformed to uppercase +unless it follows a numeral. The rest of the characters in the sequence are +transformed to lowercase. + +#### Syntax + +`res = [[stdlib_ascii(module):to_sentence(function)]] (string)` + +#### Class + +Pure function. + +#### Argument + +`string`: shall be an intrinsic character type. It is an `intent(in)` argument. + +#### Result value + +The result is an intrinsic character type of the same length as `string`. + +#### Example + +```fortran +program demo_to_sentence + use stdlib_ascii, only : to_sentence + implicit none + print*, to_sentence("hello!") ! returns "Hello!" + print*, to_sentence("'enquoted'") ! returns "'Enquoted'" + print*, to_sentence("1st") ! returns "1st" + end program demo_to_sentence +``` ### `reverse` @@ -170,7 +214,6 @@ program demo_reverse end program demo_reverse ``` - ### `to_string` #### Status diff --git a/doc/specs/stdlib_string_type.md b/doc/specs/stdlib_string_type.md index 30e5c1755..76f5cd5c4 100644 --- a/doc/specs/stdlib_string_type.md +++ b/doc/specs/stdlib_string_type.md @@ -1130,7 +1130,8 @@ end program demo #### Description -Returns a new string_type instance which holds the lowercase version of the character sequence hold by the input string. +Returns a new string_type instance which holds the lowercase version of the +character sequence hold by the input string. #### Syntax @@ -1150,7 +1151,7 @@ Elemental function. #### Result Value -The Result is a scalar `string_type` value. +The result is a scalar `string_type` value. #### Example @@ -1175,7 +1176,8 @@ end program demo #### Description -Returns a new string_type instance which holds the uppercase version of the character sequence hold by the input string. +Returns a new string_type instance which holds the uppercase version of the +character sequence hold by the input string. #### Syntax @@ -1195,7 +1197,7 @@ Elemental function. #### Result Value -The Result is a scalar `string_type` value. +The result is a scalar `string_type` value. #### Example @@ -1220,9 +1222,13 @@ end program demo #### Description -Returns a new string_type instance which holds the titlecase (or capitalized) version of the character sequence hold by the input string. -Capitalized version: The first alphabetical character of the input character sequence is transformed to uppercase unless it -follows a numeral and the rest of the characters in the sequence are transformed to lowercase. +Returns a new string_type instance which holds the titlecase version +of the character sequence hold by the input string. +Title case: First character of every word in the sentence is converted to +uppercase and the rest of the characters are converted to lowercase. +A word is a contiguous sequence of character(s) which consists of alphabetical +character(s) and numeral(s) only and doesn't exclude any alphabetical character +or numeral present next to either of its 2 ends. #### Syntax @@ -1242,23 +1248,71 @@ Elemental function. #### Result Value -The Result is a scalar `string_type` value. +The result is a scalar `string_type` value. #### Example ```fortran -program demo - use stdlib_string_type +program demo_to_title + use stdlib_string_type, only: string_type, to_title implicit none type(string_type) :: string, titlecase_string - string = "Titlecase This String" - ! string <-- "Titlecase This String" + string = "titlecase this string." + ! string <-- "titlecase this string." titlecase_string = to_title(string) - ! string <-- "Titlecase This String" - ! titlecase_string <-- "Titlecase this string" -end program demo + ! string <-- "titlecase this string." + ! titlecase_string <-- "Titlecase This String." +end program demo_to_title +``` + + +### To\_sentence function + +#### Description + +Returns a new string_type instance which holds the sentencecase +version of the character sequence hold by the input string. +Sentencecase version: The first alphabetical character of the input character sequence +is transformed to uppercase unless it follows a numeral and the rest of the +characters in the sequence are transformed to lowercase. + +#### Syntax + +`sentencecase_string = [[stdlib_string_type(module): to_sentence(interface)]] (string)` + +#### Status + +Experimental + +#### Class + +Elemental function. + +#### Argument + +`string`: Instance of `string_type`. This argument is `intent(in)`. + +#### Result Value + +The result is a scalar `string_type` value. + +#### Example + +```fortran +program demo_to_sentence + use stdlib_string_type, only: string_type, to_sentence + implicit none + type(string_type) :: string, sentencecase_string + + string = "sentencecase this string." + ! string <-- "sentencecase this string." + + sentencecase_string = to_sentence(string) + ! string <-- "sentencecase this string." + ! sentencecase_string <-- "Sentencecase this string." +end program demo_to_sentence ``` @@ -1266,7 +1320,8 @@ end program demo #### Description -Returns a new string_type instance which holds the reversed version of the character sequence hold by the input string. +Returns a new string_type instance which holds the reversed version of the +character sequence hold by the input string. #### Syntax @@ -1286,7 +1341,7 @@ Elemental function. #### Result Value -The Result is a scalar `string_type` value. +The result is a scalar `string_type` value. #### Example diff --git a/src/Makefile.manual b/src/Makefile.manual index 8ad3fe61a..b372a8cb6 100644 --- a/src/Makefile.manual +++ b/src/Makefile.manual @@ -114,3 +114,4 @@ stdlib_stats_distribution_PRNG.o: \ stdlib_error.o stdlib_string_type.o: stdlib_ascii.o stdlib_kinds.o stdlib_strings.o: stdlib_ascii.o stdlib_string_type.o +stdlib_math.o: stdlib_kinds.o diff --git a/src/stdlib_ascii.fypp b/src/stdlib_ascii.fypp index 08816949a..ce7257d01 100644 --- a/src/stdlib_ascii.fypp +++ b/src/stdlib_ascii.fypp @@ -19,7 +19,7 @@ module stdlib_ascii public :: is_lower, is_upper ! Character conversion functions - public :: to_lower, to_upper, to_title, reverse + public :: to_lower, to_upper, to_title, to_sentence, reverse public :: to_string !> Version: experimental @@ -100,6 +100,13 @@ module stdlib_ascii module procedure :: to_title end interface to_title + !> Returns a new character sequence which is the sentence case + !> version of the input character sequence + !> This method is pure and returns a character sequence + interface to_sentence + module procedure :: to_sentence + end interface to_sentence + !> Returns a new character sequence which is reverse of !> the input charater sequence !> This method is pure and returns a character sequence @@ -284,31 +291,58 @@ contains end function to_upper - !> Convert character variable to title case + !> Converts character sequence to title case !> ([Specification](../page/specs/stdlib_ascii.html#to_title)) !> !> Version: experimental pure function to_title(string) result(title_string) character(len=*), intent(in) :: string character(len=len(string)) :: title_string + integer :: i + logical :: capitalize_switch + + capitalize_switch = .true. + do i = 1, len(string) + if (is_alphanum(string(i:i))) then + if (capitalize_switch) then + title_string(i:i) = char_to_upper(string(i:i)) + capitalize_switch = .false. + else + title_string(i:i) = char_to_lower(string(i:i)) + end if + else + title_string(i:i) = string(i:i) + capitalize_switch = .true. + end if + end do + + end function to_title + + !> Converts character sequence to sentence case + !> ([Specification](../page/specs/stdlib_ascii.html#to_sentence)) + !> + !> Version: experimental + pure function to_sentence(string) result(sentence_string) + character(len=*), intent(in) :: string + character(len=len(string)) :: sentence_string integer :: i, n n = len(string) do i = 1, len(string) if (is_alphanum(string(i:i))) then - title_string(i:i) = char_to_upper(string(i:i)) + sentence_string(i:i) = char_to_upper(string(i:i)) n = i exit else - title_string(i:i) = string(i:i) + sentence_string(i:i) = string(i:i) end if end do do i = n + 1, len(string) - title_string(i:i) = char_to_lower(string(i:i)) + sentence_string(i:i) = char_to_lower(string(i:i)) end do - end function to_title + end function to_sentence !> Reverse the character order in the input character variable !> ([Specification](../page/specs/stdlib_ascii.html#reverse)) diff --git a/src/stdlib_string_type.fypp b/src/stdlib_string_type.fypp index 21422cd21..772fa4642 100644 --- a/src/stdlib_string_type.fypp +++ b/src/stdlib_string_type.fypp @@ -14,7 +14,7 @@ !> The specification of this module is available [here](../page/specs/stdlib_string_type.html). module stdlib_string_type use stdlib_ascii, only: to_lower_ => to_lower, to_upper_ => to_upper, & - & to_title_ => to_title, reverse_ => reverse, to_string + & to_title_ => to_title, to_sentence_ => to_sentence, reverse_ => reverse, to_string use stdlib_kinds, only : int8, int16, int32, int64 implicit none private @@ -22,7 +22,7 @@ module stdlib_string_type public :: string_type public :: len, len_trim, trim, index, scan, verify, repeat, adjustr, adjustl public :: lgt, lge, llt, lle, char, ichar, iachar - public :: to_lower, to_upper, to_title, reverse + public :: to_lower, to_upper, to_title, to_sentence, reverse public :: assignment(=) public :: operator(>), operator(>=), operator(<), operator(<=) public :: operator(==), operator(/=), operator(//) @@ -122,9 +122,17 @@ module stdlib_string_type module procedure :: to_title_string end interface to_title + !> Returns the sentencecase version of the character sequence hold by the input string + !> + !> This method is elemental and returns a new string_type instance which holds this + !> sentencecase character sequence + interface to_sentence + module procedure :: to_sentence_string + end interface to_sentence + !> Reverses the character sequence hold by the input string !> - !> This method is Elemental and returns a new string_type instance which holds this + !> This method is elemental and returns a new string_type instance which holds this !> reverse character sequence interface reverse module procedure :: reverse_string @@ -535,6 +543,15 @@ contains end function to_title_string + !> Convert the character sequence hold by the input string to sentence case + elemental function to_sentence_string(string) result(sentence_string) + type(string_type), intent(in) :: string + type(string_type) :: sentence_string + + sentence_string%raw = to_sentence_(maybe(string)) + + end function to_sentence_string + !> Reverse the character sequence hold by the input string elemental function reverse_string(string) result(reversed_string) diff --git a/src/tests/ascii/test_ascii.f90 b/src/tests/ascii/test_ascii.f90 index ba8e377fa..e898e4998 100644 --- a/src/tests/ascii/test_ascii.f90 +++ b/src/tests/ascii/test_ascii.f90 @@ -6,7 +6,7 @@ program test_ascii whitespace, letters, is_alphanum, is_alpha, is_lower, is_upper, & is_digit, is_octal_digit, is_hex_digit, is_white, is_blank, & is_control, is_punctuation, is_graphical, is_printable, is_ascii, & - to_lower, to_upper, to_title, reverse, LF, TAB, NUL, DEL, & + to_lower, to_upper, to_title, to_sentence, reverse, LF, TAB, NUL, DEL, & to_string use stdlib_kinds, only : int8, int16, int32, int64 @@ -73,6 +73,7 @@ program test_ascii call test_to_upper_string call test_to_lower_string call test_to_title_string + call test_to_sentence_string call test_reverse_string call test_to_string @@ -583,26 +584,48 @@ end subroutine test_to_upper_string subroutine test_to_title_string character(len=:), allocatable :: dlc - character(len=32), parameter :: input = "tiTLe" + character(len=32), parameter :: input = "tHis Is tO bE tiTlEd" - dlc = to_title("tiTLe") - call check(dlc == "Title") + dlc = to_title("tHis Is tO bE tiTlEd") + call check(dlc == "This Is To Be Titled") dlc = to_title(input) call check(len(dlc) == 32) - call check(len_trim(dlc) == 5) - call check(trim(dlc) == "Title") + call check(len_trim(dlc) == 20) + call check(trim(dlc) == "This Is To Be Titled") dlc = to_title(" s P a C e D !") - call check(dlc == " S p a c e d !") + call check(dlc == " S P A C E D !") - dlc = to_title("1st, 2nd, 3rd") + dlc = to_title("1st, 2nD, 3RD") call check(dlc == "1st, 2nd, 3rd") dlc = to_title("""quOTed""") call check(dlc == """Quoted""") end subroutine test_to_title_string + subroutine test_to_sentence_string + character(len=:), allocatable :: dlc + character(len=32), parameter :: input = "tHis iS A seNteNcE." + + dlc = to_sentence("tHis iS A seNteNcE.") + call check(dlc == "This is a sentence.") + + dlc = to_sentence(input) + call check(len(dlc) == 32) + call check(len_trim(dlc) == 19) + call check(trim(dlc) == "This is a sentence.") + + dlc = to_sentence(" s P a C e D !") + call check(dlc == " S p a c e d !") + + dlc = to_sentence("1st, 2nd, 3rd") + call check(dlc == "1st, 2nd, 3rd") + + dlc = to_sentence("""quOTed""") + call check(dlc == """Quoted""") + end subroutine test_to_sentence_string + subroutine test_reverse_string character(len=:), allocatable :: dlc character(len=32), parameter :: input = "reversed" diff --git a/src/tests/string/test_string_functions.f90 b/src/tests/string/test_string_functions.f90 index 4a8d516a8..e7157697d 100644 --- a/src/tests/string/test_string_functions.f90 +++ b/src/tests/string/test_string_functions.f90 @@ -2,7 +2,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, reverse + to_lower, to_upper, to_title, to_sentence, reverse implicit none contains @@ -27,12 +27,21 @@ end subroutine test_to_upper_string subroutine test_to_title_string type(string_type) :: test_string, compare_string - test_string = "_#To tiTlE !$%-az09AZ" - compare_string = "_#To title !$%-az09az" + test_string = "tO_%t!TL3 7h1S p#ra$e" + compare_string = "To_%T!Tl3 7h1s P#Ra$E" call check(to_title(test_string) == compare_string) end subroutine test_to_title_string + + subroutine test_to_sentence_string + type(string_type) :: test_string, compare_string + test_string = "_#To seNtEncE !$%-az09AZ" + compare_string = "_#To sentence !$%-az09az" + + call check(to_sentence(test_string) == compare_string) + + end subroutine test_to_sentence_string subroutine test_reverse_string type(string_type) :: test_string, compare_string @@ -53,6 +62,7 @@ program tester call test_to_lower_string call test_to_upper_string call test_to_title_string + call test_to_sentence_string call test_reverse_string end program tester