You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
The following code where pure functions were designated elemental compiles with gfortran and ifx.
module m
implicit nonecontains
elemental logical function is_alpha(c)
character(len=1), intent(in) :: c !! The characterto test.
is_alpha = (c >='A'.and. c <='Z') .or. (c >='a'.and. c <='z')
end function
!> Checks whether `c` is a letter or a number (0 .. 9, a .. z, A .. Z).
elemental logical function is_alphanum(c)
character(len=1), intent(in) :: c !! The characterto test.
is_alphanum = (c >='0'.and. c <='9') .or. (c >='a'.and. c <='z') &
.or. (c >='A'.and. c <='Z')
end function
!> Checks whether or not `c` is in the ASCII character set -
!> i.e. in the range 0 .. 0x7F.
elemental logical function is_ascii(c)
character(len=1), intent(in) :: c !! The characterto test.
is_ascii =iachar(c) <=int(z'7F')
end function
!> Checks whether `c` is a control character.
elemental logical function is_control(c)
character(len=1), intent(in) :: c !! The characterto test.
integer:: ic
ic =iachar(c)
is_control = ic < int(z'20') .or. ic == int(z'7F')
end function
!> Checks whether `c` is a digit (0 .. 9).
elemental logical function is_digit(c)
character(len=1), intent(in) :: c !! The characterto test.
is_digit = ('0' <= c) .and. (c <='9')
end function
!> Checks whether `c` is a digit in base 8 (0 .. 7).
elemental logical function is_octal_digit(c)
character(len=1), intent(in) :: c !! The characterto test.
is_octal_digit = (c >='0') .and. (c <='7');
end function
!> Checks whether `c` is a digit in base 16 (0 .. 9, A .. F, a .. f).
elemental logical function is_hex_digit(c)
character(len=1), intent(in) :: c !! The characterto test.
is_hex_digit = (c >='0'.and. c <='9') .or. (c >='a'.and. c <='f') &
.or. (c >='A'.and. c <='F')
end function
!> Checks whether or not `c` is a punctuation character. That includes
!> all ASCII characters which are not control characters, letters,
!> digits, or whitespace.
elemental logical function is_punctuation(c)
character(len=1), intent(in) :: c !! The characterto test.
integer:: ic
ic =iachar(c) ! '~''!'
is_punctuation = (ic <=int(z'7E')) .and. (ic >=int(z'21')) .and. &
(.not. is_alphanum(c))
end function
!> Checks whether or not `c` is a printable character other than the
!> space character.
elemental logical function is_graphical(c)
character(len=1), intent(in) :: c !! The characterto test.
integer:: ic
ic =iachar(c)
!The character is graphical if it's between '!' and '~' in the ASCII table, !that is: printable but not a space is_graphical = (int(z'21') <= ic) .and. (ic <= int(z'7E')) end function !> Checks whether or not `c` is a printable character - including the !> space character. elemental logical function is_printable(c) character(len=1), intent(in) :: c !! The character to test. integer :: ic ic = iachar(c) !The character is printable if it's between '' and '~'in the ASCII table
is_printable = ic >=iachar('') .and. ic <=int(z'7E')
end function
!> Checks whether `c` is a lowercase ASCII letter (a .. z).
elemental logical function is_lower(c)
character(len=1), intent(in) :: c !! The characterto test.
integer:: ic
ic =iachar(c)
is_lower = ic >=iachar('a') .and. ic <=iachar('z')
end function
!> Checks whether `c` is an uppercase ASCII letter (A .. Z).
elemental logical function is_upper(c)
character(len=1), intent(in) :: c !! The characterto test.
is_upper = (c >='A') .and. (c <='Z')
end function
!> Checks whether or not `c` is a whitespace character. That includes the
!> space, tab, vertical tab, form feed, carriage return, and linefeed
!> characters.
elemental logical function is_white(c)
character(len=1), intent(in) :: c !! The characterto test.
integer:: ic
ic =iachar(c) ! TAB, LF, VT, FF, CR
is_white = (c == '') .or. (ic >=int(z'09') .and. ic <=int(z'0D'));
end function
!> Checks whether or not `c` is a blank character. That includes the
!> only the space and tab characters
elemental logical function is_blank(c)
character(len=1), intent(in) :: c !! The characterto test.
integer:: ic
ic =iachar(c) ! TAB
is_blank = (c == '') .or. (ic == int(z'09'));
end function
end module m
If people agree this change should be made, I could try to submit a pull request.
The text was updated successfully, but these errors were encountered:
Hi @Beliavsky you are welcome to test it out. When I proposed this PR #886 I had tried to promote some of those to elemental as well but had some problems with the tests, I can't remember what it was. If you cross check that everything works fine, then please go ahead and open a new PR.
The following functions in
stdlib_ascii.f90
can be madeelemental
:The following code where pure functions were designated elemental compiles with gfortran and ifx.
If people agree this change should be made, I could try to submit a pull request.
The text was updated successfully, but these errors were encountered: