Skip to content
46 changes: 40 additions & 6 deletions src/stdlib_ascii.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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_alpha(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))
Expand Down
21 changes: 19 additions & 2 deletions src/stdlib_string_type.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -14,15 +14,15 @@
!> 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

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(//)
Expand Down Expand Up @@ -122,6 +122,14 @@ 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
Expand Down Expand Up @@ -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)
Expand Down
41 changes: 32 additions & 9 deletions src/tests/ascii/test_ascii.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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")
call check(dlc == "1st, 2nd, 3rd")
dlc = to_title("1st, 2nd, 3rD, 4TH")
call check(dlc == "1St, 2Nd, 3Rd, 4Th")

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"
Expand Down
16 changes: 13 additions & 3 deletions src/tests/string/test_string_functions.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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 t8iTLE_th!s p#ra$e"
compare_string = "_To T8Itle_Th!S 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
Expand All @@ -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