{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Text.Ascii
(
IsAscii(..)
, isAscii
, Ascii
, maybeAscii
, ascii
, isControl
, isPrintable
, isWhiteSpace
, isSpaceOrTab
, isLower
, isUpper
, toLower
, toUpper
, isAlpha
, isAlphaNum
, isDecDigit
, isNzDecDigit
, fromDecDigit
, fromNzDecDigit
, unsafeFromDecDigit
, isBinDigit
, isNzBinDigit
, fromBinDigit
, fromNzBinDigit
, unsafeFromBinDigit
, isOctDigit
, isNzOctDigit
, fromOctDigit
, fromNzOctDigit
, unsafeFromOctDigit
, isUpHexDigit
, isNzUpHexDigit
, fromUpHexDigit
, fromNzUpHexDigit
, unsafeFromUpHexDigit
, isLowHexDigit
, isNzLowHexDigit
, fromLowHexDigit
, fromNzLowHexDigit
, unsafeFromLowHexDigit
, isHexDigit
, isNzHexDigit
, fromHexDigit
, fromNzHexDigit
, unsafeFromHexDigit
, isControl8
, isPrintable8
, isWhiteSpace8
, isSpaceOrTab8
, isLower8
, isUpper8
, toLower8
, toUpper8
, isAlpha8
, isAlphaNum8
, isDecDigit8
, isNzDecDigit8
, fromDecDigit8
, fromNzDecDigit8
, unsafeFromDecDigit8
, isBinDigit8
, isNzBinDigit8
, fromBinDigit8
, fromNzBinDigit8
, unsafeFromBinDigit8
, isOctDigit8
, isNzOctDigit8
, fromOctDigit8
, fromNzOctDigit8
, unsafeFromOctDigit8
, isUpHexDigit8
, isNzUpHexDigit8
, fromUpHexDigit8
, fromNzUpHexDigit8
, unsafeFromUpHexDigit8
, isLowHexDigit8
, isNzLowHexDigit8
, fromLowHexDigit8
, fromNzLowHexDigit8
, unsafeFromLowHexDigit8
, isHexDigit8
, isNzHexDigit8
, fromHexDigit8
, fromNzHexDigit8
, unsafeFromHexDigit8
) where
import Data.Checked
import Data.Function (on)
import Data.Char (ord, chr)
import Data.String (IsString(..))
import Data.Word (Word8)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as TS
import qualified Data.Text.Lazy as TL
import Data.Semigroup (Semigroup(..))
import Data.Monoid (Monoid(..))
import Data.CaseInsensitive (FoldCase(..))
import Data.Hashable (Hashable(..))
data IsAscii = IsAscii
instance Property IsAscii Word8 where
holds :: IsAscii -> Word8 -> Bool
holds IsAscii
_ = (Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
128)
{-# INLINE holds #-}
instance Property IsAscii BS.ByteString where
holds :: IsAscii -> ByteString -> Bool
holds IsAscii
_ = (Word8 -> Bool) -> ByteString -> Bool
BS.all Word8 -> Bool
forall v. Property IsAscii v => v -> Bool
isAscii
{-# INLINE holds #-}
instance Property IsAscii BL.ByteString where
holds :: IsAscii -> ByteString -> Bool
holds IsAscii
_ = (Word8 -> Bool) -> ByteString -> Bool
BL.all Word8 -> Bool
forall v. Property IsAscii v => v -> Bool
isAscii
{-# INLINE holds #-}
instance Property IsAscii Char where
holds :: IsAscii -> Char -> Bool
holds IsAscii
_ = (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
128) (Int -> Bool) -> (Char -> Int) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord
{-# INLINE holds #-}
instance Property IsAscii α ⇒ Property IsAscii [α] where
holds :: IsAscii -> [α] -> Bool
holds IsAscii
_ = (α -> Bool) -> [α] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all α -> Bool
forall v. Property IsAscii v => v -> Bool
isAscii
{-# INLINE holds #-}
instance Property IsAscii TS.Text where
holds :: IsAscii -> Text -> Bool
holds IsAscii
_ = (Char -> Bool) -> Text -> Bool
TS.all Char -> Bool
forall v. Property IsAscii v => v -> Bool
isAscii
{-# INLINE holds #-}
instance Property IsAscii TL.Text where
holds :: IsAscii -> Text -> Bool
holds IsAscii
_ = (Char -> Bool) -> Text -> Bool
TL.all Char -> Bool
forall v. Property IsAscii v => v -> Bool
isAscii
{-# INLINE holds #-}
isAscii ∷ Property IsAscii v ⇒ v → Bool
isAscii :: forall v. Property IsAscii v => v -> Bool
isAscii = IsAscii -> v -> Bool
forall p v. Property p v => p -> v -> Bool
holds IsAscii
IsAscii
{-# INLINE isAscii #-}
type Ascii α = Checked IsAscii α
instance Eq α ⇒ Eq (Ascii α) where
== :: Ascii α -> Ascii α -> Bool
(==) = α -> α -> Bool
forall a. Eq a => a -> a -> Bool
(==) (α -> α -> Bool) -> (Ascii α -> α) -> Ascii α -> Ascii α -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Ascii α -> α
forall p v. Checked p v -> v
checked
{-# INLINE (==) #-}
instance Ord α ⇒ Ord (Ascii α) where
compare :: Ascii α -> Ascii α -> Ordering
compare = α -> α -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (α -> α -> Ordering)
-> (Ascii α -> α) -> Ascii α -> Ascii α -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Ascii α -> α
forall p v. Checked p v -> v
checked
{-# INLINE compare #-}
instance Show α ⇒ Show (Ascii α) where
showsPrec :: Int -> Ascii α -> ShowS
showsPrec Int
p = Int -> α -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p (α -> ShowS) -> (Ascii α -> α) -> Ascii α -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ascii α -> α
forall p v. Checked p v -> v
checked
instance Semigroup α ⇒ Semigroup (Ascii α) where
Ascii α
x <> :: Ascii α -> Ascii α -> Ascii α
<> Ascii α
y = α -> Ascii α
forall v p. v -> Checked p v
trustMe (α -> Ascii α) -> α -> Ascii α
forall a b. (a -> b) -> a -> b
$ Ascii α -> α
forall p v. Checked p v -> v
checked Ascii α
x α -> α -> α
forall a. Semigroup a => a -> a -> a
<> Ascii α -> α
forall p v. Checked p v -> v
checked Ascii α
y
{-# INLINE (<>) #-}
sconcat :: NonEmpty (Ascii α) -> Ascii α
sconcat = α -> Ascii α
forall v p. v -> Checked p v
trustMe (α -> Ascii α)
-> (NonEmpty (Ascii α) -> α) -> NonEmpty (Ascii α) -> Ascii α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty α -> α
forall a. Semigroup a => NonEmpty a -> a
sconcat (NonEmpty α -> α)
-> (NonEmpty (Ascii α) -> NonEmpty α) -> NonEmpty (Ascii α) -> α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ascii α -> α) -> NonEmpty (Ascii α) -> NonEmpty α
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ascii α -> α
forall p v. Checked p v -> v
checked
{-# INLINE sconcat #-}
stimes :: forall b. Integral b => b -> Ascii α -> Ascii α
stimes b
n = α -> Ascii α
forall v p. v -> Checked p v
trustMe (α -> Ascii α) -> (Ascii α -> α) -> Ascii α -> Ascii α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> α -> α
forall b. Integral b => b -> α -> α
forall a b. (Semigroup a, Integral b) => b -> a -> a
stimes b
n (α -> α) -> (Ascii α -> α) -> Ascii α -> α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ascii α -> α
forall p v. Checked p v -> v
checked
{-# INLINE stimes #-}
instance Monoid α ⇒ Monoid (Ascii α) where
mempty :: Ascii α
mempty = α -> Ascii α
forall v p. v -> Checked p v
trustMe α
forall a. Monoid a => a
mempty
{-# INLINE mempty #-}
mappend :: Ascii α -> Ascii α -> Ascii α
mappend Ascii α
x Ascii α
y = α -> Ascii α
forall v p. v -> Checked p v
trustMe (α -> Ascii α) -> α -> Ascii α
forall a b. (a -> b) -> a -> b
$ α -> α -> α
forall a. Monoid a => a -> a -> a
mappend (Ascii α -> α
forall p v. Checked p v -> v
checked Ascii α
x) (Ascii α -> α
forall p v. Checked p v -> v
checked Ascii α
y)
{-# INLINE mappend #-}
mconcat :: [Ascii α] -> Ascii α
mconcat = α -> Ascii α
forall v p. v -> Checked p v
trustMe (α -> Ascii α) -> ([Ascii α] -> α) -> [Ascii α] -> Ascii α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [α] -> α
forall a. Monoid a => [a] -> a
mconcat ([α] -> α) -> ([Ascii α] -> [α]) -> [Ascii α] -> α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ascii α -> α) -> [Ascii α] -> [α]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ascii α -> α
forall p v. Checked p v -> v
checked
{-# INLINE mconcat #-}
instance IsString α ⇒ IsString (Ascii α) where
fromString :: String -> Ascii α
fromString String
s | String -> Bool
forall v. Property IsAscii v => v -> Bool
isAscii String
s = α -> Ascii α
forall v p. v -> Checked p v
trustMe (α -> Ascii α) -> α -> Ascii α
forall a b. (a -> b) -> a -> b
$ String -> α
forall a. IsString a => String -> a
fromString String
s
| Bool
otherwise = String -> Ascii α
forall a. HasCallStack => String -> a
error (String -> Ascii α) -> String -> Ascii α
forall a b. (a -> b) -> a -> b
$ String
"Not an ASCII string: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
s
{-# INLINE fromString #-}
instance Hashable α ⇒ Hashable (Ascii α) where
#if MIN_VERSION_hashable(1,2,0)
hashWithSalt :: Int -> Ascii α -> Int
hashWithSalt Int
s = Int -> α -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
s (α -> Int) -> (Ascii α -> α) -> Ascii α -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ascii α -> α
forall p v. Checked p v -> v
checked
{-# INLINE hashWithSalt #-}
#else
hash = hash . checked
{-# INLINE hash #-}
#endif
instance FoldCase (Ascii Char) where
foldCase :: Ascii Char -> Ascii Char
foldCase = (Char -> Char) -> Ascii Char -> Ascii Char
forall v p. (v -> v) -> Checked p v -> Checked p v
trustMap Char -> Char
toLower
{-# INLINE foldCase #-}
instance FoldCase (Ascii α) ⇒ FoldCase (Ascii [α]) where
foldCase :: Ascii [α] -> Ascii [α]
foldCase = ([α] -> [α]) -> Ascii [α] -> Ascii [α]
forall v p. (v -> v) -> Checked p v -> Checked p v
trustMap (([α] -> [α]) -> Ascii [α] -> Ascii [α])
-> ([α] -> [α]) -> Ascii [α] -> Ascii [α]
forall a b. (a -> b) -> a -> b
$ (α -> α) -> [α] -> [α]
forall a b. (a -> b) -> [a] -> [b]
map ((α -> α) -> [α] -> [α]) -> (α -> α) -> [α] -> [α]
forall a b. (a -> b) -> a -> b
$ Ascii α -> α
forall p v. Checked p v -> v
checked (Ascii α -> α) -> (α -> Ascii α) -> α -> α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ascii α -> Ascii α
forall s. FoldCase s => s -> s
foldCase (Ascii α -> Ascii α) -> (α -> Ascii α) -> α -> Ascii α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IsAscii -> α -> Ascii α
forall p v. p -> v -> Checked p v
trustThat IsAscii
IsAscii
{-# INLINE foldCase #-}
instance FoldCase (Ascii BS.ByteString) where
foldCase :: Ascii ByteString -> Ascii ByteString
foldCase = (ByteString -> ByteString) -> Ascii ByteString -> Ascii ByteString
forall v p. (v -> v) -> Checked p v -> Checked p v
trustMap ((ByteString -> ByteString)
-> Ascii ByteString -> Ascii ByteString)
-> (ByteString -> ByteString)
-> Ascii ByteString
-> Ascii ByteString
forall a b. (a -> b) -> a -> b
$ (Word8 -> Word8) -> ByteString -> ByteString
BS.map Word8 -> Word8
toLower8
{-# INLINE foldCase #-}
instance FoldCase (Ascii BL.ByteString) where
foldCase :: Ascii ByteString -> Ascii ByteString
foldCase = (ByteString -> ByteString) -> Ascii ByteString -> Ascii ByteString
forall v p. (v -> v) -> Checked p v -> Checked p v
trustMap ((ByteString -> ByteString)
-> Ascii ByteString -> Ascii ByteString)
-> (ByteString -> ByteString)
-> Ascii ByteString
-> Ascii ByteString
forall a b. (a -> b) -> a -> b
$ (Word8 -> Word8) -> ByteString -> ByteString
BL.map Word8 -> Word8
toLower8
{-# INLINE foldCase #-}
instance FoldCase (Ascii TS.Text) where
foldCase :: Ascii Text -> Ascii Text
foldCase = (Text -> Text) -> Ascii Text -> Ascii Text
forall v p. (v -> v) -> Checked p v -> Checked p v
trustMap ((Text -> Text) -> Ascii Text -> Ascii Text)
-> (Text -> Text) -> Ascii Text -> Ascii Text
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> Text -> Text
TS.map Char -> Char
toLower
{-# INLINE foldCase #-}
instance FoldCase (Ascii TL.Text) where
foldCase :: Ascii Text -> Ascii Text
foldCase = (Text -> Text) -> Ascii Text -> Ascii Text
forall v p. (v -> v) -> Checked p v -> Checked p v
trustMap ((Text -> Text) -> Ascii Text -> Ascii Text)
-> (Text -> Text) -> Ascii Text -> Ascii Text
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> Text -> Text
TL.map Char -> Char
toLower
{-# INLINE foldCase #-}
maybeAscii ∷ Char → Maybe Word8
maybeAscii :: Char -> Maybe Word8
maybeAscii Char
c | Char -> Bool
forall v. Property IsAscii v => v -> Bool
isAscii Char
c = Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (Word8 -> Maybe Word8) -> Word8 -> Maybe Word8
forall a b. (a -> b) -> a -> b
$ Char -> Word8
ascii Char
c
| Bool
otherwise = Maybe Word8
forall a. Maybe a
Nothing
{-# INLINABLE maybeAscii #-}
ascii ∷ Char → Word8
ascii :: Char -> Word8
ascii = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> (Char -> Int) -> Char -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord
{-# INLINE ascii #-}
isControl ∷ Char → Bool
isControl :: Char -> Bool
isControl Char
c = Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
32 Bool -> Bool -> Bool
|| Int
w Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
127
where w :: Int
w = Char -> Int
ord Char
c
{-# INLINE isControl #-}
isPrintable ∷ Char → Bool
isPrintable :: Char -> Bool
isPrintable Char
c = Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
32 Bool -> Bool -> Bool
&& Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
127
where w :: Int
w = Char -> Int
ord Char
c
{-# INLINE isPrintable #-}
isWhiteSpace ∷ Char → Bool
isWhiteSpace :: Char -> Bool
isWhiteSpace Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| (Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
9 Bool -> Bool -> Bool
&& Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
13)
where w :: Int
w = Char -> Int
ord Char
c
{-# INLINE isWhiteSpace #-}
isSpaceOrTab ∷ Char → Bool
isSpaceOrTab :: Char -> Bool
isSpaceOrTab Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t'
{-# INLINE isSpaceOrTab #-}
isLower ∷ Char → Bool
isLower :: Char -> Bool
isLower Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'a' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'z'
{-# INLINE isLower #-}
isUpper ∷ Char → Bool
isUpper :: Char -> Bool
isUpper Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'A' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'Z'
{-# INLINE isUpper #-}
toLower ∷ Char → Char
toLower :: Char -> Char
toLower Char
c | Char -> Bool
isUpper Char
c = Int -> Char
chr (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
32)
| Bool
otherwise = Char
c
{-# INLINABLE toLower #-}
toUpper ∷ Char → Char
toUpper :: Char -> Char
toUpper Char
c | Char -> Bool
isLower Char
c = Int -> Char
chr (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
32)
| Bool
otherwise = Char
c
{-# INLINABLE toUpper #-}
isAlpha ∷ Char → Bool
isAlpha :: Char -> Bool
isAlpha Char
c = Char -> Bool
isUpper Char
c Bool -> Bool -> Bool
|| Char -> Bool
isLower Char
c
{-# INLINABLE isAlpha #-}
isAlphaNum ∷ Char → Bool
isAlphaNum :: Char -> Bool
isAlphaNum Char
c = Char -> Bool
isDecDigit Char
c Bool -> Bool -> Bool
|| Char -> Bool
isAlpha Char
c
{-# INLINABLE isAlphaNum #-}
isDecDigit ∷ Char → Bool
isDecDigit :: Char -> Bool
isDecDigit Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9'
{-# INLINE isDecDigit #-}
isNzDecDigit ∷ Char → Bool
isNzDecDigit :: Char -> Bool
isNzDecDigit Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'1' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9'
{-# INLINE isNzDecDigit #-}
fromDecDigit ∷ Num a ⇒ Char → Maybe a
fromDecDigit :: forall a. Num a => Char -> Maybe a
fromDecDigit Char
c | Char -> Bool
isDecDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromDecDigit #-}
fromNzDecDigit ∷ Num a ⇒ Char → Maybe a
fromNzDecDigit :: forall a. Num a => Char -> Maybe a
fromNzDecDigit Char
c | Char -> Bool
isNzDecDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzDecDigit #-}
unsafeFromDecDigit ∷ Num a ⇒ Char → a
unsafeFromDecDigit :: forall a. Num a => Char -> a
unsafeFromDecDigit Char
c = Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'0')
{-# INLINE unsafeFromDecDigit #-}
isBinDigit ∷ Char → Bool
isBinDigit :: Char -> Bool
isBinDigit Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'0' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'1'
{-# INLINE isBinDigit #-}
isNzBinDigit ∷ Char → Bool
isNzBinDigit :: Char -> Bool
isNzBinDigit Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'1'
{-# INLINE isNzBinDigit #-}
fromBinDigit ∷ Num a ⇒ Char → Maybe a
fromBinDigit :: forall a. Num a => Char -> Maybe a
fromBinDigit Char
c | Char -> Bool
isBinDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromBinDigit Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromBinDigit #-}
fromNzBinDigit ∷ Num a ⇒ Char → Maybe a
fromNzBinDigit :: forall a. Num a => Char -> Maybe a
fromNzBinDigit Char
c | Char -> Bool
isNzBinDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just a
1
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzBinDigit #-}
unsafeFromBinDigit ∷ Num a ⇒ Char → a
unsafeFromBinDigit :: forall a. Num a => Char -> a
unsafeFromBinDigit = Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit
{-# INLINE unsafeFromBinDigit #-}
isOctDigit ∷ Char → Bool
isOctDigit :: Char -> Bool
isOctDigit Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'7'
{-# INLINE isOctDigit #-}
isNzOctDigit ∷ Char → Bool
isNzOctDigit :: Char -> Bool
isNzOctDigit Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'1' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'7'
{-# INLINE isNzOctDigit #-}
fromOctDigit ∷ Num a ⇒ Char → Maybe a
fromOctDigit :: forall a. Num a => Char -> Maybe a
fromOctDigit Char
c | Char -> Bool
isOctDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromOctDigit Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromOctDigit #-}
fromNzOctDigit ∷ Num a ⇒ Char → Maybe a
fromNzOctDigit :: forall a. Num a => Char -> Maybe a
fromNzOctDigit Char
c | Char -> Bool
isNzOctDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromOctDigit Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzOctDigit #-}
unsafeFromOctDigit ∷ Num a ⇒ Char → a
unsafeFromOctDigit :: forall a. Num a => Char -> a
unsafeFromOctDigit = Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit
{-# INLINE unsafeFromOctDigit #-}
isLowAF ∷ Char → Bool
isLowAF :: Char -> Bool
isLowAF Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'a' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'f'
{-# INLINE isLowAF #-}
fromLowAF ∷ Num a ⇒ Char → a
fromLowAF :: forall a. Num a => Char -> a
fromLowAF Char
c = Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'a' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
10)
{-# INLINE fromLowAF #-}
isLowHexDigit ∷ Char → Bool
isLowHexDigit :: Char -> Bool
isLowHexDigit Char
c = Char -> Bool
isDecDigit Char
c Bool -> Bool -> Bool
|| Char -> Bool
isLowAF Char
c
{-# INLINABLE isLowHexDigit #-}
isNzLowHexDigit ∷ Char → Bool
isNzLowHexDigit :: Char -> Bool
isNzLowHexDigit Char
c = Char -> Bool
isNzDecDigit Char
c Bool -> Bool -> Bool
|| Char -> Bool
isLowAF Char
c
{-# INLINABLE isNzLowHexDigit #-}
fromLowHexDigit ∷ Num a ⇒ Char → Maybe a
fromLowHexDigit :: forall a. Num a => Char -> Maybe a
fromLowHexDigit Char
c | Char -> Bool
isDecDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Char -> Bool
isLowAF Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
fromLowAF Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromLowHexDigit #-}
fromNzLowHexDigit ∷ Num a ⇒ Char → Maybe a
fromNzLowHexDigit :: forall a. Num a => Char -> Maybe a
fromNzLowHexDigit Char
c | Char -> Bool
isNzDecDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Char -> Bool
isLowAF Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
fromLowAF Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzLowHexDigit #-}
unsafeFromLowHexDigit ∷ Num a ⇒ Char → a
unsafeFromLowHexDigit :: forall a. Num a => Char -> a
unsafeFromLowHexDigit Char
c | Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
< Char
'a' = Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Bool
otherwise = Char -> a
forall a. Num a => Char -> a
fromLowAF Char
c
{-# INLINE unsafeFromLowHexDigit #-}
isUpAF ∷ Char → Bool
isUpAF :: Char -> Bool
isUpAF Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'A' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'F'
{-# INLINE isUpAF #-}
fromUpAF ∷ Num a ⇒ Char → a
fromUpAF :: forall a. Num a => Char -> a
fromUpAF Char
c = Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'A' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
10)
{-# INLINE fromUpAF #-}
isUpHexDigit ∷ Char → Bool
isUpHexDigit :: Char -> Bool
isUpHexDigit Char
c = Char -> Bool
isDecDigit Char
c Bool -> Bool -> Bool
|| Char -> Bool
isUpAF Char
c
{-# INLINABLE isUpHexDigit #-}
isNzUpHexDigit ∷ Char → Bool
isNzUpHexDigit :: Char -> Bool
isNzUpHexDigit Char
c = Char -> Bool
isNzDecDigit Char
c Bool -> Bool -> Bool
|| Char -> Bool
isUpAF Char
c
{-# INLINABLE isNzUpHexDigit #-}
fromUpHexDigit ∷ Num a ⇒ Char → Maybe a
fromUpHexDigit :: forall a. Num a => Char -> Maybe a
fromUpHexDigit Char
c | Char -> Bool
isDecDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Char -> Bool
isUpAF Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
fromUpAF Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromUpHexDigit #-}
fromNzUpHexDigit ∷ Num a ⇒ Char → Maybe a
fromNzUpHexDigit :: forall a. Num a => Char -> Maybe a
fromNzUpHexDigit Char
c | Char -> Bool
isNzDecDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Char -> Bool
isUpAF Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
fromUpAF Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzUpHexDigit #-}
unsafeFromUpHexDigit ∷ Num a ⇒ Char → a
unsafeFromUpHexDigit :: forall a. Num a => Char -> a
unsafeFromUpHexDigit Char
c | Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
< Char
'A' = Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Bool
otherwise = Char -> a
forall a. Num a => Char -> a
fromUpAF Char
c
{-# INLINE unsafeFromUpHexDigit #-}
isHexDigit ∷ Char → Bool
isHexDigit :: Char -> Bool
isHexDigit Char
c = Char -> Bool
isDecDigit Char
c Bool -> Bool -> Bool
|| Char -> Bool
isUpAF Char
c Bool -> Bool -> Bool
|| Char -> Bool
isLowAF Char
c
{-# INLINABLE isHexDigit #-}
isNzHexDigit ∷ Char → Bool
isNzHexDigit :: Char -> Bool
isNzHexDigit Char
c = Char -> Bool
isNzDecDigit Char
c Bool -> Bool -> Bool
|| Char -> Bool
isUpAF Char
c Bool -> Bool -> Bool
|| Char -> Bool
isLowAF Char
c
{-# INLINABLE isNzHexDigit #-}
fromHexDigit ∷ Num a ⇒ Char → Maybe a
fromHexDigit :: forall a. Num a => Char -> Maybe a
fromHexDigit Char
c | Char -> Bool
isDecDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Char -> Bool
isUpAF Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
fromUpAF Char
c
| Char -> Bool
isLowAF Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
fromLowAF Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromHexDigit #-}
fromNzHexDigit ∷ Num a ⇒ Char → Maybe a
fromNzHexDigit :: forall a. Num a => Char -> Maybe a
fromNzHexDigit Char
c | Char -> Bool
isNzDecDigit Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Char -> Bool
isUpAF Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
fromUpAF Char
c
| Char -> Bool
isLowAF Char
c = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Char -> a
forall a. Num a => Char -> a
fromLowAF Char
c
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzHexDigit #-}
unsafeFromHexDigit ∷ Num a ⇒ Char → a
unsafeFromHexDigit :: forall a. Num a => Char -> a
unsafeFromHexDigit Char
c | Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
< Char
'A' = Char -> a
forall a. Num a => Char -> a
unsafeFromDecDigit Char
c
| Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
< Char
'a' = Char -> a
forall a. Num a => Char -> a
fromUpAF Char
c
| Bool
otherwise = Char -> a
forall a. Num a => Char -> a
fromLowAF Char
c
{-# INLINE unsafeFromHexDigit #-}
isControl8 ∷ Word8 → Bool
isControl8 :: Word8 -> Bool
isControl8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
32 Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
127
{-# INLINE isControl8 #-}
isPrintable8 ∷ Word8 → Bool
isPrintable8 :: Word8 -> Bool
isPrintable8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
32 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
127
{-# INLINE isPrintable8 #-}
isWhiteSpace8 ∷ Word8 → Bool
isWhiteSpace8 :: Word8 -> Bool
isWhiteSpace8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Word8
ascii Char
' ' Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
9 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
13
{-# INLINE isWhiteSpace8 #-}
isSpaceOrTab8 ∷ Word8 → Bool
isSpaceOrTab8 :: Word8 -> Bool
isSpaceOrTab8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Word8
ascii Char
' ' Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Word8
ascii Char
'\t'
{-# INLINE isSpaceOrTab8 #-}
isLower8 ∷ Word8 → Bool
isLower8 :: Word8 -> Bool
isLower8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Char -> Word8
ascii Char
'a' Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Char -> Word8
ascii Char
'z'
{-# INLINE isLower8 #-}
isUpper8 ∷ Word8 → Bool
isUpper8 :: Word8 -> Bool
isUpper8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Char -> Word8
ascii Char
'A' Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Char -> Word8
ascii Char
'Z'
{-# INLINE isUpper8 #-}
toLower8 ∷ Word8 → Word8
toLower8 :: Word8 -> Word8
toLower8 Word8
w | Word8 -> Bool
isUpper8 Word8
w = Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
32
| Bool
otherwise = Word8
w
{-# INLINABLE toLower8 #-}
toUpper8 ∷ Word8 → Word8
toUpper8 :: Word8 -> Word8
toUpper8 Word8
w | Word8 -> Bool
isLower8 Word8
w = Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Word8
32
| Bool
otherwise = Word8
w
{-# INLINABLE toUpper8 #-}
isAlpha8 ∷ Word8 → Bool
isAlpha8 :: Word8 -> Bool
isAlpha8 Word8
w = Word8 -> Bool
isUpper8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isLower8 Word8
w
{-# INLINABLE isAlpha8 #-}
isAlphaNum8 ∷ Word8 → Bool
isAlphaNum8 :: Word8 -> Bool
isAlphaNum8 Word8
w = Word8 -> Bool
isDecDigit8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isAlpha8 Word8
w
{-# INLINABLE isAlphaNum8 #-}
isDecDigit8 ∷ Word8 → Bool
isDecDigit8 :: Word8 -> Bool
isDecDigit8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Char -> Word8
ascii Char
'0' Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Char -> Word8
ascii Char
'9'
{-# INLINE isDecDigit8 #-}
isNzDecDigit8 ∷ Word8 → Bool
isNzDecDigit8 :: Word8 -> Bool
isNzDecDigit8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Char -> Word8
ascii Char
'1' Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Char -> Word8
ascii Char
'9'
{-# INLINE isNzDecDigit8 #-}
fromDecDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromDecDigit8 :: forall a. Num a => Word8 -> Maybe a
fromDecDigit8 Word8
w | Word8 -> Bool
isDecDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromDecDigit8 #-}
fromNzDecDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromNzDecDigit8 :: forall a. Num a => Word8 -> Maybe a
fromNzDecDigit8 Word8
w | Word8 -> Bool
isNzDecDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzDecDigit8 #-}
unsafeFromDecDigit8 ∷ Num a ⇒ Word8 → a
unsafeFromDecDigit8 :: forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w = Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Char -> Word8
ascii Char
'0')
{-# INLINE unsafeFromDecDigit8 #-}
isBinDigit8 ∷ Word8 → Bool
isBinDigit8 :: Word8 -> Bool
isBinDigit8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Word8
ascii Char
'0' Bool -> Bool -> Bool
|| Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Word8
ascii Char
'1'
{-# INLINE isBinDigit8 #-}
isNzBinDigit8 ∷ Word8 → Bool
isNzBinDigit8 :: Word8 -> Bool
isNzBinDigit8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Word8
ascii Char
'1'
{-# INLINE isNzBinDigit8 #-}
fromBinDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromBinDigit8 :: forall a. Num a => Word8 -> Maybe a
fromBinDigit8 Word8
w | Word8 -> Bool
isBinDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromBinDigit8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromBinDigit8 #-}
fromNzBinDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromNzBinDigit8 :: forall a. Num a => Word8 -> Maybe a
fromNzBinDigit8 Word8
w | Word8 -> Bool
isNzBinDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just a
1
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzBinDigit8 #-}
unsafeFromBinDigit8 ∷ Num a ⇒ Word8 → a
unsafeFromBinDigit8 :: forall a. Num a => Word8 -> a
unsafeFromBinDigit8 = Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8
{-# INLINE unsafeFromBinDigit8 #-}
isOctDigit8 ∷ Word8 → Bool
isOctDigit8 :: Word8 -> Bool
isOctDigit8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Char -> Word8
ascii Char
'0' Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Char -> Word8
ascii Char
'7'
{-# INLINE isOctDigit8 #-}
isNzOctDigit8 ∷ Word8 → Bool
isNzOctDigit8 :: Word8 -> Bool
isNzOctDigit8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Char -> Word8
ascii Char
'1' Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Char -> Word8
ascii Char
'7'
{-# INLINE isNzOctDigit8 #-}
fromOctDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromOctDigit8 :: forall a. Num a => Word8 -> Maybe a
fromOctDigit8 Word8
w | Word8 -> Bool
isOctDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromOctDigit8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromOctDigit8 #-}
fromNzOctDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromNzOctDigit8 :: forall a. Num a => Word8 -> Maybe a
fromNzOctDigit8 Word8
w | Word8 -> Bool
isNzOctDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromOctDigit8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzOctDigit8 #-}
unsafeFromOctDigit8 ∷ Num a ⇒ Word8 → a
unsafeFromOctDigit8 :: forall a. Num a => Word8 -> a
unsafeFromOctDigit8 = Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8
{-# INLINE unsafeFromOctDigit8 #-}
isLowAF8 ∷ Word8 → Bool
isLowAF8 :: Word8 -> Bool
isLowAF8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Char -> Word8
ascii Char
'a' Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Char -> Word8
ascii Char
'f'
{-# INLINE isLowAF8 #-}
fromLowAF8 ∷ Num a ⇒ Word8 → a
fromLowAF8 :: forall a. Num a => Word8 -> a
fromLowAF8 Word8
w = Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Char -> Word8
ascii Char
'a' Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
10)
{-# INLINE fromLowAF8 #-}
isLowHexDigit8 ∷ Word8 → Bool
isLowHexDigit8 :: Word8 -> Bool
isLowHexDigit8 Word8
w = Word8 -> Bool
isDecDigit8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isLowAF8 Word8
w
{-# INLINABLE isLowHexDigit8 #-}
isNzLowHexDigit8 ∷ Word8 → Bool
isNzLowHexDigit8 :: Word8 -> Bool
isNzLowHexDigit8 Word8
w = Word8 -> Bool
isNzDecDigit8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isLowAF8 Word8
w
{-# INLINABLE isNzLowHexDigit8 #-}
fromLowHexDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromLowHexDigit8 :: forall a. Num a => Word8 -> Maybe a
fromLowHexDigit8 Word8
w | Word8 -> Bool
isDecDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Word8 -> Bool
isLowAF8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
fromLowAF8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromLowHexDigit8 #-}
fromNzLowHexDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromNzLowHexDigit8 :: forall a. Num a => Word8 -> Maybe a
fromNzLowHexDigit8 Word8
w | Word8 -> Bool
isNzDecDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Word8 -> Bool
isLowAF8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
fromLowAF8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzLowHexDigit8 #-}
unsafeFromLowHexDigit8 ∷ Num a ⇒ Word8 → a
unsafeFromLowHexDigit8 :: forall a. Num a => Word8 -> a
unsafeFromLowHexDigit8 Word8
w | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Char -> Word8
ascii Char
'a' = Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Bool
otherwise = Word8 -> a
forall a. Num a => Word8 -> a
fromLowAF8 Word8
w
{-# INLINE unsafeFromLowHexDigit8 #-}
isUpAF8 ∷ Word8 → Bool
isUpAF8 :: Word8 -> Bool
isUpAF8 Word8
w = Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Char -> Word8
ascii Char
'A' Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Char -> Word8
ascii Char
'F'
{-# INLINE isUpAF8 #-}
fromUpAF8 ∷ Num a ⇒ Word8 → a
fromUpAF8 :: forall a. Num a => Word8 -> a
fromUpAF8 Word8
w = Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Char -> Word8
ascii Char
'A' Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
10)
{-# INLINE fromUpAF8 #-}
isUpHexDigit8 ∷ Word8 → Bool
isUpHexDigit8 :: Word8 -> Bool
isUpHexDigit8 Word8
w = Word8 -> Bool
isDecDigit8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isUpAF8 Word8
w
{-# INLINABLE isUpHexDigit8 #-}
isNzUpHexDigit8 ∷ Word8 → Bool
isNzUpHexDigit8 :: Word8 -> Bool
isNzUpHexDigit8 Word8
w = Word8 -> Bool
isNzDecDigit8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isUpAF8 Word8
w
{-# INLINABLE isNzUpHexDigit8 #-}
fromUpHexDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromUpHexDigit8 :: forall a. Num a => Word8 -> Maybe a
fromUpHexDigit8 Word8
w | Word8 -> Bool
isDecDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Word8 -> Bool
isUpAF8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
fromUpAF8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromUpHexDigit8 #-}
fromNzUpHexDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromNzUpHexDigit8 :: forall a. Num a => Word8 -> Maybe a
fromNzUpHexDigit8 Word8
w | Word8 -> Bool
isNzDecDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Word8 -> Bool
isUpAF8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
fromUpAF8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzUpHexDigit8 #-}
unsafeFromUpHexDigit8 ∷ Num a ⇒ Word8 → a
unsafeFromUpHexDigit8 :: forall a. Num a => Word8 -> a
unsafeFromUpHexDigit8 Word8
w | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Char -> Word8
ascii Char
'A' = Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Bool
otherwise = Word8 -> a
forall a. Num a => Word8 -> a
fromUpAF8 Word8
w
{-# INLINE unsafeFromUpHexDigit8 #-}
isHexDigit8 ∷ Word8 → Bool
isHexDigit8 :: Word8 -> Bool
isHexDigit8 Word8
w = Word8 -> Bool
isDecDigit8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isUpAF8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isLowAF8 Word8
w
{-# INLINABLE isHexDigit8 #-}
isNzHexDigit8 ∷ Word8 → Bool
isNzHexDigit8 :: Word8 -> Bool
isNzHexDigit8 Word8
w = Word8 -> Bool
isNzDecDigit8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isUpAF8 Word8
w Bool -> Bool -> Bool
|| Word8 -> Bool
isLowAF8 Word8
w
{-# INLINABLE isNzHexDigit8 #-}
fromHexDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromHexDigit8 :: forall a. Num a => Word8 -> Maybe a
fromHexDigit8 Word8
w | Word8 -> Bool
isDecDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Word8 -> Bool
isUpAF8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
fromUpAF8 Word8
w
| Word8 -> Bool
isLowAF8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
fromLowAF8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromHexDigit8 #-}
fromNzHexDigit8 ∷ Num a ⇒ Word8 → Maybe a
fromNzHexDigit8 :: forall a. Num a => Word8 -> Maybe a
fromNzHexDigit8 Word8
w | Word8 -> Bool
isNzDecDigit8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Word8 -> Bool
isUpAF8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
fromUpAF8 Word8
w
| Word8 -> Bool
isLowAF8 Word8
w = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Word8 -> a
forall a. Num a => Word8 -> a
fromLowAF8 Word8
w
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
{-# INLINABLE fromNzHexDigit8 #-}
unsafeFromHexDigit8 ∷ Num a ⇒ Word8 → a
unsafeFromHexDigit8 :: forall a. Num a => Word8 -> a
unsafeFromHexDigit8 Word8
w | Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Char -> Word8
ascii Char
'A' = Word8 -> a
forall a. Num a => Word8 -> a
unsafeFromDecDigit8 Word8
w
| Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Char -> Word8
ascii Char
'a' = Word8 -> a
forall a. Num a => Word8 -> a
fromUpAF8 Word8
w
| Bool
otherwise = Word8 -> a
forall a. Num a => Word8 -> a
fromLowAF8 Word8
w
{-# INLINE unsafeFromHexDigit8 #-}