Skip to content
57 changes: 50 additions & 7 deletions doc/specs/stdlib_ascii.md
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ program demo_to_upper
implicit none
print'(a)', to_upper("hello!") ! returns "HELLO!"
end program demo_to_upper
```
```

### `to_title`

Expand All @@ -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

Expand All @@ -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`

Expand Down Expand Up @@ -170,7 +214,6 @@ program demo_reverse
end program demo_reverse
```


### `to_string`

#### Status
Expand Down
89 changes: 72 additions & 17 deletions doc/specs/stdlib_string_type.md
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -1242,31 +1248,80 @@ 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
```

<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
### Reverse function

#### 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

Expand All @@ -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

Expand Down
1 change: 1 addition & 0 deletions src/Makefile.manual
Original file line number Diff line number Diff line change
Expand Up @@ -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
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_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))
Expand Down
23 changes: 20 additions & 3 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,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
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
Loading