Skip to content

Commit d0cc617

Browse files
authored
Merge pull request #235 from fortran-lang/update_ascii
Update ascii - second round: clean up the code and implement robust versions of to_lower and to_upper
2 parents 5856e4f + 9a82237 commit d0cc617

File tree

1 file changed

+35
-19
lines changed

1 file changed

+35
-19
lines changed

src/stdlib_ascii.f90

+35-19
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,9 @@ module stdlib_ascii
6060
character(len=*), public, parameter :: lowercase = letters(27:) !! a .. z
6161
character(len=*), public, parameter :: whitespace = " "//TAB//VT//CR//LF//FF !! ASCII _whitespace
6262

63+
character(len=26), parameter, private :: lower_case = 'abcdefghijklmnopqrstuvwxyz'
64+
character(len=26), parameter, private :: upper_case = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
65+
6366
contains
6467

6568
!> Checks whether `c` is an ASCII letter (A .. Z, a .. z).
@@ -135,7 +138,9 @@ pure logical function is_punctuation(c)
135138
pure logical function is_graphical(c)
136139
character(len=1), intent(in) :: c !! The character to test.
137140
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
139144
is_graphical = (int(z'21') <= ic) .and. (ic <= int(z'7E'))
140145
end function
141146

@@ -144,22 +149,25 @@ pure logical function is_graphical(c)
144149
pure logical function is_printable(c)
145150
character(len=1), intent(in) :: c !! The character to test.
146151
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')
149155
end function
150156

151157
!> Checks whether `c` is a lowercase ASCII letter (a .. z).
152158
pure logical function is_lower(c)
153159
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')
155163
end function
156164

157165
!> Checks whether `c` is an uppercase ASCII letter (A .. Z).
158166
pure logical function is_upper(c)
159167
character(len=1), intent(in) :: c !! The character to test.
160168
integer :: ic
161169
ic = iachar(c)
162-
is_upper = (ic >= iachar('A')) .and. (ic <= iachar('Z'))
170+
is_upper = ic >= iachar('A') .and. ic <= iachar('Z')
163171
end function
164172

165173
!> Checks whether or not `c` is a whitespace character. That includes the
@@ -169,7 +177,7 @@ pure logical function is_white(c)
169177
character(len=1), intent(in) :: c !! The character to test.
170178
integer :: ic
171179
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'))
173181
end function
174182

175183
!> Checks whether or not `c` is a blank character. That includes the
@@ -178,31 +186,39 @@ pure logical function is_blank(c)
178186
character(len=1), intent(in) :: c !! The character to test.
179187
integer :: ic
180188
ic = iachar(c) ! TAB
181-
is_blank = (ic == iachar(' ')) .or. (ic == int(z'09'));
189+
is_blank = ic == iachar(' ') .or. ic == int(z'09')
182190
end function
183191

184192
!> Returns the corresponding lowercase letter, if `c` is an uppercase
185193
! ASCII character, otherwise `c` itself.
186194
pure function to_lower(c) result(t)
187195
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
194206
end function
195207

196208
!> Returns the corresponding uppercase letter, if `c` is a lowercase
197209
! ASCII character, otherwise `c` itself.
198210
pure function to_upper(c) result(t)
199211
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
206222
end function
207223

208224
end module

0 commit comments

Comments
 (0)