{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
module PlutusTx.Lift.Class
( Typeable (..)
, Lift (..)
, RTCompile
, makeTypeable
, makeLift
, withTyVars
, LiftError (..)
) where
import PlutusTx.Lift.THUtils
import PlutusIR
import PlutusIR.Compiler.Definitions
import PlutusIR.Compiler.Names
import PlutusIR.MkPir
import PlutusCore.Default qualified as PLC
import PlutusCore.MkPlc qualified as PLC
import PlutusCore.Quote
import Control.Monad.Except hiding (lift)
import Control.Monad.Reader hiding (lift)
import Control.Monad.State hiding (lift)
import Control.Monad.Trans qualified as Trans
import Language.Haskell.TH qualified as TH hiding (newName)
import Language.Haskell.TH.Datatype qualified as TH
import Language.Haskell.TH.Syntax qualified as TH hiding (newName)
import Language.Haskell.TH.Syntax.Compat qualified as TH
import Data.Map qualified as Map
import Data.Set qualified as Set
import Control.Exception qualified as Prelude (Exception, throw)
import Data.Foldable
import Data.List (sortBy)
import Data.Maybe
import Data.Proxy
import Data.Text qualified as T
import Data.Traversable
import ErrorCode
import Prettyprinter qualified as PP
import Prelude as Haskell
type RTCompile uni fun = DefT TH.Name uni fun () Quote
type RTCompileScope uni fun = ReaderT (LocalVars uni) (RTCompile uni fun)
type THCompile = StateT Deps (ReaderT THLocalVars (ExceptT LiftError TH.Q))
data LiftError = UnsupportedLiftKind TH.Kind
| UnsupportedLiftType TH.Type
| UserLiftError T.Text
| LiftMissingDataCons TH.Name
| LiftMissingVar TH.Name
deriving anyclass (Show LiftError
Typeable LiftError
Typeable LiftError
-> Show LiftError
-> (LiftError -> SomeException)
-> (SomeException -> Maybe LiftError)
-> (LiftError -> String)
-> Exception LiftError
SomeException -> Maybe LiftError
LiftError -> String
LiftError -> SomeException
forall e.
Typeable e
-> Show e
-> (e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> Exception e
displayException :: LiftError -> String
$cdisplayException :: LiftError -> String
fromException :: SomeException -> Maybe LiftError
$cfromException :: SomeException -> Maybe LiftError
toException :: LiftError -> SomeException
$ctoException :: LiftError -> SomeException
$cp2Exception :: Show LiftError
$cp1Exception :: Typeable LiftError
Prelude.Exception)
instance PP.Pretty LiftError where
pretty :: LiftError -> Doc ann
pretty (UnsupportedLiftType Type
t) = Doc ann
"Unsupported lift type: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
PP.<+> Type -> Doc ann
forall a ann. Show a => a -> Doc ann
PP.viaShow Type
t
pretty (UnsupportedLiftKind Type
t) = Doc ann
"Unsupported lift kind: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
PP.<+> Type -> Doc ann
forall a ann. Show a => a -> Doc ann
PP.viaShow Type
t
pretty (UserLiftError Text
t) = Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
PP.pretty Text
t
pretty (LiftMissingDataCons Name
n) = Doc ann
"Constructors not created for type: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
PP.<+> Name -> Doc ann
forall a ann. Show a => a -> Doc ann
PP.viaShow Name
n
pretty (LiftMissingVar Name
n) = Doc ann
"Unknown local variable: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
PP.<+> Name -> Doc ann
forall a ann. Show a => a -> Doc ann
PP.viaShow Name
n
instance Show LiftError where
show :: LiftError -> String
show = Doc Any -> String
forall a. Show a => a -> String
show (Doc Any -> String)
-> (LiftError -> Doc Any) -> LiftError -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LiftError -> Doc Any
forall a ann. Pretty a => a -> Doc ann
PP.pretty
instance HasErrorCode LiftError where
errorCode :: LiftError -> ErrorCode
errorCode UnsupportedLiftType {} = Natural -> ErrorCode
ErrorCode Natural
44
errorCode UnsupportedLiftKind {} = Natural -> ErrorCode
ErrorCode Natural
45
errorCode UserLiftError {} = Natural -> ErrorCode
ErrorCode Natural
46
errorCode LiftMissingDataCons {} = Natural -> ErrorCode
ErrorCode Natural
47
errorCode LiftMissingVar {} = Natural -> ErrorCode
ErrorCode Natural
48
newtype CompileType = CompileType { CompileType
-> forall fun. RTCompile DefaultUni fun (Type TyName DefaultUni ())
unCompileType :: forall fun . RTCompile PLC.DefaultUni fun (Type TyName PLC.DefaultUni ()) }
newtype CompileTypeScope = CompileTypeScope { CompileTypeScope
-> forall fun.
RTCompileScope DefaultUni fun (Type TyName DefaultUni ())
unCompileTypeScope :: forall fun . RTCompileScope PLC.DefaultUni fun (Type TyName PLC.DefaultUni ()) }
newtype CompileDeclFun = CompileDeclFun { CompileDeclFun
-> forall fun.
Type TyName DefaultUni ()
-> RTCompileScope
DefaultUni fun (VarDecl TyName Name DefaultUni fun ())
unCompileDeclFun :: forall fun . Type TyName PLC.DefaultUni () -> RTCompileScope PLC.DefaultUni fun (VarDecl TyName Name PLC.DefaultUni fun ()) }
type LocalVars uni = Map.Map TH.Name (Type TyName uni ())
type THLocalVars = Set.Set TH.Name
withTyVars :: (MonadReader (LocalVars uni) m) => [(TH.Name, TyVarDecl TyName ())] -> m a -> m a
withTyVars :: [(Name, TyVarDecl TyName ())] -> m a -> m a
withTyVars [(Name, TyVarDecl TyName ())]
mappings = (Map Name (Type TyName uni ()) -> Map Name (Type TyName uni ()))
-> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\Map Name (Type TyName uni ())
scope -> (Map Name (Type TyName uni ())
-> (Name, TyVarDecl TyName ()) -> Map Name (Type TyName uni ()))
-> Map Name (Type TyName uni ())
-> [(Name, TyVarDecl TyName ())]
-> Map Name (Type TyName uni ())
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Map Name (Type TyName uni ())
acc (Name
n, TyVarDecl TyName ()
tvd) -> Name
-> Type TyName uni ()
-> Map Name (Type TyName uni ())
-> Map Name (Type TyName uni ())
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Name
n (() -> TyVarDecl TyName () -> Type TyName uni ()
forall ann tyname (uni :: * -> *).
ann -> TyVarDecl tyname ann -> Type tyname uni ann
mkTyVar () TyVarDecl TyName ()
tvd) Map Name (Type TyName uni ())
acc) Map Name (Type TyName uni ())
scope [(Name, TyVarDecl TyName ())]
mappings)
thWithTyVars :: (MonadReader THLocalVars m) => [TH.Name] -> m a -> m a
thWithTyVars :: [Name] -> m a -> m a
thWithTyVars [Name]
names = (Set Name -> Set Name) -> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\Set Name
scope -> (Name -> Set Name -> Set Name) -> Set Name -> [Name] -> Set Name
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Name -> Set Name -> Set Name
forall a. Ord a => a -> Set a -> Set a
Set.insert Set Name
scope [Name]
names)
data Dep = TypeableDep TH.Type | LiftDep TH.Type deriving stock (Int -> Dep -> ShowS
[Dep] -> ShowS
Dep -> String
(Int -> Dep -> ShowS)
-> (Dep -> String) -> ([Dep] -> ShowS) -> Show Dep
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Dep] -> ShowS
$cshowList :: [Dep] -> ShowS
show :: Dep -> String
$cshow :: Dep -> String
showsPrec :: Int -> Dep -> ShowS
$cshowsPrec :: Int -> Dep -> ShowS
Show, Dep -> Dep -> Bool
(Dep -> Dep -> Bool) -> (Dep -> Dep -> Bool) -> Eq Dep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dep -> Dep -> Bool
$c/= :: Dep -> Dep -> Bool
== :: Dep -> Dep -> Bool
$c== :: Dep -> Dep -> Bool
Eq, Eq Dep
Eq Dep
-> (Dep -> Dep -> Ordering)
-> (Dep -> Dep -> Bool)
-> (Dep -> Dep -> Bool)
-> (Dep -> Dep -> Bool)
-> (Dep -> Dep -> Bool)
-> (Dep -> Dep -> Dep)
-> (Dep -> Dep -> Dep)
-> Ord Dep
Dep -> Dep -> Bool
Dep -> Dep -> Ordering
Dep -> Dep -> Dep
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Dep -> Dep -> Dep
$cmin :: Dep -> Dep -> Dep
max :: Dep -> Dep -> Dep
$cmax :: Dep -> Dep -> Dep
>= :: Dep -> Dep -> Bool
$c>= :: Dep -> Dep -> Bool
> :: Dep -> Dep -> Bool
$c> :: Dep -> Dep -> Bool
<= :: Dep -> Dep -> Bool
$c<= :: Dep -> Dep -> Bool
< :: Dep -> Dep -> Bool
$c< :: Dep -> Dep -> Bool
compare :: Dep -> Dep -> Ordering
$ccompare :: Dep -> Dep -> Ordering
$cp1Ord :: Eq Dep
Ord)
type Deps = Set.Set Dep
getTyConDeps :: Deps -> Set.Set TH.Name
getTyConDeps :: Deps -> Set Name
getTyConDeps Deps
deps = [Name] -> Set Name
forall a. Ord a => [a] -> Set a
Set.fromList ([Name] -> Set Name) -> [Name] -> Set Name
forall a b. (a -> b) -> a -> b
$ (Dep -> Maybe Name) -> [Dep] -> [Name]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Dep -> Maybe Name
typeableDep ([Dep] -> [Name]) -> [Dep] -> [Name]
forall a b. (a -> b) -> a -> b
$ Deps -> [Dep]
forall a. Set a -> [a]
Set.toList Deps
deps
where
typeableDep :: Dep -> Maybe Name
typeableDep (TypeableDep (TH.ConT Name
n)) = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
n
typeableDep Dep
_ = Maybe Name
forall a. Maybe a
Nothing
addTypeableDep :: TH.Type -> THCompile ()
addTypeableDep :: Type -> THCompile ()
addTypeableDep Type
ty = do
Type
ty' <- Type -> THCompile Type
normalizeAndResolve Type
ty
(Deps -> Deps) -> THCompile ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((Deps -> Deps) -> THCompile ()) -> (Deps -> Deps) -> THCompile ()
forall a b. (a -> b) -> a -> b
$ Dep -> Deps -> Deps
forall a. Ord a => a -> Set a -> Set a
Set.insert (Dep -> Deps -> Deps) -> Dep -> Deps -> Deps
forall a b. (a -> b) -> a -> b
$ Type -> Dep
TypeableDep Type
ty'
addLiftDep :: TH.Type -> THCompile ()
addLiftDep :: Type -> THCompile ()
addLiftDep Type
ty = do
Type
ty' <- Type -> THCompile Type
normalizeAndResolve Type
ty
(Deps -> Deps) -> THCompile ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((Deps -> Deps) -> THCompile ()) -> (Deps -> Deps) -> THCompile ()
forall a b. (a -> b) -> a -> b
$ Dep -> Deps -> Deps
forall a. Ord a => a -> Set a -> Set a
Set.insert (Dep -> Deps -> Deps) -> Dep -> Deps -> Deps
forall a b. (a -> b) -> a -> b
$ Type -> Dep
LiftDep Type
ty'
typeablePir :: TH.Type -> TH.Type -> TH.Type
typeablePir :: Type -> Type -> Type
typeablePir Type
uni Type
ty = Name -> [Type] -> Type
TH.classPred ''Typeable [Type
uni, Type
ty]
liftPir :: TH.Type -> TH.Type -> TH.Type
liftPir :: Type -> Type -> Type
liftPir Type
uni Type
ty = Name -> [Type] -> Type
TH.classPred ''Lift [Type
uni, Type
ty]
toConstraint :: TH.Type -> Dep -> TH.Pred
toConstraint :: Type -> Dep -> Type
toConstraint Type
uni = \case
TypeableDep Type
n -> Type -> Type -> Type
typeablePir Type
uni Type
n
LiftDep Type
ty -> Type -> Type -> Type
liftPir Type
uni Type
ty
isClosedConstraint :: TH.Pred -> Bool
isClosedConstraint :: Type -> Bool
isClosedConstraint = [Name] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Name] -> Bool) -> (Type -> [Name]) -> Type -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> [Name]
forall a. TypeSubstitution a => a -> [Name]
TH.freeVariables
normalizeAndResolve :: TH.Type -> THCompile TH.Type
normalizeAndResolve :: Type -> THCompile Type
normalizeAndResolve Type
ty = Type -> Type
normalizeType (Type -> Type) -> THCompile Type -> THCompile Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ReaderT (Set Name) (ExceptT LiftError Q) Type -> THCompile Type
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Trans.lift (ReaderT (Set Name) (ExceptT LiftError Q) Type -> THCompile Type)
-> ReaderT (Set Name) (ExceptT LiftError Q) Type -> THCompile Type
forall a b. (a -> b) -> a -> b
$ ExceptT LiftError Q Type
-> ReaderT (Set Name) (ExceptT LiftError Q) Type
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Trans.lift (ExceptT LiftError Q Type
-> ReaderT (Set Name) (ExceptT LiftError Q) Type)
-> ExceptT LiftError Q Type
-> ReaderT (Set Name) (ExceptT LiftError Q) Type
forall a b. (a -> b) -> a -> b
$ Q Type -> ExceptT LiftError Q Type
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Trans.lift (Q Type -> ExceptT LiftError Q Type)
-> Q Type -> ExceptT LiftError Q Type
forall a b. (a -> b) -> a -> b
$ Type -> Q Type
TH.resolveTypeSynonyms Type
ty)
sortedCons :: TH.DatatypeInfo -> [TH.ConstructorInfo]
sortedCons :: DatatypeInfo -> [ConstructorInfo]
sortedCons TH.DatatypeInfo{datatypeName :: DatatypeInfo -> Name
TH.datatypeName=Name
tyName, datatypeCons :: DatatypeInfo -> [ConstructorInfo]
TH.datatypeCons=[ConstructorInfo]
cons} =
let sorted :: [ConstructorInfo]
sorted = (ConstructorInfo -> ConstructorInfo -> Ordering)
-> [ConstructorInfo] -> [ConstructorInfo]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (\(ConstructorInfo -> Name
TH.constructorName -> (TH.Name OccName
o1 NameFlavour
_)) (ConstructorInfo -> Name
TH.constructorName -> (TH.Name OccName
o2 NameFlavour
_)) -> OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare OccName
o1 OccName
o2) [ConstructorInfo]
cons
in if Name
tyName Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== ''Bool Bool -> Bool -> Bool
|| Name
tyName Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== ''[] then [ConstructorInfo] -> [ConstructorInfo]
forall a. [a] -> [a]
reverse [ConstructorInfo]
sorted else [ConstructorInfo]
sorted
#if MIN_VERSION_template_haskell(2,17,0)
tvNameAndKind :: TH.TyVarBndrUnit -> THCompile (TH.Name, Kind ())
tvNameAndKind = \case
TH.KindedTV name _ kind -> do
kind' <- (compileKind <=< normalizeAndResolve) kind
pure (name, kind')
TH.PlainTV name _ -> pure (name, Type ())
#else
tvNameAndKind :: TH.TyVarBndr -> THCompile (TH.Name, Kind ())
tvNameAndKind :: TyVarBndr -> THCompile (Name, Kind ())
tvNameAndKind = \case
TH.KindedTV Name
name Type
kind -> do
Kind ()
kind' <- (Type -> THCompile (Kind ())
compileKind (Type -> THCompile (Kind ()))
-> (Type -> THCompile Type) -> Type -> THCompile (Kind ())
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Type -> THCompile Type
normalizeAndResolve) Type
kind
(Name, Kind ()) -> THCompile (Name, Kind ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Name
name, Kind ()
kind')
TH.PlainTV Name
name -> (Name, Kind ()) -> THCompile (Name, Kind ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Name
name, () -> Kind ()
forall ann. ann -> Kind ann
Type ())
#endif
compileKind :: TH.Kind -> THCompile (Kind ())
compileKind :: Type -> THCompile (Kind ())
compileKind = \case
Type
TH.StarT -> Kind () -> THCompile (Kind ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Kind () -> THCompile (Kind ())) -> Kind () -> THCompile (Kind ())
forall a b. (a -> b) -> a -> b
$ () -> Kind ()
forall ann. ann -> Kind ann
Type ()
TH.AppT (TH.AppT Type
TH.ArrowT Type
k1) Type
k2 -> () -> Kind () -> Kind () -> Kind ()
forall ann. ann -> Kind ann -> Kind ann -> Kind ann
KindArrow () (Kind () -> Kind () -> Kind ())
-> THCompile (Kind ())
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(Kind () -> Kind ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Type -> THCompile (Kind ())
compileKind Type
k1 StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(Kind () -> Kind ())
-> THCompile (Kind ()) -> THCompile (Kind ())
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Type -> THCompile (Kind ())
compileKind Type
k2
Type
k -> LiftError -> THCompile (Kind ())
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (LiftError -> THCompile (Kind ()))
-> LiftError -> THCompile (Kind ())
forall a b. (a -> b) -> a -> b
$ Type -> LiftError
UnsupportedLiftKind Type
k
compileType :: TH.Type -> THCompile (TH.TExpQ CompileTypeScope)
compileType :: Type -> THCompile (TExpQ CompileTypeScope)
compileType = \case
TH.AppT Type
t1 Type
t2 -> do
TExpQ CompileTypeScope
t1' <- Type -> THCompile (TExpQ CompileTypeScope)
compileType Type
t1
TExpQ CompileTypeScope
t2' <- Type -> THCompile (TExpQ CompileTypeScope)
compileType Type
t2
TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope))
-> (TExpQ CompileTypeScope -> TExpQ CompileTypeScope)
-> TExpQ CompileTypeScope
-> THCompile (TExpQ CompileTypeScope)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TExpQ CompileTypeScope -> TExpQ CompileTypeScope
forall (m :: * -> *) a. Splice m a -> Splice m a
TH.examineSplice (TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope))
-> TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope)
forall a b. (a -> b) -> a -> b
$ [|| CompileTypeScope (TyApp () <$> unCompileTypeScope ($$(TH.liftSplice t1')) <*> unCompileTypeScope ($$(TH.liftSplice t2'))) ||]
t :: Type
t@(TH.ConT Name
name) -> Type -> Name -> THCompile (TExpQ CompileTypeScope)
compileTypeableType Type
t Name
name
t :: Type
t@(TH.VarT Name
name) -> do
Bool
isLocal <- (Set Name -> Bool)
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (Name -> Set Name -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Name
name)
if Bool
isLocal
then TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope))
-> (TExpQ CompileTypeScope -> TExpQ CompileTypeScope)
-> TExpQ CompileTypeScope
-> THCompile (TExpQ CompileTypeScope)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TExpQ CompileTypeScope -> TExpQ CompileTypeScope
forall (m :: * -> *) a. Splice m a -> Splice m a
TH.examineSplice (TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope))
-> TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope)
forall a b. (a -> b) -> a -> b
$ [||
CompileTypeScope $ do
vars <- ask
case Map.lookup name vars of
Just ty -> pure ty
Nothing -> Prelude.throw $ LiftMissingVar name
||]
else Type -> Name -> THCompile (TExpQ CompileTypeScope)
compileTypeableType Type
t Name
name
Type
t -> LiftError -> THCompile (TExpQ CompileTypeScope)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (LiftError -> THCompile (TExpQ CompileTypeScope))
-> LiftError -> THCompile (TExpQ CompileTypeScope)
forall a b. (a -> b) -> a -> b
$ Type -> LiftError
UnsupportedLiftType Type
t
compileTypeableType :: TH.Type -> TH.Name -> THCompile (TH.TExpQ CompileTypeScope)
compileTypeableType :: Type -> Name -> THCompile (TExpQ CompileTypeScope)
compileTypeableType Type
ty Name
name = do
Type -> THCompile ()
addTypeableDep Type
ty
let trep :: TH.TExpQ CompileType
trep :: TExpQ CompileType
trep = Q Exp -> TExpQ CompileType
forall a. Q Exp -> Q (TExp a)
TH.unsafeTExpCoerce [| CompileType (typeRep (Proxy :: Proxy $(pure ty))) |]
TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope))
-> (TExpQ CompileTypeScope -> TExpQ CompileTypeScope)
-> TExpQ CompileTypeScope
-> THCompile (TExpQ CompileTypeScope)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TExpQ CompileTypeScope -> TExpQ CompileTypeScope
forall (m :: * -> *) a. Splice m a -> Splice m a
TH.examineSplice (TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope))
-> TExpQ CompileTypeScope -> THCompile (TExpQ CompileTypeScope)
forall a b. (a -> b) -> a -> b
$ [||
let trep' :: forall fun . RTCompileScope PLC.DefaultUni fun (Type TyName PLC.DefaultUni ())
trep' = Trans.lift $ unCompileType ($$(TH.liftSplice trep))
in CompileTypeScope $ do
maybeType <- lookupType () name
case maybeType of
Just t -> pure t
Nothing -> trep'
||]
class Typeable uni (a :: k) where
typeRep :: Proxy a -> RTCompile uni fun (Type TyName uni ())
recordAlias' :: TH.Name -> RTCompileScope PLC.DefaultUni fun ()
recordAlias' :: Name -> RTCompileScope DefaultUni fun ()
recordAlias' = Name -> RTCompileScope DefaultUni fun ()
forall key (uni :: * -> *) fun ann (m :: * -> *).
MonadDefs key uni fun ann m =>
key -> m ()
recordAlias
defineDatatype' :: TH.Name -> DatatypeDef TyName Name PLC.DefaultUni fun () -> Set.Set TH.Name -> RTCompileScope PLC.DefaultUni fun ()
defineDatatype' :: Name
-> DatatypeDef TyName Name DefaultUni fun ()
-> Set Name
-> RTCompileScope DefaultUni fun ()
defineDatatype' = Name
-> DatatypeDef TyName Name DefaultUni fun ()
-> Set Name
-> RTCompileScope DefaultUni fun ()
forall key (uni :: * -> *) fun ann (m :: * -> *).
MonadDefs key uni fun ann m =>
key -> DatatypeDef TyName Name uni fun ann -> Set key -> m ()
defineDatatype
compileTypeRep :: TH.DatatypeInfo -> THCompile (TH.TExpQ CompileType)
compileTypeRep :: DatatypeInfo -> THCompile (TExpQ CompileType)
compileTypeRep dt :: DatatypeInfo
dt@TH.DatatypeInfo{datatypeName :: DatatypeInfo -> Name
TH.datatypeName=Name
tyName, datatypeVars :: DatatypeInfo -> [TyVarBndr]
TH.datatypeVars=[TyVarBndr]
tvs} = do
[(Name, Kind ())]
tvNamesAndKinds <- (TyVarBndr -> THCompile (Name, Kind ()))
-> [TyVarBndr]
-> StateT
Deps (ReaderT (Set Name) (ExceptT LiftError Q)) [(Name, Kind ())]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse TyVarBndr -> THCompile (Name, Kind ())
tvNameAndKind [TyVarBndr]
tvs
let typeKind :: Kind ()
typeKind = ((Name, Kind ()) -> Kind () -> Kind ())
-> Kind () -> [(Name, Kind ())] -> Kind ()
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\(Name
_, Kind ()
k) Kind ()
acc -> () -> Kind () -> Kind () -> Kind ()
forall ann. ann -> Kind ann -> Kind ann -> Kind ann
KindArrow () Kind ()
k Kind ()
acc) (() -> Kind ()
forall ann. ann -> Kind ann
Type ()) [(Name, Kind ())]
tvNamesAndKinds
let cons :: [ConstructorInfo]
cons = DatatypeInfo -> [ConstructorInfo]
sortedCons DatatypeInfo
dt
[Name]
-> THCompile (TExpQ CompileType) -> THCompile (TExpQ CompileType)
forall (m :: * -> *) a.
MonadReader (Set Name) m =>
[Name] -> m a -> m a
thWithTyVars (((Name, Kind ()) -> Name) -> [(Name, Kind ())] -> [Name]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Name, Kind ()) -> Name
forall a b. (a, b) -> a
fst [(Name, Kind ())]
tvNamesAndKinds) (THCompile (TExpQ CompileType) -> THCompile (TExpQ CompileType))
-> THCompile (TExpQ CompileType) -> THCompile (TExpQ CompileType)
forall a b. (a -> b) -> a -> b
$ if DatatypeInfo -> Bool
isNewtype DatatypeInfo
dt
then do
TExpQ CompileTypeScope
argTy <- case [ConstructorInfo]
cons of
[ TH.ConstructorInfo {constructorFields :: ConstructorInfo -> [Type]
TH.constructorFields=[Type
argTy]} ] -> (Type -> THCompile (TExpQ CompileTypeScope)
compileType (Type -> THCompile (TExpQ CompileTypeScope))
-> (Type -> THCompile Type)
-> Type
-> THCompile (TExpQ CompileTypeScope)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Type -> THCompile Type
normalizeAndResolve) Type
argTy
[ConstructorInfo]
_ -> LiftError -> THCompile (TExpQ CompileTypeScope)
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (LiftError -> THCompile (TExpQ CompileTypeScope))
-> LiftError -> THCompile (TExpQ CompileTypeScope)
forall a b. (a -> b) -> a -> b
$ Text -> LiftError
UserLiftError Text
"Newtypes must have a single constructor with a single argument"
Set Name
deps <- (Deps -> Set Name)
-> StateT
Deps (ReaderT (Set Name) (ExceptT LiftError Q)) (Set Name)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets Deps -> Set Name
getTyConDeps
TExpQ CompileType -> THCompile (TExpQ CompileType)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TExpQ CompileType -> THCompile (TExpQ CompileType))
-> (TExpQ CompileType -> TExpQ CompileType)
-> TExpQ CompileType
-> THCompile (TExpQ CompileType)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TExpQ CompileType -> TExpQ CompileType
forall (m :: * -> *) a. Splice m a -> Splice m a
TH.examineSplice (TExpQ CompileType -> THCompile (TExpQ CompileType))
-> TExpQ CompileType -> THCompile (TExpQ CompileType)
forall a b. (a -> b) -> a -> b
$ [||
let
argTy' :: forall fun . RTCompileScope PLC.DefaultUni fun (Type TyName PLC.DefaultUni ())
argTy' = unCompileTypeScope $$(TH.liftSplice argTy)
act :: forall fun . RTCompileScope PLC.DefaultUni fun (Type TyName PLC.DefaultUni ())
act = do
maybeDefined <- lookupType () tyName
case maybeDefined of
Just ty -> pure ty
Nothing -> do
(_, dtvd) <- mkTyVarDecl tyName typeKind
tvds <- traverse (uncurry mkTyVarDecl) tvNamesAndKinds
alias <- withTyVars tvds $ mkIterTyLam (fmap snd tvds) <$> argTy'
defineType tyName (PLC.Def dtvd alias) deps
recordAlias' tyName
pure alias
in CompileType $ runReaderT act mempty
||]
else do
[TExpQ CompileDeclFun]
constrExprs <- (ConstructorInfo
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ CompileDeclFun))
-> [ConstructorInfo]
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
[TExpQ CompileDeclFun]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ConstructorInfo
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ CompileDeclFun)
compileConstructorDecl [ConstructorInfo]
cons
Set Name
deps <- (Deps -> Set Name)
-> StateT
Deps (ReaderT (Set Name) (ExceptT LiftError Q)) (Set Name)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets Deps -> Set Name
getTyConDeps
TExpQ CompileType -> THCompile (TExpQ CompileType)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TExpQ CompileType -> THCompile (TExpQ CompileType))
-> (TExpQ CompileType -> TExpQ CompileType)
-> TExpQ CompileType
-> THCompile (TExpQ CompileType)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TExpQ CompileType -> TExpQ CompileType
forall (m :: * -> *) a. Splice m a -> Splice m a
TH.examineSplice (TExpQ CompileType -> THCompile (TExpQ CompileType))
-> TExpQ CompileType -> THCompile (TExpQ CompileType)
forall a b. (a -> b) -> a -> b
$ [||
let
constrExprs' :: [CompileDeclFun]
constrExprs' = $$(TH.liftSplice $ tyListE constrExprs)
act :: forall fun . RTCompileScope PLC.DefaultUni fun (Type TyName PLC.DefaultUni ())
act = do
maybeDefined <- lookupType () tyName
case maybeDefined of
Just ty -> pure ty
Nothing -> do
(_, dtvd) <- mkTyVarDecl tyName typeKind
tvds <- traverse (uncurry mkTyVarDecl) tvNamesAndKinds
let resultType = mkIterTyApp () (mkTyVar () dtvd) (fmap (mkTyVar () . snd) tvds)
matchName <- safeFreshName (T.pack "match_" <> showName tyName)
let fakeDatatype = Datatype () dtvd [] matchName []
defineDatatype' tyName (PLC.Def dtvd fakeDatatype) Set.empty
withTyVars tvds $ do
let constrActs :: RTCompileScope PLC.DefaultUni fun [VarDecl TyName Name PLC.DefaultUni fun ()]
constrActs = sequence $ fmap (\x -> unCompileDeclFun x) constrExprs' <*> [resultType]
constrs <- constrActs
let datatype = Datatype () dtvd (fmap snd tvds) matchName constrs
defineDatatype tyName (PLC.Def dtvd datatype) deps
pure $ mkTyVar () dtvd
in CompileType $ runReaderT act mempty
||]
compileConstructorDecl
:: TH.ConstructorInfo
-> THCompile (TH.TExpQ CompileDeclFun)
compileConstructorDecl :: ConstructorInfo
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ CompileDeclFun)
compileConstructorDecl TH.ConstructorInfo{constructorName :: ConstructorInfo -> Name
TH.constructorName=Name
name, constructorFields :: ConstructorInfo -> [Type]
TH.constructorFields=[Type]
argTys} = do
[TExpQ CompileTypeScope]
tyExprs <- (Type -> THCompile (TExpQ CompileTypeScope))
-> [Type]
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
[TExpQ CompileTypeScope]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Type -> THCompile (TExpQ CompileTypeScope)
compileType (Type -> THCompile (TExpQ CompileTypeScope))
-> (Type -> THCompile Type)
-> Type
-> THCompile (TExpQ CompileTypeScope)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Type -> THCompile Type
normalizeAndResolve) [Type]
argTys
TExpQ CompileDeclFun
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ CompileDeclFun)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TExpQ CompileDeclFun
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ CompileDeclFun))
-> (TExpQ CompileDeclFun -> TExpQ CompileDeclFun)
-> TExpQ CompileDeclFun
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ CompileDeclFun)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TExpQ CompileDeclFun -> TExpQ CompileDeclFun
forall (m :: * -> *) a. Splice m a -> Splice m a
TH.examineSplice (TExpQ CompileDeclFun
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ CompileDeclFun))
-> TExpQ CompileDeclFun
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ CompileDeclFun)
forall a b. (a -> b) -> a -> b
$ [||
let
tyExprs' :: forall fun . [RTCompileScope PLC.DefaultUni fun (Type TyName PLC.DefaultUni ())]
tyExprs' = fmap (\x -> unCompileTypeScope x) $$(TH.liftSplice $ tyListE tyExprs)
in CompileDeclFun $ \resultType -> do
tys' <- sequence tyExprs'
let constrTy = mkIterTyFun () tys' resultType
constrName <- safeFreshName $ showName name
pure $ VarDecl () constrName constrTy
||]
makeTypeable :: TH.Type -> TH.Name -> TH.Q [TH.Dec]
makeTypeable :: Type -> Name -> Q [Dec]
makeTypeable Type
uni Name
name = do
Extension -> Q ()
requireExtension Extension
TH.ScopedTypeVariables
DatatypeInfo
info <- Name -> Q DatatypeInfo
TH.reifyDatatype Name
name
(TExpQ CompileType
rhs, Deps
deps) <- THCompile (TExpQ CompileType) -> Q (TExpQ CompileType, Deps)
forall a. THCompile a -> Q (a, Deps)
runTHCompile (THCompile (TExpQ CompileType) -> Q (TExpQ CompileType, Deps))
-> THCompile (TExpQ CompileType) -> Q (TExpQ CompileType, Deps)
forall a b. (a -> b) -> a -> b
$ DatatypeInfo -> THCompile (TExpQ CompileType)
compileTypeRep DatatypeInfo
info
let constraints :: [Type]
constraints = (Type -> Bool) -> [Type] -> [Type]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Type -> Bool) -> Type -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Bool
isClosedConstraint) ([Type] -> [Type]) -> [Type] -> [Type]
forall a b. (a -> b) -> a -> b
$ Type -> Dep -> Type
toConstraint Type
uni (Dep -> Type) -> [Dep] -> [Type]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Deps -> [Dep]
forall a. Set a -> [a]
Set.toList Deps
deps
let unwrappedRhs :: Q Exp
unwrappedRhs = [| unCompileType |] Q Exp -> Q Exp -> Q Exp
`TH.appE` TExpQ CompileType -> Q Exp
forall a. Q (TExp a) -> Q Exp
TH.unTypeQ TExpQ CompileType
rhs
Dec
decl <- Name -> [ClauseQ] -> DecQ
TH.funD 'typeRep [[PatQ] -> BodyQ -> [DecQ] -> ClauseQ
TH.clause [PatQ
TH.wildP] (Q Exp -> BodyQ
TH.normalB Q Exp
unwrappedRhs) []]
[Dec] -> Q [Dec]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Maybe Overlap -> [Type] -> Type -> [Dec] -> Dec
TH.InstanceD Maybe Overlap
forall a. Maybe a
Nothing [Type]
constraints (Type -> Type -> Type
typeablePir Type
uni (Name -> Type
TH.ConT Name
name)) [Dec
decl]]
class Lift uni a where
lift :: a -> RTCompile uni fun (Term TyName Name uni fun ())
compileLift :: TH.DatatypeInfo -> THCompile [TH.Q TH.Clause]
compileLift :: DatatypeInfo -> THCompile [ClauseQ]
compileLift DatatypeInfo
dt = ((Int, ConstructorInfo)
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) ClauseQ)
-> [(Int, ConstructorInfo)] -> THCompile [ClauseQ]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Int
-> ConstructorInfo
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) ClauseQ)
-> (Int, ConstructorInfo)
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) ClauseQ
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (DatatypeInfo
-> Int
-> ConstructorInfo
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) ClauseQ
compileConstructorClause DatatypeInfo
dt)) ([Int] -> [ConstructorInfo] -> [(Int, ConstructorInfo)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] (DatatypeInfo -> [ConstructorInfo]
sortedCons DatatypeInfo
dt))
compileConstructorClause
:: TH.DatatypeInfo -> Int -> TH.ConstructorInfo -> THCompile (TH.Q TH.Clause)
compileConstructorClause :: DatatypeInfo
-> Int
-> ConstructorInfo
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) ClauseQ
compileConstructorClause dt :: DatatypeInfo
dt@TH.DatatypeInfo{datatypeName :: DatatypeInfo -> Name
TH.datatypeName=Name
tyName, datatypeVars :: DatatypeInfo -> [TyVarBndr]
TH.datatypeVars=[TyVarBndr]
tvs} Int
index TH.ConstructorInfo{constructorName :: ConstructorInfo -> Name
TH.constructorName=Name
name, constructorFields :: ConstructorInfo -> [Type]
TH.constructorFields=[Type]
argTys} = do
(Type -> THCompile ()) -> [Type] -> THCompile ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ Type -> THCompile ()
addLiftDep [Type]
argTys
[TExpQ CompileTypeScope]
tyExprs <- if DatatypeInfo -> Bool
isNewtype DatatypeInfo
dt then [TExpQ CompileTypeScope]
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
[TExpQ CompileTypeScope]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [] else [TyVarBndr]
-> (TyVarBndr -> THCompile (TExpQ CompileTypeScope))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
[TExpQ CompileTypeScope]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [TyVarBndr]
tvs ((TyVarBndr -> THCompile (TExpQ CompileTypeScope))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
[TExpQ CompileTypeScope])
-> (TyVarBndr -> THCompile (TExpQ CompileTypeScope))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
[TExpQ CompileTypeScope]
forall a b. (a -> b) -> a -> b
$ \TyVarBndr
tv -> do
(Name
n, Kind ()
_) <- TyVarBndr -> THCompile (Name, Kind ())
tvNameAndKind TyVarBndr
tv
Type -> THCompile (TExpQ CompileTypeScope)
compileType (Name -> Type
TH.VarT Name
n)
[Name]
patNames <- ReaderT (Set Name) (ExceptT LiftError Q) [Name]
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) [Name]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Trans.lift (ReaderT (Set Name) (ExceptT LiftError Q) [Name]
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) [Name])
-> ReaderT (Set Name) (ExceptT LiftError Q) [Name]
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) [Name]
forall a b. (a -> b) -> a -> b
$ ExceptT LiftError Q [Name]
-> ReaderT (Set Name) (ExceptT LiftError Q) [Name]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Trans.lift (ExceptT LiftError Q [Name]
-> ReaderT (Set Name) (ExceptT LiftError Q) [Name])
-> ExceptT LiftError Q [Name]
-> ReaderT (Set Name) (ExceptT LiftError Q) [Name]
forall a b. (a -> b) -> a -> b
$ Q [Name] -> ExceptT LiftError Q [Name]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Trans.lift (Q [Name] -> ExceptT LiftError Q [Name])
-> Q [Name] -> ExceptT LiftError Q [Name]
forall a b. (a -> b) -> a -> b
$ [Type] -> (Type -> Q Name) -> Q [Name]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [Type]
argTys ((Type -> Q Name) -> Q [Name]) -> (Type -> Q Name) -> Q [Name]
forall a b. (a -> b) -> a -> b
$ \Type
_ -> String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
TH.newName String
"arg"
let pat :: PatQ
pat = Name -> [PatQ] -> PatQ
TH.conP Name
name ((Name -> PatQ) -> [Name] -> [PatQ]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Name -> PatQ
TH.varP [Name]
patNames)
let liftExprs :: [TH.TExpQ (RTCompile PLC.DefaultUni fun (Term TyName Name PLC.DefaultUni fun ()))]
liftExprs :: [TExpQ
(RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ()))]
liftExprs = (Name
-> TExpQ
(RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())))
-> [Name]
-> [TExpQ
(RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ()))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Name
pn -> Q Exp
-> TExpQ
(RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ()))
forall a. Q Exp -> Q (TExp a)
TH.unsafeTExpCoerce (Q Exp
-> TExpQ
(RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ())))
-> Q Exp
-> TExpQ
(RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ()))
forall a b. (a -> b) -> a -> b
$ Name -> Q Exp
TH.varE 'lift Q Exp -> Q Exp -> Q Exp
`TH.appE` Name -> Q Exp
TH.varE Name
pn) [Name]
patNames
TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
rhsExpr <- if DatatypeInfo -> Bool
isNewtype DatatypeInfo
dt
then case [TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))]
forall fun.
[TExpQ
(RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ()))]
liftExprs of
[TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
argExpr] -> TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ())))
forall (f :: * -> *) a. Applicative f => a -> f a
pure TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
argExpr
[TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))]
_ -> LiftError
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ())))
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (LiftError
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))))
-> LiftError
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ())))
forall a b. (a -> b) -> a -> b
$ Text -> LiftError
UserLiftError Text
"Newtypes must have a single constructor with a single argument"
else
TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ())))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))))
-> (TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ())))
-> TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ())))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
forall (m :: * -> *) a. Splice m a -> Splice m a
TH.examineSplice (TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))))
-> TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> StateT
Deps
(ReaderT (Set Name) (ExceptT LiftError Q))
(TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ())))
forall a b. (a -> b) -> a -> b
$ [||
let
liftExprs' :: forall fun . [RTCompile PLC.DefaultUni fun (Term TyName Name PLC.DefaultUni fun ())]
liftExprs' = $$(TH.liftSplice $ tyListE liftExprs)
trep :: forall fun . RTCompile PLC.DefaultUni fun (Type TyName PLC.DefaultUni ())
trep = $$(TH.unsafeSpliceCoerce [| typeRep (Proxy :: Proxy $(TH.conT tyName)) |])
in do
_ <- trep
maybeConstructors <- lookupConstructors () tyName
constrs <- case maybeConstructors of
Nothing -> Prelude.throw $ LiftMissingDataCons tyName
Just cs -> pure cs
let constr = constrs !! index
lifts :: [Term TyName Name PLC.DefaultUni fun ()] <- sequence liftExprs'
let tyExprs' :: [RTCompileScope PLC.DefaultUni fun (Type TyName PLC.DefaultUni ())]
tyExprs' = fmap (\x -> unCompileTypeScope x) $$(TH.liftSplice $ tyListE tyExprs)
types <- flip runReaderT mempty $ sequence tyExprs'
pure $ mkIterApp () (mkIterInst () constr types) lifts
||]
ClauseQ
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) ClauseQ
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ClauseQ
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) ClauseQ)
-> ClauseQ
-> StateT Deps (ReaderT (Set Name) (ExceptT LiftError Q)) ClauseQ
forall a b. (a -> b) -> a -> b
$ [PatQ] -> BodyQ -> [DecQ] -> ClauseQ
TH.clause [PatQ
pat] (Q Exp -> BodyQ
TH.normalB (Q Exp -> BodyQ) -> Q Exp -> BodyQ
forall a b. (a -> b) -> a -> b
$ TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
-> Q Exp
forall a. Q (TExp a) -> Q Exp
TH.unTypeQ TExpQ
(RTCompile DefaultUni Any (Term TyName Name DefaultUni Any ()))
rhsExpr) []
makeLift :: TH.Name -> TH.Q [TH.Dec]
makeLift :: Name -> Q [Dec]
makeLift Name
name = do
Extension -> Q ()
requireExtension Extension
TH.ScopedTypeVariables
let uni :: Type
uni = Name -> Type
TH.ConT ''PLC.DefaultUni
[Dec]
typeableDecs <- Type -> Name -> Q [Dec]
makeTypeable Type
uni Name
name
DatatypeInfo
info <- Name -> Q DatatypeInfo
TH.reifyDatatype Name
name
let datatypeType :: Type
datatypeType = DatatypeInfo -> Type
TH.datatypeType DatatypeInfo
info
([ClauseQ]
clauses, Deps
deps) <- THCompile [ClauseQ] -> Q ([ClauseQ], Deps)
forall a. THCompile a -> Q (a, Deps)
runTHCompile (THCompile [ClauseQ] -> Q ([ClauseQ], Deps))
-> THCompile [ClauseQ] -> Q ([ClauseQ], Deps)
forall a b. (a -> b) -> a -> b
$ DatatypeInfo -> THCompile [ClauseQ]
compileLift DatatypeInfo
info
let prunedDeps :: Deps
prunedDeps = Dep -> Deps -> Deps
forall a. Ord a => a -> Set a -> Set a
Set.delete (Type -> Dep
LiftDep Type
datatypeType) Deps
deps
let constraints :: [Type]
constraints = (Type -> Bool) -> [Type] -> [Type]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Type -> Bool) -> Type -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Bool
isClosedConstraint) ([Type] -> [Type]) -> [Type] -> [Type]
forall a b. (a -> b) -> a -> b
$ Type -> Dep -> Type
toConstraint Type
uni (Dep -> Type) -> [Dep] -> [Type]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Deps -> [Dep]
forall a. Set a -> [a]
Set.toList Deps
prunedDeps
Dec
decl <- Name -> [ClauseQ] -> DecQ
TH.funD 'lift [ClauseQ]
clauses
let liftDecs :: [Dec]
liftDecs = [Maybe Overlap -> [Type] -> Type -> [Dec] -> Dec
TH.InstanceD Maybe Overlap
forall a. Maybe a
Nothing [Type]
constraints (Type -> Type -> Type
liftPir Type
uni Type
datatypeType) [Dec
decl]]
[Dec] -> Q [Dec]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Dec] -> Q [Dec]) -> [Dec] -> Q [Dec]
forall a b. (a -> b) -> a -> b
$ [Dec]
typeableDecs [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++ [Dec]
liftDecs
runTHCompile :: THCompile a -> TH.Q (a, Deps)
runTHCompile :: THCompile a -> Q (a, Deps)
runTHCompile THCompile a
m = do
Either LiftError (a, Deps)
res <- ExceptT LiftError Q (a, Deps) -> Q (Either LiftError (a, Deps))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT LiftError Q (a, Deps) -> Q (Either LiftError (a, Deps)))
-> (ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
-> ExceptT LiftError Q (a, Deps))
-> ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
-> Q (Either LiftError (a, Deps))
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
-> Set Name -> ExceptT LiftError Q (a, Deps))
-> Set Name
-> ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
-> ExceptT LiftError Q (a, Deps)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
-> Set Name -> ExceptT LiftError Q (a, Deps)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT Set Name
forall a. Monoid a => a
mempty (ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
-> Q (Either LiftError (a, Deps)))
-> ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
-> Q (Either LiftError (a, Deps))
forall a b. (a -> b) -> a -> b
$
(THCompile a
-> Deps -> ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps))
-> Deps
-> THCompile a
-> ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
forall a b c. (a -> b -> c) -> b -> a -> c
flip THCompile a
-> Deps -> ReaderT (Set Name) (ExceptT LiftError Q) (a, Deps)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT Deps
forall a. Monoid a => a
mempty THCompile a
m
case Either LiftError (a, Deps)
res of
Left LiftError
a -> String -> Q (a, Deps)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q (a, Deps)) -> String -> Q (a, Deps)
forall a b. (a -> b) -> a -> b
$ String
"Generating Lift instances: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Doc Any -> String
forall a. Show a => a -> String
show (LiftError -> Doc Any
forall a ann. Pretty a => a -> Doc ann
PP.pretty LiftError
a)
Right (a, Deps)
b -> (a, Deps) -> Q (a, Deps)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a, Deps)
b