@@ -65,18 +65,14 @@ 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- integer :: ic
69- ic = iachar (c)
70- is_alpha = (ic >= iachar (' A' ) .and. ic <= iachar (' Z' )) .or. (ic >= iachar (' a' ) .and. ic <= iachar (' z' ))
68+ is_alpha = (c >= ' A' .and. c <= ' Z' ) .or. (c >= ' a' .and. c <= ' z' )
7169 end function
7270
7371 ! > Checks whether `c` is a letter or a number (0 .. 9, a .. z, A .. Z).
7472 pure logical function is_alphanum(c)
7573 character (len= 1 ), intent (in ) :: c ! ! The character to test.
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' ))
74+ is_alphanum = (c >= ' 0' .and. c <= ' 9' ) .or. (c >= ' a' .and. c <= ' z' ) &
75+ .or. (c >= ' A' .and. c <= ' Z' )
8076 end function
8177
8278 ! > Checks whether or not `c` is in the ASCII character set -
@@ -97,25 +93,20 @@ pure logical function is_control(c)
9793 ! > Checks whether `c` is a digit (0 .. 9).
9894 pure logical function is_digit(c)
9995 character (len= 1 ), intent (in ) :: c ! ! The character to test.
100- integer :: ic
101- is_digit = (iachar (' 0' ) <= ic) .and. (ic <= iachar (' 9' ))
96+ is_digit = (' 0' <= c) .and. (c <= ' 9' )
10297 end function
10398
10499 ! > Checks whether `c` is a digit in base 8 (0 .. 7).
105100 pure logical function is_octal_digit(c)
106101 character (len= 1 ), intent (in ) :: c ! ! The character to test.
107- integer :: ic
108- ic = iachar (c)
109- is_octal_digit = (ic >= iachar (' 0' )) .and. (ic <= iachar (' 7' ))
102+ is_octal_digit = (c >= ' 0' ) .and. (c <= ' 7' );
110103 end function
111104
112105 ! > Checks whether `c` is a digit in base 16 (0 .. 9, A .. F, a .. f).
113- pure logical function is_hex_digit(cin )
106+ pure logical function is_hex_digit(c )
114107 character (len= 1 ), intent (in ) :: c ! ! The character to test.
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' ))
108+ is_hex_digit = (c >= ' 0' .and. c <= ' 9' ) .or. (c >= ' a' .and. c <= ' f' ) &
109+ .or. (c >= ' A' .and. c <= ' F' )
119110 end function
120111
121112 ! > Checks whether or not `c` is a punctuation character. That includes
@@ -148,17 +139,15 @@ pure logical function is_printable(c)
148139 end function
149140
150141 ! > Checks whether `c` is a lowercase ASCII letter (a .. z).
151- pure logical function is_lower(cin )
142+ pure logical function is_lower(c )
152143 character (len= 1 ), intent (in ) :: c ! ! The character to test.
153144 is_lower = (c >= ' a' ) .and. (c <= ' z' )
154145 end function
155146
156147 ! > Checks whether `c` is an uppercase ASCII letter (A .. Z).
157148 pure logical function is_upper(c)
158149 character (len= 1 ), intent (in ) :: c ! ! The character to test.
159- integer :: ic
160- ic = iachar (c)
161- is_upper = (ic >= iachar (' A' )) .and. (ic <= iachar (' Z' ))
150+ is_upper = (c >= ' A' ) .and. (c <= ' Z' )
162151 end function
163152
164153 ! > Checks whether or not `c` is a whitespace character. That includes the
@@ -168,7 +157,7 @@ pure logical function is_white(c)
168157 character (len= 1 ), intent (in ) :: c ! ! The character to test.
169158 integer :: ic
170159 ic = iachar (c) ! TAB, LF, VT, FF, CR
171- is_white = (ic == iachar ( ' ' ) ) .or. (ic >= int (z' 09' ) .and. ic <= int (z' 0D' ));
160+ is_white = (c == ' ' ) .or. (ic >= int (z' 09' ) .and. ic <= int (z' 0D' ));
172161 end function
173162
174163 ! > Checks whether or not `c` is a blank character. That includes the
@@ -177,7 +166,7 @@ pure logical function is_blank(c)
177166 character (len= 1 ), intent (in ) :: c ! ! The character to test.
178167 integer :: ic
179168 ic = iachar (c) ! TAB
180- is_blank = (ic == iachar ( ' ' ) ) .or. (ic == int (z' 09' ));
169+ is_blank = (c == ' ' ) .or. (ic == int (z' 09' ));
181170 end function
182171
183172 ! > Returns the corresponding lowercase letter, if `c` is an uppercase
0 commit comments