Skip to content

Commit 08e489a

Browse files
committed
promote ascii pure functions to elemental
1 parent 1ba499c commit 08e489a

File tree

1 file changed

+14
-14
lines changed

1 file changed

+14
-14
lines changed

src/stdlib_ascii.fypp

Lines changed: 14 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -107,47 +107,47 @@ module stdlib_ascii
107107
contains
108108

109109
!> Checks whether `c` is an ASCII letter (A .. Z, a .. z).
110-
pure logical function is_alpha(c)
110+
elemental logical function is_alpha(c)
111111
character(len=1), intent(in) :: c !! The character to test.
112112
is_alpha = (c >= 'A' .and. c <= 'Z') .or. (c >= 'a' .and. c <= 'z')
113113
end function
114114

115115
!> Checks whether `c` is a letter or a number (0 .. 9, a .. z, A .. Z).
116-
pure logical function is_alphanum(c)
116+
elemental logical function is_alphanum(c)
117117
character(len=1), intent(in) :: c !! The character to test.
118118
is_alphanum = (c >= '0' .and. c <= '9') .or. (c >= 'a' .and. c <= 'z') &
119119
.or. (c >= 'A' .and. c <= 'Z')
120120
end function
121121

122122
!> Checks whether or not `c` is in the ASCII character set -
123123
!> i.e. in the range 0 .. 0x7F.
124-
pure logical function is_ascii(c)
124+
elemental logical function is_ascii(c)
125125
character(len=1), intent(in) :: c !! The character to test.
126126
is_ascii = iachar(c) <= int(z'7F')
127127
end function
128128

129129
!> Checks whether `c` is a control character.
130-
pure logical function is_control(c)
130+
elemental logical function is_control(c)
131131
character(len=1), intent(in) :: c !! The character to test.
132132
integer :: ic
133133
ic = iachar(c)
134134
is_control = ic < int(z'20') .or. ic == int(z'7F')
135135
end function
136136

137137
!> Checks whether `c` is a digit (0 .. 9).
138-
pure logical function is_digit(c)
138+
elemental logical function is_digit(c)
139139
character(len=1), intent(in) :: c !! The character to test.
140140
is_digit = ('0' <= c) .and. (c <= '9')
141141
end function
142142

143143
!> Checks whether `c` is a digit in base 8 (0 .. 7).
144-
pure logical function is_octal_digit(c)
144+
elemental logical function is_octal_digit(c)
145145
character(len=1), intent(in) :: c !! The character to test.
146146
is_octal_digit = (c >= '0') .and. (c <= '7');
147147
end function
148148

149149
!> Checks whether `c` is a digit in base 16 (0 .. 9, A .. F, a .. f).
150-
pure logical function is_hex_digit(c)
150+
elemental logical function is_hex_digit(c)
151151
character(len=1), intent(in) :: c !! The character to test.
152152
is_hex_digit = (c >= '0' .and. c <= '9') .or. (c >= 'a' .and. c <= 'f') &
153153
.or. (c >= 'A' .and. c <= 'F')
@@ -156,7 +156,7 @@ contains
156156
!> Checks whether or not `c` is a punctuation character. That includes
157157
!> all ASCII characters which are not control characters, letters,
158158
!> digits, or whitespace.
159-
pure logical function is_punctuation(c)
159+
elemental logical function is_punctuation(c)
160160
character(len=1), intent(in) :: c !! The character to test.
161161
integer :: ic
162162
ic = iachar(c) ! '~' '!'
@@ -166,7 +166,7 @@ contains
166166

167167
!> Checks whether or not `c` is a printable character other than the
168168
!> space character.
169-
pure logical function is_graphical(c)
169+
elemental logical function is_graphical(c)
170170
character(len=1), intent(in) :: c !! The character to test.
171171
integer :: ic
172172
ic = iachar(c)
@@ -177,7 +177,7 @@ contains
177177

178178
!> Checks whether or not `c` is a printable character - including the
179179
!> space character.
180-
pure logical function is_printable(c)
180+
elemental logical function is_printable(c)
181181
character(len=1), intent(in) :: c !! The character to test.
182182
integer :: ic
183183
ic = iachar(c)
@@ -186,23 +186,23 @@ contains
186186
end function
187187

188188
!> Checks whether `c` is a lowercase ASCII letter (a .. z).
189-
pure logical function is_lower(c)
189+
elemental logical function is_lower(c)
190190
character(len=1), intent(in) :: c !! The character to test.
191191
integer :: ic
192192
ic = iachar(c)
193193
is_lower = ic >= iachar('a') .and. ic <= iachar('z')
194194
end function
195195

196196
!> Checks whether `c` is an uppercase ASCII letter (A .. Z).
197-
pure logical function is_upper(c)
197+
elemental logical function is_upper(c)
198198
character(len=1), intent(in) :: c !! The character to test.
199199
is_upper = (c >= 'A') .and. (c <= 'Z')
200200
end function
201201

202202
!> Checks whether or not `c` is a whitespace character. That includes the
203203
!> space, tab, vertical tab, form feed, carriage return, and linefeed
204204
!> characters.
205-
pure logical function is_white(c)
205+
elemental logical function is_white(c)
206206
character(len=1), intent(in) :: c !! The character to test.
207207
integer :: ic
208208
ic = iachar(c) ! TAB, LF, VT, FF, CR
@@ -211,7 +211,7 @@ contains
211211

212212
!> Checks whether or not `c` is a blank character. That includes the
213213
!> only the space and tab characters
214-
pure logical function is_blank(c)
214+
elemental logical function is_blank(c)
215215
character(len=1), intent(in) :: c !! The character to test.
216216
integer :: ic
217217
ic = iachar(c) ! TAB

0 commit comments

Comments
 (0)