text-latin1-0.3.1: Latin-1 (including ASCII) utility functions

Safe HaskellSafe
LanguageHaskell98

Text.Ascii

Contents

Description

ASCII utility functions.

Synopsis

ASCII checks

data IsAscii Source #

Constructors

IsAscii 

Instances

Property IsAscii Char Source # 

Methods

holds :: IsAscii -> Char -> Bool #

Property IsAscii Word8 Source # 

Methods

holds :: IsAscii -> Word8 -> Bool #

Property IsAscii ByteString Source # 

Methods

holds :: IsAscii -> ByteString -> Bool #

Property IsAscii ByteString Source # 

Methods

holds :: IsAscii -> ByteString -> Bool #

Property IsAscii Text Source # 

Methods

holds :: IsAscii -> Text -> Bool #

Property IsAscii Text Source # 

Methods

holds :: IsAscii -> Text -> Bool #

Property IsAscii α => Property IsAscii [α] Source # 

Methods

holds :: IsAscii -> [α] -> Bool #

Eq α => Eq (Ascii α) Source # 

Methods

(==) :: Ascii α -> Ascii α -> Bool #

(/=) :: Ascii α -> Ascii α -> Bool #

Ord α => Ord (Ascii α) Source # 

Methods

compare :: Ascii α -> Ascii α -> Ordering #

(<) :: Ascii α -> Ascii α -> Bool #

(<=) :: Ascii α -> Ascii α -> Bool #

(>) :: Ascii α -> Ascii α -> Bool #

(>=) :: Ascii α -> Ascii α -> Bool #

max :: Ascii α -> Ascii α -> Ascii α #

min :: Ascii α -> Ascii α -> Ascii α #

Show α => Show (Ascii α) Source # 

Methods

showsPrec :: Int -> Ascii α -> ShowS #

show :: Ascii α -> String #

showList :: [Ascii α] -> ShowS #

IsString α => IsString (Ascii α) Source # 

Methods

fromString :: String -> Ascii α #

Semigroup α => Semigroup (Ascii α) Source # 

Methods

(<>) :: Ascii α -> Ascii α -> Ascii α #

sconcat :: NonEmpty (Ascii α) -> Ascii α #

stimes :: Integral b => b -> Ascii α -> Ascii α #

Monoid α => Monoid (Ascii α) Source # 

Methods

mempty :: Ascii α #

mappend :: Ascii α -> Ascii α -> Ascii α #

mconcat :: [Ascii α] -> Ascii α #

FoldCase (Ascii Char) Source # 
FoldCase (Ascii α) => FoldCase (Ascii [α]) Source # 

Methods

foldCase :: Ascii [α] -> Ascii [α] #

foldCaseList :: [Ascii [α]] -> [Ascii [α]]

FoldCase (Ascii ByteString) Source # 
FoldCase (Ascii ByteString) Source # 
FoldCase (Ascii Text) Source # 
FoldCase (Ascii Text) Source # 
Hashable α => Hashable (Ascii α) Source # 

Methods

hashWithSalt :: Int -> Ascii α -> Int #

hash :: Ascii α -> Int #

maybeAscii :: Char -> Maybe Word8 Source #

Map a character to its ASCII encoding if possible, otherwise return Nothing.

ascii :: Char -> Word8 Source #

Encode an ASCII character. No checks are performed.

Character properties

isControl :: Char -> Bool Source #

Test if a character is an ASCII control character.

isPrintable :: Char -> Bool Source #

Test if a character is an ASCII printable character.

isWhiteSpace :: Char -> Bool Source #

Test if a character is an ASCII whitespace character.

isSpaceOrTab :: Char -> Bool Source #

Test if a character is the SPACE or the TAB character.

isLower :: Char -> Bool Source #

Test if a character is an ASCII lower-case letter.

isUpper :: Char -> Bool Source #

Test if a character is an ASCII upper-case letter.

toLower :: Char -> Char Source #

Map lower-case ASCII letters to the corresponding upper-case letters, leaving other characters as is.

toUpper :: Char -> Char Source #

Map upper-case ASCII letters to the corresponding lower-case letters, leaving other characters as is.

isAlpha :: Char -> Bool Source #

Test if a character is an ASCII letter.

isAlphaNum :: Char -> Bool Source #

Test if a character is either an ASCII letter or a decimal digit.

isDecDigit :: Char -> Bool Source #

Test if a character is a decimal digit ('0' ... '9').

isNzDecDigit :: Char -> Bool Source #

Test if a character is a non-zero decimal digit ('1' ... '9').

fromDecDigit :: Num a => Char -> Maybe a Source #

Map a decimal digit to the corresponding number. Return Nothing on other inputs.

fromNzDecDigit :: Num a => Char -> Maybe a Source #

Map non-zero decimal digits to the corresponding numbers. Return Nothing on other inputs.

unsafeFromDecDigit :: Num a => Char -> a Source #

Map decimal digits to the corresponding numbers. No checks are performed.

isBinDigit :: Char -> Bool Source #

Test if a character is a binary digit ('0' or '1').

isNzBinDigit :: Char -> Bool Source #

Test if a character is the non-zero binary digit ('1').

fromBinDigit :: Num a => Char -> Maybe a Source #

Map binary digits to the corresponding numbers. Return Nothing on other inputs.

fromNzBinDigit :: Num a => Char -> Maybe a Source #

Map the digit '1' to the number 1. Return Nothing on other inputs.

unsafeFromBinDigit :: Num a => Char -> a Source #

Map binary digits to the corresponding numbers. No checks are performed.

isOctDigit :: Char -> Bool Source #

Test if a character is an octal digit ('0' ... '7').

isNzOctDigit :: Char -> Bool Source #

Test if a character is a non-zero octal digit ('1' ... '7').

fromOctDigit :: Num a => Char -> Maybe a Source #

Map octal digits to the corresponding numbers. Return Nothing on other inputs.

fromNzOctDigit :: Num a => Char -> Maybe a Source #

Map non-zero octal digits to the corresponding numbers. Return Nothing on other inputs.

unsafeFromOctDigit :: Num a => Char -> a Source #

Map octal digits to the corresponding numbers. No checks are performed.

isUpHexDigit :: Char -> Bool Source #

Test if a character is an upper-case hexadecimal digit ('0' ... '9' or A ... F).

isNzUpHexDigit :: Char -> Bool Source #

Test if a character is a non-zero upper-case hexadecimal digit ('1' ... '9' or A ... F).

fromUpHexDigit :: Num a => Char -> Maybe a Source #

Map upper-case hexadecimal digits to the corresponding numbers. Return Nothing on other inputs.

fromNzUpHexDigit :: Num a => Char -> Maybe a Source #

Map non-zero upper-case hexadecimal digits to the corresponding numbers. Return Nothing on other inputs.

unsafeFromUpHexDigit :: Num a => Char -> a Source #

Map upper-case hexadecimal digits to the corresponding numbers. No checks are performed.

isLowHexDigit :: Char -> Bool Source #

Test if a character is a lower-case hexadecimal digit ('0' ... '9' or a ... f).

isNzLowHexDigit :: Char -> Bool Source #

Test if a character is a non-zero lower-case hexadecimal digit ('1' ... '9' or a ... f).

fromLowHexDigit :: Num a => Char -> Maybe a Source #

Map lower-case hexadecimal digits to the corresponding numbers. Return Nothing on other inputs.

fromNzLowHexDigit :: Num a => Char -> Maybe a Source #

Map non-zero lower-case hexadecimal digits to the corresponding numbers. Return Nothing on other inputs.

unsafeFromLowHexDigit :: Num a => Char -> a Source #

Map lower-case hexadecimal digits to the corresponding numbers. No checks are performed.

isHexDigit :: Char -> Bool Source #

Test if a character is a hexadecimal digit ('0' ... '9' or a ... f or A ... F).

isNzHexDigit :: Char -> Bool Source #

Test if a character is a non-zero hexadecimal digit ('1' ... '9' or a ... f or A ... F).

fromHexDigit :: Num a => Char -> Maybe a Source #

Map hexadecimal digits to the corresponding numbers. Return Nothing on other inputs.

fromNzHexDigit :: Num a => Char -> Maybe a Source #

Map non-zero hexadecimal digits to the corresponding numbers. Return Nothing on other inputs.

unsafeFromHexDigit :: Num a => Char -> a Source #

Map hexadecimal digits to the corresponding numbers. No checks are performed.

Byte properties

isControl8 :: Word8 -> Bool Source #

Test if a byte is the encoding of an ASCII control character.

isPrintable8 :: Word8 -> Bool Source #

