1
+ ! > The `stdlib_ascii` module provides procedures for handling and manipulating
2
+ ! > intrinsic character variables and constants.
3
+ ! >
4
+ ! > The specification of this module is available [here](../page/specs/stdlib_ascii.html).
1
5
module stdlib_ascii
2
6
3
7
implicit none
@@ -12,7 +16,7 @@ module stdlib_ascii
12
16
public :: is_lower, is_upper
13
17
14
18
! Character conversion functions
15
- public :: to_lower, to_upper
19
+ public :: to_lower, to_upper, to_title, reverse
16
20
17
21
! All control characters in the ASCII table (see www.asciitable.com).
18
22
character (len= 1 ), public , parameter :: NUL = achar (int (z' 00' )) ! ! Null
@@ -60,9 +64,6 @@ module stdlib_ascii
60
64
character (len=* ), public , parameter :: lowercase = letters(27 :) ! ! a .. z
61
65
character (len=* ), public , parameter :: whitespace = " " // TAB// VT// CR// LF// FF ! ! ASCII _whitespace
62
66
63
- character (len= 26 ), parameter , private :: lower_case = ' abcdefghijklmnopqrstuvwxyz'
64
- character (len= 26 ), parameter , private :: upper_case = ' ABCDEFGHIJKLMNOPQRSTUVWXYZ'
65
-
66
67
contains
67
68
68
69
! > Checks whether `c` is an ASCII letter (A .. Z, a .. z).
@@ -79,7 +80,7 @@ pure logical function is_alphanum(c)
79
80
end function
80
81
81
82
! > Checks whether or not `c` is in the ASCII character set -
82
- ! i.e. in the range 0 .. 0x7F.
83
+ ! > i.e. in the range 0 .. 0x7F.
83
84
pure logical function is_ascii(c)
84
85
character (len= 1 ), intent (in ) :: c ! ! The character to test.
85
86
is_ascii = iachar (c) <= int (z' 7F' )
@@ -113,8 +114,8 @@ pure logical function is_hex_digit(c)
113
114
end function
114
115
115
116
! > Checks whether or not `c` is a punctuation character. That includes
116
- ! all ASCII characters which are not control characters, letters,
117
- ! digits, or whitespace.
117
+ ! > all ASCII characters which are not control characters, letters,
118
+ ! > digits, or whitespace.
118
119
pure logical function is_punctuation(c)
119
120
character (len= 1 ), intent (in ) :: c ! ! The character to test.
120
121
integer :: ic
@@ -124,7 +125,7 @@ pure logical function is_punctuation(c)
124
125
end function
125
126
126
127
! > Checks whether or not `c` is a printable character other than the
127
- ! space character.
128
+ ! > space character.
128
129
pure logical function is_graphical(c)
129
130
character (len= 1 ), intent (in ) :: c ! ! The character to test.
130
131
integer :: ic
@@ -135,7 +136,7 @@ pure logical function is_graphical(c)
135
136
end function
136
137
137
138
! > Checks whether or not `c` is a printable character - including the
138
- ! space character.
139
+ ! > space character.
139
140
pure logical function is_printable(c)
140
141
character (len= 1 ), intent (in ) :: c ! ! The character to test.
141
142
integer :: ic
@@ -159,8 +160,8 @@ pure logical function is_upper(c)
159
160
end function
160
161
161
162
! > Checks whether or not `c` is a whitespace character. That includes the
162
- ! space, tab, vertical tab, form feed, carriage return, and linefeed
163
- ! characters.
163
+ ! > space, tab, vertical tab, form feed, carriage return, and linefeed
164
+ ! > characters.
164
165
pure logical function is_white(c)
165
166
character (len= 1 ), intent (in ) :: c ! ! The character to test.
166
167
integer :: ic
@@ -169,7 +170,7 @@ pure logical function is_white(c)
169
170
end function
170
171
171
172
! > Checks whether or not `c` is a blank character. That includes the
172
- ! only the space and tab characters
173
+ ! > only the space and tab characters
173
174
pure logical function is_blank(c)
174
175
character (len= 1 ), intent (in ) :: c ! ! The character to test.
175
176
integer :: ic
@@ -178,35 +179,107 @@ pure logical function is_blank(c)
178
179
end function
179
180
180
181
! > Returns the corresponding lowercase letter, if `c` is an uppercase
181
- ! ASCII character, otherwise `c` itself.
182
- pure function to_lower (c ) result(t)
182
+ ! > ASCII character, otherwise `c` itself.
183
+ pure function char_to_lower (c ) result(t)
183
184
character (len= 1 ), intent (in ) :: c ! ! A character.
184
185
character (len= 1 ) :: t
185
186
integer :: k
186
187
187
- k = index ( upper_case , c )
188
+ k = index ( uppercase , c )
188
189
189
190
if ( k > 0 ) then
190
- t = lower_case (k:k)
191
+ t = lowercase (k:k)
191
192
else
192
193
t = c
193
194
endif
194
- end function
195
+ end function char_to_lower
195
196
196
197
! > Returns the corresponding uppercase letter, if `c` is a lowercase
197
- ! ASCII character, otherwise `c` itself.
198
- pure function to_upper (c ) result(t)
198
+ ! > ASCII character, otherwise `c` itself.
199
+ pure function char_to_upper (c ) result(t)
199
200
character (len= 1 ), intent (in ) :: c ! ! A character.
200
201
character (len= 1 ) :: t
201
202
integer :: k
202
203
203
- k = index ( lower_case , c )
204
+ k = index ( lowercase , c )
204
205
205
206
if ( k > 0 ) then
206
- t = upper_case (k:k)
207
+ t = uppercase (k:k)
207
208
else
208
209
t = c
209
210
endif
210
- end function
211
+ end function char_to_upper
212
+
213
+ ! > Convert character variable to lower case
214
+ ! > ([Specification](../page/specs/stdlib_ascii.html#to_lower))
215
+ ! >
216
+ ! > Version: experimental
217
+ pure function to_lower (string ) result(lower_string)
218
+ character (len=* ), intent (in ) :: string
219
+ character (len= len (string)) :: lower_string
220
+ integer :: i
221
+
222
+ do i = 1 , len (string)
223
+ lower_string(i:i) = char_to_lower(string (i:i))
224
+ end do
225
+
226
+ end function to_lower
227
+
228
+ ! > Convert character variable to upper case
229
+ ! > ([Specification](../page/specs/stdlib_ascii.html#to_upper))
230
+ ! >
231
+ ! > Version: experimental
232
+ pure function to_upper (string ) result(upper_string)
233
+ character (len=* ), intent (in ) :: string
234
+ character (len= len (string)) :: upper_string
235
+ integer :: i
236
+
237
+ do i = 1 , len (string)
238
+ upper_string(i:i) = char_to_upper(string (i:i))
239
+ end do
240
+
241
+ end function to_upper
242
+
243
+ ! > Convert character variable to title case
244
+ ! > ([Specification](../page/specs/stdlib_ascii.html#to_title))
245
+ ! >
246
+ ! > Version: experimental
247
+ pure function to_title (string ) result(title_string)
248
+ character (len=* ), intent (in ) :: string
249
+ character (len= len (string)) :: title_string
250
+ integer :: i, n
251
+
252
+ n = len (string)
253
+ do i = 1 , len (string)
254
+ if (is_alphanum(string (i:i))) then
255
+ title_string(i:i) = char_to_upper(string (i:i))
256
+ n = i
257
+ exit
258
+ else
259
+ title_string(i:i) = string (i:i)
260
+ end if
261
+ end do
262
+
263
+ do i = n + 1 , len (string)
264
+ title_string(i:i) = char_to_lower(string (i:i))
265
+ end do
266
+
267
+ end function to_title
268
+
269
+ ! > Reverse the character order in the input character variable
270
+ ! > ([Specification](../page/specs/stdlib_ascii.html#reverse))
271
+ ! >
272
+ ! > Version: experimental
273
+ pure function reverse (string ) result(reverse_string)
274
+ character (len=* ), intent (in ) :: string
275
+ character (len= len (string)) :: reverse_string
276
+ integer :: i, n
277
+
278
+ n = len (string)
279
+ do i = 1 , n
280
+ reverse_string(n- i+1 :n- i+1 ) = string (i:i)
281
+ end do
282
+
283
+ end function reverse
211
284
212
- end module
285
+ end module stdlib_ascii
0 commit comments