{-# 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 qualified Data.ByteString as BS
import Data.CaseInsensitive (FoldCase (foldCase))
import Data.Char (chr, isAscii)
import Data.Coerce (coerce)
import Data.Hashable (Hashable)
import qualified Data.List.NonEmpty as NE
import Data.Word (Word8)
import GHC.Exts (IsList (Item, fromList, fromListN, toList))
import Numeric (showHex)
import Optics.AffineTraversal (An_AffineTraversal, atraversal)
import Optics.At.Core (Index, IxValue, Ixed (IxKind, ix))
import Text.Megaparsec.Stream
( Stream
( Token,
Tokens,
chunkLength,
chunkToTokens,
take1_,
takeN_,
takeWhile_,
tokenToChunk,
tokensToChunk
),
TraversableStream (reachOffset),
VisualStream (showTokens),
)
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
{-# INLINEABLE minBound #-}
minBound = AsciiChar 0
{-# INLINEABLE maxBound #-}
maxBound = AsciiChar 127
instance FoldCase AsciiChar where
{-# INLINEABLE foldCase #-}
foldCase ac@(AsciiChar w8)
| 65 <= w8 && w8 <= 90 = AsciiChar (w8 + 32)
| otherwise = ac
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
type instance Index AsciiText = Int
type instance IxValue AsciiText = AsciiChar
instance Ixed AsciiText where
type IxKind AsciiText = An_AffineTraversal
{-# INLINEABLE ix #-}
ix i = atraversal get put
where
get :: AsciiText -> Either AsciiText AsciiChar
get (AsciiText at) = case at BS.!? i of
Nothing -> Left . AsciiText $ at
Just w8 -> Right . AsciiChar $ w8
put :: AsciiText -> AsciiChar -> AsciiText
put (AsciiText at) (AsciiChar ac) = case BS.splitAt i at of
(lead, end) -> case BS.uncons end of
Nothing -> AsciiText at
Just (_, end') -> AsciiText (lead <> BS.singleton ac <> end')
instance FoldCase AsciiText where
{-# INLINEABLE foldCase #-}
foldCase (AsciiText bs) = AsciiText . BS.map go $ bs
where
go :: Word8 -> Word8
go w8
| 65 <= w8 && w8 <= 90 = w8 + 32
| otherwise = w8
instance Stream AsciiText where
type Token AsciiText = AsciiChar
type Tokens AsciiText = AsciiText
{-# INLINEABLE tokenToChunk #-}
tokenToChunk _ = coerce BS.singleton
{-# INLINEABLE tokensToChunk #-}
tokensToChunk _ = fromList
{-# INLINEABLE chunkToTokens #-}
chunkToTokens _ = toList
{-# INLINEABLE chunkLength #-}
chunkLength _ = coerce BS.length
{-# INLINEABLE take1_ #-}
take1_ = coerce BS.uncons
{-# INLINEABLE takeN_ #-}
takeN_ n at@(AsciiText bs)
| n <= 0 = Just (coerce BS.empty, at)
| BS.length bs == 0 = Nothing
| otherwise = Just . coerce . BS.splitAt n $ bs
{-# INLINEABLE takeWhile_ #-}
takeWhile_ = coerce BS.span
instance VisualStream AsciiText where
{-# INLINEABLE showTokens #-}
showTokens _ = fmap (chr . fromIntegral) . coerce @_ @[Word8] . NE.toList
instance TraversableStream AsciiText where
{-# INLINEABLE reachOffset #-}
reachOffset o ps = coerce (reachOffset o ps)
isJustAscii :: Word8 -> Maybe Char
isJustAscii w8 =
if isAscii asChar
then pure asChar
else Nothing
where
asChar :: Char
asChar = chr . fromIntegral $ w8