Test if a byte is the encoding of an ASCII printable character.

isWhiteSpace8 :: Word8 -> Bool Source #

Test if a byte is the encoding of an ASCII whitespace character.

isSpaceOrTab8 :: Word8 -> Bool Source #

Test if a byte is the encoding of the SPACE or the TAB character.

isLower8 :: Word8 -> Bool Source #

Test if a byte is the encoding of an ASCII lower-case letter.

isUpper8 :: Word8 -> Bool Source #

Test if a byte is the encoding of an ASCII upper-case letter.

toLower8 :: Word8 -> Word8 Source #

Map the encodings of lower-case ASCII letters to the encodings of the corresponding upper-case letters, leaving other bytes as is.

toUpper8 :: Word8 -> Word8 Source #

Map the encodings of upper-case ASCII letters to the encodings of the corresponding lower-case letters, leaving other bytes as is.

isAlpha8 :: Word8 -> Bool Source #

Test if a byte is the encoding of an ASCII letter.

isAlphaNum8 :: Word8 -> Bool Source #

Test if a byte is the encoding of either an ASCII letter or a decimal digit.

isDecDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a decimal digit ('0' ... '9').

isNzDecDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a non-zero decimal digit ('1' ... '9').

fromDecDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a decimal digit to the corresponding number. Return Nothing on other inputs.

fromNzDecDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a non-zero decimal digit to the corresponding number. Return Nothing on other inputs.

unsafeFromDecDigit8 :: Num a => Word8 -> a Source #

Map the encoding of a decimal digit to the corresponding number. No checks are performed.

isBinDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a binary digit ('0' or '1').

isNzBinDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of the non-zero binary digit ('1').

fromBinDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a binary digit to the corresponding number. Return Nothing on other inputs.

fromNzBinDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of the digit '1' to the number 1. Return Nothing on other inputs.

unsafeFromBinDigit8 :: Num a => Word8 -> a Source #

Map the encoding of a binary digit to the corresponding number. No checks are performed.

isOctDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of an octal digit ('0' ... '7').

isNzOctDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a non-zero octal digit ('1' ... '7').

fromOctDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of an octal digit to the corresponding number. Return Nothing on other inputs.

fromNzOctDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a non-zero octal digit to the corresponding number. Return Nothing on other inputs.

unsafeFromOctDigit8 :: Num a => Word8 -> a Source #

Map the encoding of an octal digit to the corresponding number. No checks are performed.

isUpHexDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of an upper-case hexadecimal digit ('0' ... '9' or A ... F).

isNzUpHexDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a non-zero upper-case hexadecimal digit ('1' ... '9' or A ... F).

fromUpHexDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of an upper-case hexadecimal digit to the corresponding number. Return Nothing on other inputs.

fromNzUpHexDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a non-zero upper-case hexadecimal digit to the corresponding number. Return Nothing on other inputs.

unsafeFromUpHexDigit8 :: Num a => Word8 -> a Source #

Map the encoding of an upper-case hexadecimal digit to the corresponding number. No checks are performed.

isLowHexDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a lower-case hexadecimal digit ('0' ... '9' or a ... f).

isNzLowHexDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a non-zero lower-case hexadecimal digit ('1' ... '9' or a ... f).

fromLowHexDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a lower-case hexadecimal digit to the corresponding number. Return Nothing on other inputs.

fromNzLowHexDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a non-zero lower-case hexadecimal digit to the corresponding number. Return Nothing on other inputs.

unsafeFromLowHexDigit8 :: Num a => Word8 -> a Source #

Map the encoding of a lower-case hexadecimal digit to the corresponding number. No checks are performed.

isHexDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a hexadecimal digit ('0' ... '9' or a ... f or A ... F).

isNzHexDigit8 :: Word8 -> Bool Source #

Test if a byte is the encoding of a non-zero hexadecimal digit ('1' ... '9' or a ... f or A ... F).

fromHexDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a hexadecimal digit to the corresponding number. Return Nothing on other inputs.

fromNzHexDigit8 :: Num a => Word8 -> Maybe a Source #

Map the encoding of a non-zero hexadecimal digit to the corresponding number. Return Nothing on other inputs.

unsafeFromHexDigit8 :: Num a => Word8 -> a Source #

Map the encoding of a hexadecimal digit to the corresponding number. No checks are performed.