{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE Trustworthy #-}
module Text.Ascii.QQ where
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Char
( isAlphaNum,
isAscii,
isPunctuation,
isSymbol,
ord,
)
import Data.Functor (void)
import Data.Void (Void)
import GHC.Exts (IsList (fromList))
import Language.Haskell.TH.Quote (QuasiQuoter (QuasiQuoter))
import Language.Haskell.TH.Syntax
( Dec,
Exp (AppE, ConE, ListE, LitE, VarE),
Lit (IntegerL),
Pat,
Q,
Type,
)
import Text.Ascii.Internal (AsciiChar (AsciiChar), AsciiText (AsciiText))
import Text.Megaparsec
( Parsec,
between,
eof,
lookAhead,
manyTill,
oneOf,
parse,
satisfy,
single,
try,
)
import Text.Megaparsec.Char (space)
import Text.Megaparsec.Error (errorBundlePretty)
char :: QuasiQuoter
char = QuasiQuoter charQQ (errPat "char") (errType "char") (errDec "char")
ascii :: QuasiQuoter
ascii = QuasiQuoter asciiQQ (errPat "ascii") (errType "ascii") (errDec "ascii")
asciiQQ :: String -> Q Exp
asciiQQ input = case parse (between open close go) "" input of
Left err -> fail . errorBundlePretty $ err
Right result ->
pure
. AppE (ConE 'AsciiText)
. AppE (VarE 'fromList)
. ListE
. fmap (LitE . IntegerL . fromIntegral)
. BS.unpack
$ result
where
open :: Parsec Void String ()
open = space *> (void . single $ '"')
close :: Parsec Void String ()
close = single '"' *> space *> eof
go :: Parsec Void String ByteString
go = BS.pack <$> manyTill asciiByte (lookAhead . try . single $ '"')
asciiByte = do
c <- satisfy isAscii
case c of
'\\' -> do
c' <- oneOf "0abfnrtv\\\""
pure . fromIntegral . ord $ case c' of
'0' -> '\0'
'a' -> '\a'
'b' -> '\b'
'f' -> '\f'
'n' -> '\n'
'r' -> '\r'
't' -> '\t'
'v' -> '\v'
'\\' -> '\\'
_ -> '"'
_ -> pure . fromIntegral . ord $ c
charQQ :: String -> Q Exp
charQQ input = case parse (between open close go) "" input of
Left err -> fail . errorBundlePretty $ err
Right result ->
pure . AppE (ConE 'AsciiChar) . LitE . IntegerL . fromIntegral $ result
where
open :: Parsec Void String ()
open = space *> (void . single $ '\'')
close :: Parsec Void String ()
close = single '\'' *> space *> eof
go :: Parsec Void String Int
go = do
c1 <- satisfy isValidLead
case c1 of
'\\' -> do
c2 <- oneOf "0abfnrtv\\\'"
pure . ord $ case c2 of
'0' -> '\0'
'a' -> '\a'
'b' -> '\b'
'f' -> '\f'
'n' -> '\n'
'r' -> '\r'
't' -> '\t'
'v' -> '\v'
'\\' -> '\\'
_ -> '\''
_ -> pure . ord $ c1
isValidLead :: Char -> Bool
isValidLead c = isAscii c && (isAlphaNum c || c == ' ' || isSymbol c || isPunctuation c)
errPat :: String -> String -> Q Pat
errPat name _ = fail $ "'" <> name <> "' should not be used in a pattern context."
errType :: String -> String -> Q Type
errType name _ = fail $ "'" <> name <> "' should not be used in a type context."
errDec :: String -> String -> Q [Dec]
errDec name _ = fail $ "'" <> name <> "' should not be used in a declaration context."