{-# LANGUAGE TemplateHaskellQuotes #-}
module Generics.Linear.TH.MetaData (
mkMetaDataType
, mkMetaConsType
, mkMetaSelType
, SelStrictInfo(..)
, reifySelStrictInfo
) where
import Data.Maybe (fromMaybe)
import Generics.Linear.TH.Internal
import Language.Haskell.TH.Datatype as THAbs
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Syntax
import qualified Generics.Linear.Class as G
mkMetaDataType :: DatatypeVariant_ -> Name -> Q Type
mkMetaDataType :: DatatypeVariant_ -> Name -> Q Type
mkMetaDataType DatatypeVariant_
dv Name
n =
forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.MetaData
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` forall (m :: * -> *). Quote m => m TyLit -> m Type
litT (forall (m :: * -> *). Quote m => String -> m TyLit
strTyLit (Name -> String
nameBase Name
n))
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` forall (m :: * -> *). Quote m => m TyLit -> m Type
litT (forall (m :: * -> *). Quote m => String -> m TyLit
strTyLit String
m)
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` forall (m :: * -> *). Quote m => m TyLit -> m Type
litT (forall (m :: * -> *). Quote m => String -> m TyLit
strTyLit String
pkg)
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Bool -> Q Type
promoteBool (DatatypeVariant_ -> Bool
isNewtypeVariant DatatypeVariant_
dv)
where
m, pkg :: String
m :: String
m = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"Cannot fetch module name!") (Name -> Maybe String
nameModule Name
n)
pkg :: String
pkg = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"Cannot fetch package name!") (Name -> Maybe String
namePackage Name
n)
mkMetaConsType :: DatatypeVariant_ -> Name -> Name -> Bool -> Bool -> Q Type
mkMetaConsType :: DatatypeVariant_ -> Name -> Name -> Bool -> Bool -> Q Type
mkMetaConsType DatatypeVariant_
_ Name
_ Name
n Bool
conIsRecord Bool
conIsInfix = do
Maybe Fixity
mbFi <- Name -> Q (Maybe Fixity)
reifyFixity Name
n
forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.MetaCons
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` forall (m :: * -> *). Quote m => m TyLit -> m Type
litT (forall (m :: * -> *). Quote m => String -> m TyLit
strTyLit (Name -> String
nameBase Name
n))
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Maybe Fixity -> Bool -> Q Type
fixityIPromotedType Maybe Fixity
mbFi Bool
conIsInfix
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Bool -> Q Type
promoteBool Bool
conIsRecord
promoteBool :: Bool -> Q Type
promoteBool :: Bool -> Q Type
promoteBool Bool
True = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'True
promoteBool Bool
False = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'False
fixityIPromotedType :: Maybe Fixity -> Bool -> Q Type
fixityIPromotedType :: Maybe Fixity -> Bool -> Q Type
fixityIPromotedType Maybe Fixity
mbFi Bool
True =
forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.InfixI
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` FixityDirection -> Q Type
promoteAssociativity FixityDirection
a
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` forall (m :: * -> *). Quote m => m TyLit -> m Type
litT (forall (m :: * -> *). Quote m => Integer -> m TyLit
numTyLit (forall a. Integral a => a -> Integer
toInteger Int
n))
where
Fixity Int
n FixityDirection
a = forall a. a -> Maybe a -> a
fromMaybe Fixity
defaultFixity Maybe Fixity
mbFi
fixityIPromotedType Maybe Fixity
_ Bool
False = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.PrefixI
promoteAssociativity :: FixityDirection -> Q Type
promoteAssociativity :: FixityDirection -> Q Type
promoteAssociativity FixityDirection
InfixL = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.LeftAssociative
promoteAssociativity FixityDirection
InfixR = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.RightAssociative
promoteAssociativity FixityDirection
InfixN = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.NotAssociative
mkMetaSelType :: DatatypeVariant_ -> Name -> Name -> Maybe Name
-> SelStrictInfo -> Q Type
mkMetaSelType :: DatatypeVariant_
-> Name -> Name -> Maybe Name -> SelStrictInfo -> Q Type
mkMetaSelType DatatypeVariant_
_ Name
_ Name
_ Maybe Name
mbF (SelStrictInfo Unpackedness
su Strictness
ss DecidedStrictness
ds) =
let mbSelNameT :: Q Type
mbSelNameT = case Maybe Name
mbF of
Just Name
f -> forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'Just forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` forall (m :: * -> *). Quote m => m TyLit -> m Type
litT (forall (m :: * -> *). Quote m => String -> m TyLit
strTyLit (Name -> String
nameBase Name
f))
Maybe Name
Nothing -> forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'Nothing
in forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.MetaSel
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Q Type
mbSelNameT
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Unpackedness -> Q Type
promoteUnpackedness Unpackedness
su
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Strictness -> Q Type
promoteStrictness Strictness
ss
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` DecidedStrictness -> Q Type
promoteDecidedStrictness DecidedStrictness
ds
data SelStrictInfo = SelStrictInfo Unpackedness Strictness DecidedStrictness
promoteUnpackedness :: Unpackedness -> Q Type
promoteUnpackedness :: Unpackedness -> Q Type
promoteUnpackedness Unpackedness
UnspecifiedUnpackedness = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.NoSourceUnpackedness
promoteUnpackedness Unpackedness
NoUnpack = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.SourceNoUnpack
promoteUnpackedness Unpackedness
Unpack = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.SourceUnpack
promoteStrictness :: Strictness -> Q Type
promoteStrictness :: Strictness -> Q Type
promoteStrictness Strictness
UnspecifiedStrictness = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.NoSourceStrictness
promoteStrictness Strictness
Lazy = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.SourceLazy
promoteStrictness Strictness
THAbs.Strict = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.SourceStrict
promoteDecidedStrictness :: DecidedStrictness -> Q Type
promoteDecidedStrictness :: DecidedStrictness -> Q Type
promoteDecidedStrictness DecidedStrictness
DecidedLazy = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.DecidedLazy
promoteDecidedStrictness DecidedStrictness
DecidedStrict = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.DecidedStrict
promoteDecidedStrictness DecidedStrictness
DecidedUnpack = forall (m :: * -> *). Quote m => Name -> m Type
promotedT 'G.DecidedUnpack
reifySelStrictInfo :: Name -> [FieldStrictness] -> Q [SelStrictInfo]
reifySelStrictInfo :: Name -> [FieldStrictness] -> Q [SelStrictInfo]
reifySelStrictInfo Name
conName [FieldStrictness]
fs = do
[DecidedStrictness]
dcdStrs <- Name -> Q [DecidedStrictness]
reifyConStrictness Name
conName
let srcUnpks :: [Unpackedness]
srcUnpks = forall a b. (a -> b) -> [a] -> [b]
map FieldStrictness -> Unpackedness
fieldUnpackedness [FieldStrictness]
fs
srcStrs :: [Strictness]
srcStrs = forall a b. (a -> b) -> [a] -> [b]
map FieldStrictness -> Strictness
fieldStrictness [FieldStrictness]
fs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 Unpackedness -> Strictness -> DecidedStrictness -> SelStrictInfo
SelStrictInfo [Unpackedness]
srcUnpks [Strictness]
srcStrs [DecidedStrictness]
dcdStrs