{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module Text.Ascii.Internal where
import Control.DeepSeq (NFData)
import Data.ByteString (ByteString)
import Data.Char (chr, isAscii)
import Data.Coerce (coerce)
import Data.Hashable (Hashable)
import Data.Word (Word8)
import GHC.Exts (IsList (Item, fromList, fromListN, toList))
import Numeric (showHex)
import Type.Reflection (Typeable)
newtype AsciiChar = AsciiChar {toByte :: Word8}
deriving
(
Eq,
Ord,
Hashable,
NFData
)
via Word8
deriving stock
(
Typeable
)
instance Show AsciiChar where
{-# INLINEABLE show #-}
show (AsciiChar w8) = "'0x" <> showHex w8 "'"
instance Bounded AsciiChar where
minBound = AsciiChar 0
maxBound = AsciiChar 127
pattern AsByte :: Word8 -> AsciiChar
pattern AsByte w8 <- AsciiChar w8
pattern AsChar :: Char -> AsciiChar
pattern AsChar c <- AsciiChar (isJustAscii -> Just c)
{-# COMPLETE AsByte #-}
{-# COMPLETE AsChar #-}
newtype AsciiText = AsciiText ByteString
deriving
(
Eq,
Ord,
NFData,
Semigroup,
Monoid,
Show
)
via ByteString
instance IsList AsciiText where
type Item AsciiText = AsciiChar
{-# INLINEABLE fromList #-}
fromList =
coerce @ByteString @AsciiText
. fromList
. coerce @[AsciiChar] @[Word8]
{-# INLINEABLE fromListN #-}
fromListN n =
coerce @ByteString @AsciiText
. fromListN n
. coerce @[AsciiChar] @[Word8]
{-# INLINEABLE toList #-}
toList = coerce . toList . coerce @AsciiText @ByteString
isJustAscii :: Word8 -> Maybe Char
isJustAscii w8 =
if isAscii asChar
then pure asChar
else Nothing
where
asChar :: Char
asChar = chr . fromIntegral $ w8