@@ -60,6 +60,9 @@ module stdlib_ascii
60
60
character (len=* ), public , parameter :: lowercase = letters(27 :) ! ! a .. z
61
61
character (len=* ), public , parameter :: whitespace = " " // TAB// VT// CR// LF// FF ! ! ASCII _whitespace
62
62
63
+ character (len= 26 ), parameter , private :: lower_case = ' abcdefghijklmnopqrstuvwxyz'
64
+ character (len= 26 ), parameter , private :: upper_case = ' ABCDEFGHIJKLMNOPQRSTUVWXYZ'
65
+
63
66
contains
64
67
65
68
! > Checks whether `c` is an ASCII letter (A .. Z, a .. z).
@@ -135,7 +138,9 @@ pure logical function is_punctuation(c)
135
138
pure logical function is_graphical(c)
136
139
character (len= 1 ), intent (in ) :: c ! ! The character to test.
137
140
integer :: ic
138
- ic = iachar (c) ! '!' '~'
141
+ ic = iachar (c)
142
+ ! The character is graphical if it's between '!' and '~' in the ASCII table,
143
+ ! that is: printable but not a space
139
144
is_graphical = (int (z' 21' ) <= ic) .and. (ic <= int (z' 7E' ))
140
145
end function
141
146
@@ -162,7 +167,7 @@ pure logical function is_upper(c)
162
167
character (len= 1 ), intent (in ) :: c ! ! The character to test.
163
168
integer :: ic
164
169
ic = iachar (c)
165
- is_upper = ( ic >= iachar (' A' )) .and. ( ic <= iachar (' Z' ) )
170
+ is_upper = ic >= iachar (' A' ) .and. ic <= iachar (' Z' )
166
171
end function
167
172
168
173
! > Checks whether or not `c` is a whitespace character. That includes the
@@ -172,7 +177,7 @@ pure logical function is_white(c)
172
177
character (len= 1 ), intent (in ) :: c ! ! The character to test.
173
178
integer :: ic
174
179
ic = iachar (c) ! TAB, LF, VT, FF, CR
175
- is_white = ( ic == iachar (' ' )) .or. (ic >= int (z' 09' ) .and. ic <= int (z' 0D' ));
180
+ is_white = ic == iachar (' ' ) .or. (ic >= int (z' 09' ) .and. ic <= int (z' 0D' ))
176
181
end function
177
182
178
183
! > Checks whether or not `c` is a blank character. That includes the
@@ -181,31 +186,39 @@ pure logical function is_blank(c)
181
186
character (len= 1 ), intent (in ) :: c ! ! The character to test.
182
187
integer :: ic
183
188
ic = iachar (c) ! TAB
184
- is_blank = ( ic == iachar (' ' )) .or. ( ic == int (z' 09' ));
189
+ is_blank = ic == iachar (' ' ) .or. ic == int (z' 09' )
185
190
end function
186
191
187
192
! > Returns the corresponding lowercase letter, if `c` is an uppercase
188
193
! ASCII character, otherwise `c` itself.
189
194
pure function to_lower (c ) result(t)
190
195
character (len= 1 ), intent (in ) :: c ! ! A character.
191
- character (len= 1 ) :: t
192
- integer :: diff
193
- diff = iachar (' A' )- iachar (' a' )
194
- t = c
195
- ! if uppercase, make lowercase
196
- if (is_upper(t)) t = achar (iachar (t) - diff)
196
+ character (len= 1 ) :: t
197
+ integer :: k
198
+
199
+ k = index ( upper_case, c )
200
+
201
+ if ( k > 0 ) then
202
+ t = lower_case(k:k)
203
+ else
204
+ t = c
205
+ endif
197
206
end function
198
207
199
208
! > Returns the corresponding uppercase letter, if `c` is a lowercase
200
209
! ASCII character, otherwise `c` itself.
201
210
pure function to_upper (c ) result(t)
202
211
character (len= 1 ), intent (in ) :: c ! ! A character.
203
- character (len= 1 ) :: t
204
- integer :: diff
205
- diff = iachar (' A' )- iachar (' a' )
206
- t = c
207
- ! if lowercase, make uppercase
208
- if (is_lower(t)) t = achar (iachar (t) + diff)
212
+ character (len= 1 ) :: t
213
+ integer :: k
214
+
215
+ k = index ( lower_case, c )
216
+
217
+ if ( k > 0 ) then
218
+ t = upper_case(k:k)
219
+ else
220
+ t = c
221
+ endif
209
222
end function
210
223
211
224
end module
0 commit comments