@@ -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
@@ -144,22 +149,25 @@ pure logical function is_graphical(c)
144
149
pure logical function is_printable(c)
145
150
character (len= 1 ), intent (in ) :: c ! ! The character to test.
146
151
integer :: ic
147
- ic = iachar (c) ! '~'
148
- is_printable = c >= ' ' .and. ic <= int (z' 7E' )
152
+ ic = iachar (c)
153
+ ! The character is printable if it's between ' ' and '~' in the ASCII table
154
+ is_printable = ic >= iachar (' ' ) .and. ic <= int (z' 7E' )
149
155
end function
150
156
151
157
! > Checks whether `c` is a lowercase ASCII letter (a .. z).
152
158
pure logical function is_lower(c)
153
159
character (len= 1 ), intent (in ) :: c ! ! The character to test.
154
- is_lower = (c >= ' a' ) .and. (c <= ' z' )
160
+ integer :: ic
161
+ ic = iachar (c)
162
+ is_lower = ic >= iachar (' a' ) .and. ic <= iachar (' z' )
155
163
end function
156
164
157
165
! > Checks whether `c` is an uppercase ASCII letter (A .. Z).
158
166
pure logical function is_upper(c)
159
167
character (len= 1 ), intent (in ) :: c ! ! The character to test.
160
168
integer :: ic
161
169
ic = iachar (c)
162
- is_upper = ( ic >= iachar (' A' )) .and. ( ic <= iachar (' Z' ) )
170
+ is_upper = ic >= iachar (' A' ) .and. ic <= iachar (' Z' )
163
171
end function
164
172
165
173
! > Checks whether or not `c` is a whitespace character. That includes the
@@ -169,7 +177,7 @@ pure logical function is_white(c)
169
177
character (len= 1 ), intent (in ) :: c ! ! The character to test.
170
178
integer :: ic
171
179
ic = iachar (c) ! TAB, LF, VT, FF, CR
172
- 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' ))
173
181
end function
174
182
175
183
! > Checks whether or not `c` is a blank character. That includes the
@@ -178,31 +186,39 @@ pure logical function is_blank(c)
178
186
character (len= 1 ), intent (in ) :: c ! ! The character to test.
179
187
integer :: ic
180
188
ic = iachar (c) ! TAB
181
- is_blank = ( ic == iachar (' ' )) .or. ( ic == int (z' 09' ));
189
+ is_blank = ic == iachar (' ' ) .or. ic == int (z' 09' )
182
190
end function
183
191
184
192
! > Returns the corresponding lowercase letter, if `c` is an uppercase
185
193
! ASCII character, otherwise `c` itself.
186
194
pure function to_lower (c ) result(t)
187
195
character (len= 1 ), intent (in ) :: c ! ! A character.
188
- character (len= 1 ) :: t
189
- integer :: diff
190
- diff = iachar (' A' )- iachar (' a' )
191
- t = c
192
- ! if uppercase, make lowercase
193
- 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
194
206
end function
195
207
196
208
! > Returns the corresponding uppercase letter, if `c` is a lowercase
197
209
! ASCII character, otherwise `c` itself.
198
210
pure function to_upper (c ) result(t)
199
211
character (len= 1 ), intent (in ) :: c ! ! A character.
200
- character (len= 1 ) :: t
201
- integer :: diff
202
- diff = iachar (' A' )- iachar (' a' )
203
- t = c
204
- ! if lowercase, make uppercase
205
- 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
206
222
end function
207
223
208
224
end module
0 commit comments