{-# LANGUAGE Trustworthy #-}
{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UnicodeSyntax #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-unused-do-bind #-}
module Text.Gigaparsec.Internal.Token.Patterns.LexerCombinators (
module Text.Gigaparsec.Internal.Token.Patterns.LexerCombinators,
) where
import safe Text.Gigaparsec.Internal.Token.Lexer (
Lexeme (
charLiteral,
multiStringLiteral,
names,
rawMultiStringLiteral,
rawStringLiteral,
stringLiteral,
symbol
),
Lexer (lexeme, space),
Space,
)
import safe Text.Gigaparsec.Internal.Token.Names (Names)
import safe Text.Gigaparsec.Internal.Token.Symbol (Symbol)
import safe Text.Gigaparsec.Internal.Token.Text (TextParsers)
import Text.Gigaparsec.Internal.TH.DecUtils (funDsingleClause)
import Text.Gigaparsec.Internal.TH.TypeUtils (removeUnusedTVars, sanitiseBndrStars, sanitiseTypeStars)
import Text.Gigaparsec.Internal.TH.VersionAgnostic (
Dec, DocLoc(DeclDoc), Exp, Inline (Inline), Phases (AllPhases), Q, Quasi (qRecover),
Quote (newName), Type (ForallT), addModFinalizer, getDoc, isInstance,
nameBase, putDoc, reifyType,
RuleMatch (FunLike),
Type (AppT, ArrowT, ForallVisT),
pattern MulArrowT,
clause,
funD,
normalB,
pprint,
pragInlD,
sigD,
varE,
)
import Data.Bifunctor (Bifunctor (first))
import Data.Kind (Constraint)
import Data.Maybe (fromMaybe)
import Text.Gigaparsec.Internal.TH.VersionAgnostic (Name)
import Text.Gigaparsec.Token.Lexer qualified as Lexer
lexerCombinators
:: Q Exp
-> [Name]
-> Q [Dec]
lexerCombinators :: Q Exp -> [Name] -> Q [Dec]
lexerCombinators Q Exp
lexer [Name]
ns = Q Exp -> [(Name, String)] -> Q [Dec]
lexerCombinatorsWithNames Q Exp
lexer ([Name] -> [String] -> [(Name, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
ns ((Name -> String) -> [Name] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Name -> String
nameBase [Name]
ns))
lexerCombinatorsWithNames
:: Q Exp
-> [(Name, String)]
-> Q [Dec]
lexerCombinatorsWithNames :: Q Exp -> [(Name, String)] -> Q [Dec]
lexerCombinatorsWithNames Q Exp
lexer = ([[Dec]] -> [Dec]) -> Q [[Dec]] -> Q [Dec]
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[Dec]] -> [Dec]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (Q [[Dec]] -> Q [Dec])
-> ([(Name, String)] -> Q [[Dec]]) -> [(Name, String)] -> Q [Dec]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Name, String) -> Q [Dec]) -> [(Name, String)] -> Q [[Dec]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((Name -> String -> Q [Dec]) -> (Name, String) -> Q [Dec]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (Q Exp -> Name -> String -> Q [Dec]
lexerCombinatorWithName Q Exp
lexer))
lexerCombinatorWithName
:: Q Exp
-> Name
-> String
-> Q [Dec]
lexerCombinatorWithName :: Q Exp -> Name -> String -> Q [Dec]
lexerCombinatorWithName Q Exp
lexer Name
old String
nm = do
newTp <- Name -> Bool -> Q Type
getLexerCombinatorType Name
old Bool
True
mkLexerCombinatorDec lexer nm old newTp
mkLexerCombinatorDec
:: Q Exp
-> String
-> Name
-> Type
-> Q [Dec]
mkLexerCombinatorDec :: Q Exp -> String -> Name -> Type -> Q [Dec]
mkLexerCombinatorDec Q Exp
lexer String
nm Name
old Type
tp = do
newX <- String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
nm
oldDocs <- getDoc (DeclDoc old)
let newDocs = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"" Maybe String
oldDocs
addModFinalizer $ putDoc (DeclDoc newX) newDocs
sequence
[ pragInlD newX Inline FunLike AllPhases
, sigD newX (pure tp)
, funD newX [clause [] (normalB [|project $(varE old) $lexer|]) []]
]
mkLexerCombinatorDecWithProj
:: Q Exp
-> String
-> Name
-> Q Type
-> Q Exp
-> Q (Name, [Dec])
mkLexerCombinatorDecWithProj :: Q Exp -> String -> Name -> Q Type -> Q Exp -> Q (Name, [Dec])
mkLexerCombinatorDecWithProj Q Exp
lexer String
nm Name
old Q Type
tp Q Exp
proj = do
newX <- String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
nm
oldDocs <- getDoc (DeclDoc old)
let newDocs = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"" Maybe String
oldDocs
addModFinalizer $ putDoc (DeclDoc newX) newDocs
(newX,)
<$> sequence
[ pragInlD newX Inline FunLike AllPhases
, sigD newX tp
, funDsingleClause newX [|project ($(varE old) . $proj) $lexer|]
]
getLexerCombinatorType :: Name -> Bool -> Q Type
getLexerCombinatorType :: Name -> Bool -> Q Type
getLexerCombinatorType Name
old Bool
checkType = do
tp <- Name -> Q Type
reifyType Name
old
(prefix, dom, _, cod) <-
fail (notFunctionTypeMsg old tp) `qRecover` fnTpDomain tp
let newTp = Type -> Type
prefix Type
cod
b <- isInstance ''LexerField [dom]
if checkType && not b
then catchErrors dom newTp
else return $ prefix cod
where
notFunctionTypeMsg :: Name -> Type -> String
notFunctionTypeMsg :: Name -> Type -> String
notFunctionTypeMsg Name
x Type
tp = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"Constant `", Name -> String
nameBase Name
x, String
"` does not have a function type: ", Type -> String
forall a. Show a => a -> String
show Type
tp]
catchErrors :: Type -> Type -> Q a
catchErrors :: forall a. Type -> Type -> Q a
catchErrors Type
dom Type
newTp
| Name
old Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== 'Lexer.ascii = Name -> Q a
forall a. Name -> Q a
failStringParser Name
old
| Name
old Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== 'Lexer.unicode = Name -> Q a
forall a. Name -> Q a
failStringParser Name
old
| Name
old Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== 'Lexer.latin1 = Name -> Q a
forall a. Name -> Q a
failStringParser Name
old
| Bool
otherwise = String -> Q a
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (Name -> Type -> String
notLexerFieldMsg Name
old Type
dom)
failStringParser :: Name -> Q a
failStringParser :: forall a. Name -> Q a
failStringParser Name
nm =
String -> Q a
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q a) -> String -> Q a
forall a b. (a -> b) -> a -> b
$
[String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"Cannot derive a lexer combinator for `"
, Name -> String
nameBase Name
nm
, String
"`, as there are many possible "
, Name -> String
forall a. Ppr a => a -> String
pprint ''TextParsers
, String
" to define it in terms of, including:"
, Name -> String
forall a. Ppr a => a -> String
pprint 'stringLiteral
, String
", "
, Name -> String
forall a. Ppr a => a -> String
pprint 'rawStringLiteral
, String
", "
, Name -> String
forall a. Ppr a => a -> String
pprint 'multiStringLiteral
, String
", and "
, Name -> String
forall a. Ppr a => a -> String
pprint 'rawMultiStringLiteral
, String
"."
, String
"\n You will need to manually define this combinator, as you are then able to pick which TextParser it should use."
]
notLexerFieldMsg :: Name -> Type -> String
notLexerFieldMsg :: Name -> Type -> String
notLexerFieldMsg Name
x Type
tp =
[String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"Cannot produce a lexer combinator for function: "
, Name -> String
nameBase Name
x
, String
"."
, String
"\n This is because the type: `"
, Type -> String
forall a. Ppr a => a -> String
pprint Type
tp
, String
"` cannot be used to give a precise combinator, either because it does not refer to "
, String
"any fields of a `Lexer`, or because it ambiguously refers to many fields of a `Lexer`."
, String
"\n Some fields of the `Lexer` share the same type, so there are multiple possible candidate combinators for a particular field."
, String
" For example: "
, String
"\n - `decimal`, `hexadecimal`,... all have type `IntegerParsers canHold -> Parsec Integer`."
, String
"\n - `ascii`, `unicode`, ... all have type `TextParsers t -> Parsec t`."
]
type ArrowTp :: *
data ArrowTp = StdArrow | LinearArrow
fnTpDomain
:: Type
-> Q (Type -> Type, Type, ArrowTp, Type)
fnTpDomain :: Type -> Q (Type -> Type, Type, ArrowTp, Type)
fnTpDomain Type
x = do
(a, (b, c, d)) <- Type -> Q (Type -> Type, (Type, ArrowTp, Type))
fnTpDomain' (Type -> Q (Type -> Type, (Type, ArrowTp, Type)))
-> Q Type -> Q (Type -> Type, (Type, ArrowTp, Type))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Type -> Q Type
sanitiseTypeStars Type
x
return (removeUnusedTVars . a, b, c, d)
where
fnTpDomain' :: Type -> Q (Type -> Type, (Type, ArrowTp, Type))
fnTpDomain' (ForallT [TyVarBndr Specificity]
bnds [Type]
ctx Type
tp) = do
bnds' <- [TyVarBndr Specificity] -> Q [TyVarBndr Specificity]
forall flag. [TyVarBndr flag] -> Q [TyVarBndr flag]
sanitiseBndrStars [TyVarBndr Specificity]
bnds
first (ForallT bnds' ctx .) <$> fnTpDomain' tp
fnTpDomain' (ForallVisT [TyVarBndr ()]
bnds Type
tp) = do
bnds' <- [TyVarBndr ()] -> Q [TyVarBndr ()]
forall flag. [TyVarBndr flag] -> Q [TyVarBndr flag]
sanitiseBndrStars [TyVarBndr ()]
bnds
first (ForallVisT bnds' .) <$> fnTpDomain' tp
fnTpDomain' (AppT (AppT Type
ArrowT Type
a) Type
b) =
(Type -> Type, (Type, ArrowTp, Type))
-> Q (Type -> Type, (Type, ArrowTp, Type))
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return (Type -> Type
forall a. a -> a
id, (Type
a, ArrowTp
StdArrow, Type
b))
fnTpDomain' (AppT (AppT Type
MulArrowT Type
a) Type
b) =
(Type -> Type, (Type, ArrowTp, Type))
-> Q (Type -> Type, (Type, ArrowTp, Type))
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return (Type -> Type
forall a. a -> a
id, (Type
a, ArrowTp
LinearArrow, Type
b))
fnTpDomain' Type
tp =
String -> Q (Type -> Type, (Type, ArrowTp, Type))
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
(String
"Type of given function is not a function type: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Type -> String
forall a. Show a => a -> String
show Type
tp)
type LexerField :: * -> Constraint
class LexerField a where
project :: (a -> b) -> (Lexer -> b)
type LexerProj :: * -> * -> *
type LexerProj a b = (a -> b) -> (Lexer -> b)
instance LexerField Lexer where
{-# INLINE project #-}
project :: (Lexer -> b) -> (Lexer -> b)
project :: forall b. (Lexer -> b) -> Lexer -> b
project = (Lexer -> b) -> Lexer -> b
forall a. a -> a
id
instance LexerField Lexeme where
{-# INLINE project #-}
project :: (Lexeme -> b) -> (Lexer -> b)
project :: forall b. (Lexeme -> b) -> Lexer -> b
project Lexeme -> b
f = Lexeme -> b
f (Lexeme -> b) -> (Lexer -> Lexeme) -> Lexer -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lexer -> Lexeme
lexeme
instance LexerField Symbol where
{-# INLINE project #-}
project :: (Symbol -> b) -> (Lexer -> b)
project :: forall b. (Symbol -> b) -> Lexer -> b
project Symbol -> b
f = Symbol -> b
f (Symbol -> b) -> (Lexer -> Symbol) -> Lexer -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lexeme -> Symbol
symbol (Lexeme -> Symbol) -> (Lexer -> Lexeme) -> Lexer -> Symbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lexer -> Lexeme
lexeme
instance LexerField Names where
{-# INLINE project #-}
project :: (Names -> b) -> (Lexer -> b)
project :: forall b. (Names -> b) -> Lexer -> b
project Names -> b
f = Names -> b
f (Names -> b) -> (Lexer -> Names) -> Lexer -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lexeme -> Names
names (Lexeme -> Names) -> (Lexer -> Lexeme) -> Lexer -> Names
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lexer -> Lexeme
lexeme
instance LexerField (TextParsers Char) where
{-# INLINE project #-}
project :: (TextParsers Char -> b) -> (Lexer -> b)
project :: forall b. (TextParsers Char -> b) -> Lexer -> b
project TextParsers Char -> b
f = TextParsers Char -> b
f (TextParsers Char -> b)
-> (Lexer -> TextParsers Char) -> Lexer -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lexeme -> TextParsers Char
charLiteral (Lexeme -> TextParsers Char)
-> (Lexer -> Lexeme) -> Lexer -> TextParsers Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lexer -> Lexeme
lexeme
instance LexerField Space where
{-# INLINE project #-}
project :: (Space -> b) -> (Lexer -> b)
project :: forall b. (Space -> b) -> Lexer -> b
project Space -> b
f = Space -> b
f (Space -> b) -> (Lexer -> Space) -> Lexer -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lexer -> Space
space