Skip to content

Commit 1822e3f

Browse files
authored
changed to_title to to_sentence and implemented correct to_title (#407)
2 parents 5f3e2f5 + 696af49 commit 1822e3f

7 files changed

+227
-44
lines changed

doc/specs/stdlib_ascii.md

+50-7
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ program demo_to_upper
9292
implicit none
9393
print'(a)', to_upper("hello!") ! returns "HELLO!"
9494
end program demo_to_upper
95-
```
95+
```
9696

9797
### `to_title`
9898

@@ -102,9 +102,12 @@ Experimental
102102

103103
#### Description
104104

105-
Returns a capitalized version of an input character variable.
106-
The first alphabetical character is transformed to uppercase unless it follows a numeral.
107-
The rest of the character sequence is transformed to lowercase.
105+
Returns the titlecase version of the input character variable.
106+
Title case: First character of every word in the sentence is converted to
107+
uppercase and the rest of the characters are converted to lowercase.
108+
A word is a contiguous sequence of character(s) which consists of alphabetical
109+
character(s) and numeral(s) only and doesn't exclude any alphabetical character
110+
or numeral present next to either of its 2 ends.
108111

109112
#### Syntax
110113

@@ -128,11 +131,52 @@ The result is an intrinsic character type of the same length as `string`.
128131
program demo_to_title
129132
use stdlib_ascii, only : to_title
130133
implicit none
131-
print*, to_title("hello!") ! returns "Hello!"
134+
print*, to_title("hello there!") ! returns "Hello There!"
132135
print*, to_title("'enquoted'") ! returns "'Enquoted'"
133136
print*, to_title("1st") ! returns "1st"
134137
end program demo_to_title
135-
```
138+
```
139+
140+
### `to_sentence`
141+
142+
#### Status
143+
144+
Experimental
145+
146+
#### Description
147+
148+
Returns the sentencecase version of the input character variable.
149+
The first alphabetical character of the sequence is transformed to uppercase
150+
unless it follows a numeral. The rest of the characters in the sequence are
151+
transformed to lowercase.
152+
153+
#### Syntax
154+
155+
`res = [[stdlib_ascii(module):to_sentence(function)]] (string)`
156+
157+
#### Class
158+
159+
Pure function.
160+
161+
#### Argument
162+
163+
`string`: shall be an intrinsic character type. It is an `intent(in)` argument.
164+
165+
#### Result value
166+
167+
The result is an intrinsic character type of the same length as `string`.
168+
169+
#### Example
170+
171+
```fortran
172+
program demo_to_sentence
173+
use stdlib_ascii, only : to_sentence
174+
implicit none
175+
print*, to_sentence("hello!") ! returns "Hello!"
176+
print*, to_sentence("'enquoted'") ! returns "'Enquoted'"
177+
print*, to_sentence("1st") ! returns "1st"
178+
end program demo_to_sentence
179+
```
136180

137181
### `reverse`
138182

@@ -170,7 +214,6 @@ program demo_reverse
170214
end program demo_reverse
171215
```
172216

173-
174217
### `to_string`
175218

176219
#### Status

doc/specs/stdlib_string_type.md

+72-17
Original file line numberDiff line numberDiff line change
@@ -1130,7 +1130,8 @@ end program demo
11301130

11311131
#### Description
11321132

1133-
Returns a new string_type instance which holds the lowercase version of the character sequence hold by the input string.
1133+
Returns a new string_type instance which holds the lowercase version of the
1134+
character sequence hold by the input string.
11341135

11351136
#### Syntax
11361137

@@ -1150,7 +1151,7 @@ Elemental function.
11501151

11511152
#### Result Value
11521153

1153-
The Result is a scalar `string_type` value.
1154+
The result is a scalar `string_type` value.
11541155

11551156
#### Example
11561157

@@ -1175,7 +1176,8 @@ end program demo
11751176

11761177
#### Description
11771178

1178-
Returns a new string_type instance which holds the uppercase version of the character sequence hold by the input string.
1179+
Returns a new string_type instance which holds the uppercase version of the
1180+
character sequence hold by the input string.
11791181

11801182
#### Syntax
11811183

@@ -1195,7 +1197,7 @@ Elemental function.
11951197

11961198
#### Result Value
11971199

1198-
The Result is a scalar `string_type` value.
1200+
The result is a scalar `string_type` value.
11991201

12001202
#### Example
12011203

@@ -1220,9 +1222,13 @@ end program demo
12201222

12211223
#### Description
12221224

1223-
Returns a new string_type instance which holds the titlecase (or capitalized) version of the character sequence hold by the input string.
1224-
Capitalized version: The first alphabetical character of the input character sequence is transformed to uppercase unless it
1225-
follows a numeral and the rest of the characters in the sequence are transformed to lowercase.
1225+
Returns a new string_type instance which holds the titlecase version
1226+
of the character sequence hold by the input string.
1227+
Title case: First character of every word in the sentence is converted to
1228+
uppercase and the rest of the characters are converted to lowercase.
1229+
A word is a contiguous sequence of character(s) which consists of alphabetical
1230+
character(s) and numeral(s) only and doesn't exclude any alphabetical character
1231+
or numeral present next to either of its 2 ends.
12261232

12271233
#### Syntax
12281234

@@ -1242,31 +1248,80 @@ Elemental function.
12421248

12431249
#### Result Value
12441250

1245-
The Result is a scalar `string_type` value.
1251+
The result is a scalar `string_type` value.
12461252

12471253
#### Example
12481254

12491255
```fortran
1250-
program demo
1251-
use stdlib_string_type
1256+
program demo_to_title
1257+
use stdlib_string_type, only: string_type, to_title
12521258
implicit none
12531259
type(string_type) :: string, titlecase_string
12541260
1255-
string = "Titlecase This String"
1256-
! string <-- "Titlecase This String"
1261+
string = "titlecase this string."
1262+
! string <-- "titlecase this string."
12571263
12581264
titlecase_string = to_title(string)
1259-
! string <-- "Titlecase This String"
1260-
! titlecase_string <-- "Titlecase this string"
1261-
end program demo
1265+
! string <-- "titlecase this string."
1266+
! titlecase_string <-- "Titlecase This String."
1267+
end program demo_to_title
1268+
```
1269+
1270+
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
1271+
### To\_sentence function
1272+
1273+
#### Description
1274+
1275+
Returns a new string_type instance which holds the sentencecase
1276+
version of the character sequence hold by the input string.
1277+
Sentencecase version: The first alphabetical character of the input character sequence
1278+
is transformed to uppercase unless it follows a numeral and the rest of the
1279+
characters in the sequence are transformed to lowercase.
1280+
1281+
#### Syntax
1282+
1283+
`sentencecase_string = [[stdlib_string_type(module): to_sentence(interface)]] (string)`
1284+
1285+
#### Status
1286+
1287+
Experimental
1288+
1289+
#### Class
1290+
1291+
Elemental function.
1292+
1293+
#### Argument
1294+
1295+
`string`: Instance of `string_type`. This argument is `intent(in)`.
1296+
1297+
#### Result Value
1298+
1299+
The result is a scalar `string_type` value.
1300+
1301+
#### Example
1302+
1303+
```fortran
1304+
program demo_to_sentence
1305+
use stdlib_string_type, only: string_type, to_sentence
1306+
implicit none
1307+
type(string_type) :: string, sentencecase_string
1308+
1309+
string = "sentencecase this string."
1310+
! string <-- "sentencecase this string."
1311+
1312+
sentencecase_string = to_sentence(string)
1313+
! string <-- "sentencecase this string."
1314+
! sentencecase_string <-- "Sentencecase this string."
1315+
end program demo_to_sentence
12621316
```
12631317

12641318
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
12651319
### Reverse function
12661320

12671321
#### Description
12681322

1269-
Returns a new string_type instance which holds the reversed version of the character sequence hold by the input string.
1323+
Returns a new string_type instance which holds the reversed version of the
1324+
character sequence hold by the input string.
12701325

12711326
#### Syntax
12721327

@@ -1286,7 +1341,7 @@ Elemental function.
12861341

12871342
#### Result Value
12881343

1289-
The Result is a scalar `string_type` value.
1344+
The result is a scalar `string_type` value.
12901345

12911346
#### Example
12921347

src/Makefile.manual

+1
Original file line numberDiff line numberDiff line change
@@ -114,3 +114,4 @@ stdlib_stats_distribution_PRNG.o: \
114114
stdlib_error.o
115115
stdlib_string_type.o: stdlib_ascii.o stdlib_kinds.o
116116
stdlib_strings.o: stdlib_ascii.o stdlib_string_type.o
117+
stdlib_math.o: stdlib_kinds.o

src/stdlib_ascii.fypp

+40-6
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ module stdlib_ascii
1919
public :: is_lower, is_upper
2020

2121
! Character conversion functions
22-
public :: to_lower, to_upper, to_title, reverse
22+
public :: to_lower, to_upper, to_title, to_sentence, reverse
2323
public :: to_string
2424

2525
!> Version: experimental
@@ -100,6 +100,13 @@ module stdlib_ascii
100100
module procedure :: to_title
101101
end interface to_title
102102

103+
!> Returns a new character sequence which is the sentence case
104+
!> version of the input character sequence
105+
!> This method is pure and returns a character sequence
106+
interface to_sentence
107+
module procedure :: to_sentence
108+
end interface to_sentence
109+
103110
!> Returns a new character sequence which is reverse of
104111
!> the input charater sequence
105112
!> This method is pure and returns a character sequence
@@ -284,31 +291,58 @@ contains
284291

285292
end function to_upper
286293

287-
!> Convert character variable to title case
294+
!> Converts character sequence to title case
288295
!> ([Specification](../page/specs/stdlib_ascii.html#to_title))
289296
!>
290297
!> Version: experimental
291298
pure function to_title(string) result(title_string)
292299
character(len=*), intent(in) :: string
293300
character(len=len(string)) :: title_string
301+
integer :: i
302+
logical :: capitalize_switch
303+
304+
capitalize_switch = .true.
305+
do i = 1, len(string)
306+
if (is_alphanum(string(i:i))) then
307+
if (capitalize_switch) then
308+
title_string(i:i) = char_to_upper(string(i:i))
309+
capitalize_switch = .false.
310+
else
311+
title_string(i:i) = char_to_lower(string(i:i))
312+
end if
313+
else
314+
title_string(i:i) = string(i:i)
315+
capitalize_switch = .true.
316+
end if
317+
end do
318+
319+
end function to_title
320+
321+
!> Converts character sequence to sentence case
322+
!> ([Specification](../page/specs/stdlib_ascii.html#to_sentence))
323+
!>
324+
!> Version: experimental
325+
pure function to_sentence(string) result(sentence_string)
326+
character(len=*), intent(in) :: string
327+
character(len=len(string)) :: sentence_string
294328
integer :: i, n
295329

296330
n = len(string)
297331
do i = 1, len(string)
298332
if (is_alphanum(string(i:i))) then
299-
title_string(i:i) = char_to_upper(string(i:i))
333+
sentence_string(i:i) = char_to_upper(string(i:i))
300334
n = i
301335
exit
302336
else
303-
title_string(i:i) = string(i:i)
337+
sentence_string(i:i) = string(i:i)
304338
end if
305339
end do
306340

307341
do i = n + 1, len(string)
308-
title_string(i:i) = char_to_lower(string(i:i))
342+
sentence_string(i:i) = char_to_lower(string(i:i))
309343
end do
310344

311-
end function to_title
345+
end function to_sentence
312346

313347
!> Reverse the character order in the input character variable
314348
!> ([Specification](../page/specs/stdlib_ascii.html#reverse))

src/stdlib_string_type.fypp

+20-3
Original file line numberDiff line numberDiff line change
@@ -14,15 +14,15 @@
1414
!> The specification of this module is available [here](../page/specs/stdlib_string_type.html).
1515
module stdlib_string_type
1616
use stdlib_ascii, only: to_lower_ => to_lower, to_upper_ => to_upper, &
17-
& to_title_ => to_title, reverse_ => reverse, to_string
17+
& to_title_ => to_title, to_sentence_ => to_sentence, reverse_ => reverse, to_string
1818
use stdlib_kinds, only : int8, int16, int32, int64
1919
implicit none
2020
private
2121

2222
public :: string_type
2323
public :: len, len_trim, trim, index, scan, verify, repeat, adjustr, adjustl
2424
public :: lgt, lge, llt, lle, char, ichar, iachar
25-
public :: to_lower, to_upper, to_title, reverse
25+
public :: to_lower, to_upper, to_title, to_sentence, reverse
2626
public :: assignment(=)
2727
public :: operator(>), operator(>=), operator(<), operator(<=)
2828
public :: operator(==), operator(/=), operator(//)
@@ -122,9 +122,17 @@ module stdlib_string_type
122122
module procedure :: to_title_string
123123
end interface to_title
124124

125+
!> Returns the sentencecase version of the character sequence hold by the input string
126+
!>
127+
!> This method is elemental and returns a new string_type instance which holds this
128+
!> sentencecase character sequence
129+
interface to_sentence
130+
module procedure :: to_sentence_string
131+
end interface to_sentence
132+
125133
!> Reverses the character sequence hold by the input string
126134
!>
127-
!> This method is Elemental and returns a new string_type instance which holds this
135+
!> This method is elemental and returns a new string_type instance which holds this
128136
!> reverse character sequence
129137
interface reverse
130138
module procedure :: reverse_string
@@ -535,6 +543,15 @@ contains
535543

536544
end function to_title_string
537545

546+
!> Convert the character sequence hold by the input string to sentence case
547+
elemental function to_sentence_string(string) result(sentence_string)
548+
type(string_type), intent(in) :: string
549+
type(string_type) :: sentence_string
550+
551+
sentence_string%raw = to_sentence_(maybe(string))
552+
553+
end function to_sentence_string
554+
538555

539556
!> Reverse the character sequence hold by the input string
540557
elemental function reverse_string(string) result(reversed_string)

0 commit comments

Comments
 (0)