@@ -65,14 +65,18 @@ module stdlib_ascii
6565 ! > Checks whether `c` is an ASCII letter (A .. Z, a .. z).
6666 pure logical function is_alpha(c)
6767 character (len= 1 ), intent (in ) :: c ! ! The character to test.
68- is_alpha = (c >= ' A' .and. c <= ' Z' ) .or. (c >= ' a' .and. c <= ' z' )
68+ integer :: ic
69+ ic = iachar (c)
70+ is_alpha = (ic >= iachar (' A' ) .and. ic <= iachar (' Z' )) .or. (ic >= iachar (' a' ) .and. ic <= iachar (' z' ))
6971 end function
7072
7173 ! > Checks whether `c` is a letter or a number (0 .. 9, a .. z, A .. Z).
7274 pure logical function is_alphanum(c)
7375 character (len= 1 ), intent (in ) :: c ! ! The character to test.
74- is_alphanum = (c >= ' 0' .and. c <= ' 9' ) .or. (c >= ' a' .and. c <= ' z' ) &
75- .or. (c >= ' A' .and. c <= ' Z' )
76+ integer :: ic
77+ ic = iachar (c)
78+ is_alphanum = (ic >= iachar (' 0' ) .and. ic <= iachar (' 9' )) .or. (ic >= iachar (' a' ) .and. ic <= iachar (' z' )) &
79+ .or. (ic >= iachar (' A' ) .and. ic <= iachar (' Z' ))
7680 end function
7781
7882 ! > Checks whether or not `c` is in the ASCII character set -
@@ -93,20 +97,25 @@ pure logical function is_control(c)
9397 ! > Checks whether `c` is a digit (0 .. 9).
9498 pure logical function is_digit(c)
9599 character (len= 1 ), intent (in ) :: c ! ! The character to test.
96- is_digit = (' 0' <= c) .and. (c <= ' 9' )
100+ integer :: ic
101+ is_digit = (iachar (' 0' ) <= ic) .and. (ic <= iachar (' 9' ))
97102 end function
98103
99104 ! > Checks whether `c` is a digit in base 8 (0 .. 7).
100105 pure logical function is_octal_digit(c)
101106 character (len= 1 ), intent (in ) :: c ! ! The character to test.
102- is_octal_digit = (c >= ' 0' ) .and. (c <= ' 7' );
107+ integer :: ic
108+ ic = iachar (c)
109+ is_octal_digit = (ic >= iachar (' 0' )) .and. (ic <= iachar (' 7' ))
103110 end function
104111
105112 ! > Checks whether `c` is a digit in base 16 (0 .. 9, A .. F, a .. f).
106- pure logical function is_hex_digit(c )
113+ pure logical function is_hex_digit(cin )
107114 character (len= 1 ), intent (in ) :: c ! ! The character to test.
108- is_hex_digit = (c >= ' 0' .and. c <= ' 9' ) .or. (c >= ' a' .and. c <= ' f' ) &
109- .or. (c >= ' A' .and. c <= ' F' )
115+ integer :: ic
116+ ic = iachar (c)
117+ is_hex_digit = (ic >= iachar (' 0' ) .and. ic <= iachar (' 9' )) .or. (ic >= iachar (' a' ) .and. ic <= iachar (' f' )) &
118+ .or. (ic >= iachar (' A' ) .and. ic <= iachar (' F' )) .or. (ic >= iachar (' a' ) .and. ic <= iachar (' f' ))
110119 end function
111120
112121 ! > Checks whether or not `c` is a punctuation character. That includes
@@ -139,15 +148,17 @@ pure logical function is_printable(c)
139148 end function
140149
141150 ! > Checks whether `c` is a lowercase ASCII letter (a .. z).
142- pure logical function is_lower(c )
151+ pure logical function is_lower(cin )
143152 character (len= 1 ), intent (in ) :: c ! ! The character to test.
144153 is_lower = (c >= ' a' ) .and. (c <= ' z' )
145154 end function
146155
147156 ! > Checks whether `c` is an uppercase ASCII letter (A .. Z).
148157 pure logical function is_upper(c)
149158 character (len= 1 ), intent (in ) :: c ! ! The character to test.
150- is_upper = (c >= ' A' ) .and. (c <= ' Z' )
159+ integer :: ic
160+ ic = iachar (c)
161+ is_upper = (ic >= iachar (' A' )) .and. (ic <= iachar (' Z' ))
151162 end function
152163
153164 ! > Checks whether or not `c` is a whitespace character. That includes the
@@ -157,7 +168,7 @@ pure logical function is_white(c)
157168 character (len= 1 ), intent (in ) :: c ! ! The character to test.
158169 integer :: ic
159170 ic = iachar (c) ! TAB, LF, VT, FF, CR
160- is_white = (c == ' ' ) .or. (ic >= int (z' 09' ) .and. ic <= int (z' 0D' ));
171+ is_white = (ic == iachar ( ' ' ) ) .or. (ic >= int (z' 09' ) .and. ic <= int (z' 0D' ));
161172 end function
162173
163174 ! > Checks whether or not `c` is a blank character. That includes the
@@ -166,7 +177,7 @@ pure logical function is_blank(c)
166177 character (len= 1 ), intent (in ) :: c ! ! The character to test.
167178 integer :: ic
168179 ic = iachar (c) ! TAB
169- is_blank = (c == ' ' ) .or. (ic == int (z' 09' ));
180+ is_blank = (ic == iachar ( ' ' ) ) .or. (ic == int (z' 09' ));
170181 end function
171182
172183 ! > Returns the corresponding lowercase letter, if `c` is an uppercase
0 commit comments