Skip to content

Commit 8b7b1e8

Browse files
committed
faster chat_to_lower/upper
1 parent 71337ba commit 8b7b1e8

File tree

1 file changed

+12
-22
lines changed

1 file changed

+12
-22
lines changed

src/stdlib_ascii.fypp

Lines changed: 12 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -223,31 +223,27 @@ contains
223223
pure function char_to_lower(c) result(t)
224224
character(len=1), intent(in) :: c !! A character.
225225
character(len=1) :: t
226+
integer, parameter :: wp= 32, la=65, lz= 90
226227
integer :: k
227228

228-
k = index( uppercase, c )
229+
k = ichar(c)
230+
if (k>=la.and.k<=lz) k = k + wp
231+
t = char(k)
229232

230-
if ( k > 0 ) then
231-
t = lowercase(k:k)
232-
else
233-
t = c
234-
endif
235233
end function char_to_lower
236234

237235
!> Returns the corresponding uppercase letter, if `c` is a lowercase
238236
!> ASCII character, otherwise `c` itself.
239237
pure function char_to_upper(c) result(t)
240238
character(len=1), intent(in) :: c !! A character.
241239
character(len=1) :: t
240+
integer, parameter :: wp= 32, BA=97, BZ= 122
242241
integer :: k
243242

244-
k = index( lowercase, c )
243+
k = ichar(c)
244+
if (k>=BA.and.k<=BZ) k = k - wp
245+
t = char(k)
245246

246-
if ( k > 0 ) then
247-
t = uppercase(k:k)
248-
else
249-
t = c
250-
endif
251247
end function char_to_upper
252248

253249
!> Convert character variable to lower case
@@ -257,13 +253,10 @@ contains
257253
pure function to_lower(string) result(lower_string)
258254
character(len=*), intent(in) :: string
259255
character(len=len(string)) :: lower_string
260-
integer, parameter :: wp= 32, la=65, lz= 90
261-
integer :: i, icar
256+
integer :: i
262257

263258
do i = 1, len(string)
264-
icar= ichar(string(i:i))
265-
if (icar>=la.and.icar<=lz) icar= icar + wp
266-
lower_string(i:i) = char(icar)
259+
lower_string(i:i) = char_to_lower(string(i:i))
267260
end do
268261

269262
end function to_lower
@@ -275,13 +268,10 @@ contains
275268
pure function to_upper(string) result(upper_string)
276269
character(len=*), intent(in) :: string
277270
character(len=len(string)) :: upper_string
278-
integer, parameter :: wp= 32, BA=97, BZ= 122
279-
integer :: i, icar
271+
integer :: i
280272

281273
do i = 1, len(string)
282-
icar= ichar(string(i:i))
283-
if (icar>=BA.and.icar<=BZ) icar= icar - wp
284-
upper_string(i:i) = char(icar)
274+
upper_string(i:i) = char_to_upper(string(i:i))
285275
end do
286276

287277
end function to_upper

0 commit comments

Comments
 (0)