{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TemplateHaskell #-}
module TextShow.TH.Internal (
deriveTextShow
, deriveTextShow1
, deriveTextShow2
, makeShowt
, makeShowtl
, makeShowtPrec
, makeShowtlPrec
, makeShowtList
, makeShowtlList
, makeShowb
, makeShowbPrec
, makeShowbList
, makePrintT
, makePrintTL
, makeHPrintT
, makeHPrintTL
, makeLiftShowbPrec
, makeShowbPrec1
, makeLiftShowbPrec2
, makeShowbPrec2
, Options(..)
, defaultOptions
, GenTextMethods(..)
, deriveTextShowOptions
, deriveTextShow1Options
, deriveTextShow2Options
) where
import Control.Monad (unless, when)
import Data.Foldable.Compat
import Data.List.Compat
import qualified Data.List.NonEmpty.Compat as NE (reverse)
import Data.List.NonEmpty.Compat (NonEmpty(..), (<|))
import qualified Data.Map as Map (fromList, keys, lookup, singleton)
import Data.Map (Map)
import Data.Maybe
import qualified Data.Set as Set
import Data.Set (Set)
import qualified Data.Text as TS
import qualified Data.Text.IO as TS (putStrLn, hPutStrLn)
import Data.Text.Lazy (toStrict)
import qualified Data.Text.Lazy.Builder as TB
import Data.Text.Lazy.Builder (Builder, toLazyText)
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.IO as TL (putStrLn, hPutStrLn)
import GHC.Exts ( Char(..), Double(..), Float(..), Int(..), Word(..)
, Char#, Double#, Float#, Int#, Word#
#if MIN_VERSION_base(4,13,0)
, Int8#, Int16#, Word8#, Word16#
, extendInt8#, extendInt16#, extendWord8#, extendWord16#
#endif
)
import GHC.Show (appPrec, appPrec1)
import Language.Haskell.TH.Datatype
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Ppr hiding (appPrec)
import Language.Haskell.TH.Syntax
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..), TextShow1(..), TextShow2(..),
showbListWith,
showbParen, showbCommaSpace, showbSpace,
showtParen, showtCommaSpace, showtSpace,
showtlParen, showtlCommaSpace, showtlSpace)
import TextShow.Options (Options(..), GenTextMethods(..), defaultOptions)
import TextShow.Utils (isInfixDataCon, isSymVar, isTupleString)
deriveTextShow :: Name -> Q [Dec]
deriveTextShow = deriveTextShowOptions defaultOptions
deriveTextShowOptions :: Options -> Name -> Q [Dec]
deriveTextShowOptions = deriveTextShowClass TextShow
deriveTextShow1 :: Name -> Q [Dec]
deriveTextShow1 = deriveTextShow1Options defaultOptions
deriveTextShow1Options :: Options -> Name -> Q [Dec]
deriveTextShow1Options = deriveTextShowClass TextShow1
deriveTextShow2 :: Name -> Q [Dec]
deriveTextShow2 = deriveTextShow2Options defaultOptions
deriveTextShow2Options :: Options -> Name -> Q [Dec]
deriveTextShow2Options = deriveTextShowClass TextShow2
makeShowt :: Name -> Q Exp
makeShowt name = makeShowtPrec name `appE` integerE 0
makeShowtl :: Name -> Q Exp
makeShowtl name = makeShowtlPrec name `appE` integerE 0
makeShowtPrec :: Name -> Q Exp
makeShowtPrec = makeShowbPrecClass TextShow ShowtPrec defaultOptions
makeShowtlPrec :: Name -> Q Exp
makeShowtlPrec = makeShowbPrecClass TextShow ShowtlPrec defaultOptions
makeShowtList :: Name -> Q Exp
makeShowtList name = [| toStrict . $(makeShowtlList name) |]
makeShowtlList :: Name -> Q Exp
makeShowtlList name = [| toLazyText . $(makeShowbList name) |]
makeShowb :: Name -> Q Exp
makeShowb name = makeShowbPrec name `appE` integerE 0
makeShowbPrec :: Name -> Q Exp
makeShowbPrec = makeShowbPrecClass TextShow ShowbPrec defaultOptions
makeLiftShowbPrec :: Name -> Q Exp
makeLiftShowbPrec = makeShowbPrecClass TextShow1 ShowbPrec defaultOptions
makeShowbPrec1 :: Name -> Q Exp
makeShowbPrec1 name = [| $(makeLiftShowbPrec name) showbPrec showbList |]
makeLiftShowbPrec2 :: Name -> Q Exp
makeLiftShowbPrec2 = makeShowbPrecClass TextShow2 ShowbPrec defaultOptions
makeShowbPrec2 :: Name -> Q Exp
makeShowbPrec2 name = [| $(makeLiftShowbPrec2 name) showbPrec showbList showbPrec showbList |]
makeShowbList :: Name -> Q Exp
makeShowbList name = [| showbListWith $(makeShowb name) |]
makePrintT :: Name -> Q Exp
makePrintT name = [| TS.putStrLn . $(makeShowt name) |]
makePrintTL :: Name -> Q Exp
makePrintTL name = [| TL.putStrLn . $(makeShowtl name) |]
makeHPrintT :: Name -> Q Exp
makeHPrintT name = [| \h -> TS.hPutStrLn h . $(makeShowt name) |]
makeHPrintTL :: Name -> Q Exp
makeHPrintTL name = [| \h -> TL.hPutStrLn h . $(makeShowtl name) |]
deriveTextShowClass :: TextShowClass -> Options -> Name -> Q [Dec]
deriveTextShowClass tsClass opts name = do
info <- reifyDatatype name
case info of
DatatypeInfo { datatypeContext = ctxt
, datatypeName = parentName
, datatypeInstTypes = instTys
, datatypeVariant = variant
, datatypeCons = cons
} -> do
(instanceCxt, instanceType)
<- buildTypeInstance tsClass parentName ctxt instTys variant
(:[]) <$> instanceD (return instanceCxt)
(return instanceType)
(showbPrecDecs tsClass opts instTys cons)
showbPrecDecs :: TextShowClass -> Options -> [Type] -> [ConstructorInfo] -> [Q Dec]
showbPrecDecs tsClass opts instTys cons =
[genMethod ShowbPrec (showbPrecName tsClass)]
++ if tsClass == TextShow && shouldGenTextMethods
then [genMethod ShowtPrec 'showtPrec, genMethod ShowtlPrec 'showtlPrec]
else []
where
shouldGenTextMethods :: Bool
shouldGenTextMethods = case genTextMethods opts of
AlwaysTextMethods -> True
SometimesTextMethods -> all isNullaryCon cons
NeverTextMethods -> False
genMethod :: TextShowFun -> Name -> Q Dec
genMethod method methodName
= funD methodName
[ clause []
(normalB $ makeTextShowForCons tsClass method opts instTys cons)
[]
]
makeShowbPrecClass :: TextShowClass -> TextShowFun -> Options -> Name -> Q Exp
makeShowbPrecClass tsClass tsFun opts name = do
info <- reifyDatatype name
case info of
DatatypeInfo { datatypeContext = ctxt
, datatypeName = parentName
, datatypeInstTypes = instTys
, datatypeVariant = variant
, datatypeCons = cons
} ->
buildTypeInstance tsClass parentName ctxt instTys variant
>> makeTextShowForCons tsClass tsFun opts instTys cons
makeTextShowForCons :: TextShowClass -> TextShowFun -> Options -> [Type] -> [ConstructorInfo]
-> Q Exp
makeTextShowForCons tsClass tsFun opts instTys cons = do
p <- newName "p"
value <- newName "value"
sps <- newNameList "sp" $ fromEnum tsClass
sls <- newNameList "sl" $ fromEnum tsClass
let spls = zip sps sls
spsAndSls = interleave sps sls
lastTyVars = map varTToName $ drop (length instTys - fromEnum tsClass) instTys
splMap = Map.fromList $ zip lastTyVars spls
makeFun
| null cons && emptyCaseBehavior opts && ghc7'8OrLater
= caseE (varE value) []
| null cons
= appE (varE 'seq) (varE value) `appE`
appE (varE 'error)
(stringE $ "Void " ++ nameBase (showPrecName tsClass tsFun))
| otherwise
= caseE (varE value)
(map (makeTextShowForCon p tsClass tsFun splMap) cons)
lamE (map varP $ spsAndSls ++ [p, value])
. appsE
$ [ varE $ showPrecConstName tsClass tsFun
, makeFun
] ++ map varE spsAndSls
++ [varE p, varE value]
where
ghc7'8OrLater :: Bool
#if __GLASGOW_HASKELL__ >= 708
ghc7'8OrLater = True
#else
ghc7'8OrLater = False
#endif
makeTextShowForCon :: Name
-> TextShowClass
-> TextShowFun
-> TyVarMap
-> ConstructorInfo
-> Q Match
makeTextShowForCon _ _ tsFun _
(ConstructorInfo { constructorName = conName, constructorFields = [] }) =
match
(conP conName [])
(normalB $ varE (fromStringName tsFun) `appE` stringE (parenInfixConName conName ""))
[]
makeTextShowForCon p tsClass tsFun tvMap
(ConstructorInfo { constructorName = conName
, constructorVariant = NormalConstructor
, constructorFields = [argTy] }) = do
argTy' <- resolveTypeSynonyms argTy
arg <- newName "arg"
let showArg = makeTextShowForArg appPrec1 tsClass tsFun conName tvMap argTy' arg
namedArg = infixApp (varE (fromStringName tsFun) `appE` stringE (parenInfixConName conName " "))
[| (<>) |]
showArg
match
(conP conName [varP arg])
(normalB $ varE (showParenName tsFun)
`appE` infixApp (varE p) [| (>) |] (integerE appPrec)
`appE` namedArg)
[]
makeTextShowForCon p tsClass tsFun tvMap
(ConstructorInfo { constructorName = conName
, constructorVariant = NormalConstructor
, constructorFields = argTys }) = do
argTys' <- mapM resolveTypeSynonyms argTys
args <- newNameList "arg" $ length argTys'
if isNonUnitTuple conName
then do
let showArgs = zipWith (makeTextShowForArg 0 tsClass tsFun conName tvMap) argTys' args
parenCommaArgs = (varE (singletonName tsFun) `appE` charE '(')
: intersperse (varE (singletonName tsFun) `appE` charE ',') showArgs
mappendArgs = foldr' (`infixApp` [| (<>) |])
(varE (singletonName tsFun) `appE` charE ')')
parenCommaArgs
match (conP conName $ map varP args)
(normalB mappendArgs)
[]
else do
let showArgs = zipWith (makeTextShowForArg appPrec1 tsClass tsFun conName tvMap) argTys' args
mappendArgs = foldr1 (\v q -> infixApp v
[| (<>) |]
(infixApp (varE $ showSpaceName tsFun)
[| (<>) |]
q)) showArgs
namedArgs = infixApp (varE (fromStringName tsFun) `appE` stringE (parenInfixConName conName " "))
[| (<>) |]
mappendArgs
match (conP conName $ map varP args)
(normalB $ varE (showParenName tsFun)
`appE` infixApp (varE p) [| (>) |] (integerE appPrec)
`appE` namedArgs)
[]
makeTextShowForCon p tsClass tsFun tvMap
(ConstructorInfo { constructorName = conName
, constructorVariant = RecordConstructor argNames
, constructorFields = argTys }) = do
argTys' <- mapM resolveTypeSynonyms argTys
args <- newNameList "arg" $ length argTys'
let showArgs = concatMap (\(argName, argTy, arg)
-> let argNameBase = nameBase argName
infixRec = showParen (isSymVar argNameBase)
(showString argNameBase) ""
in [ varE (fromStringName tsFun) `appE` stringE (infixRec ++ " = ")
, makeTextShowForArg 0 tsClass tsFun conName tvMap argTy arg
, varE (showCommaSpaceName tsFun)
]
)
(zip3 argNames argTys' args)
braceCommaArgs = (varE (singletonName tsFun) `appE` charE '{') : take (length showArgs - 1) showArgs
mappendArgs = foldr' (`infixApp` [| (<>) |])
(varE (singletonName tsFun) `appE` charE '}')
braceCommaArgs
namedArgs = infixApp (varE (fromStringName tsFun) `appE` stringE (parenInfixConName conName " "))
[| (<>) |]
mappendArgs
match
(conP conName $ map varP args)
(normalB $ varE (showParenName tsFun)
`appE` infixApp (varE p) [| (>) |] (integerE appPrec)
`appE` namedArgs)
[]
makeTextShowForCon p tsClass tsFun tvMap
(ConstructorInfo { constructorName = conName
, constructorVariant = InfixConstructor
, constructorFields = argTys }) = do
[alTy, arTy] <- mapM resolveTypeSynonyms argTys
al <- newName "argL"
ar <- newName "argR"
fi <- fromMaybe defaultFixity <$> reifyFixityCompat conName
let conPrec = case fi of Fixity prec _ -> prec
opName = nameBase conName
infixOpE = appE (varE $ fromStringName tsFun) . stringE $
if isInfixDataCon opName
then " " ++ opName ++ " "
else " `" ++ opName ++ "` "
match
(infixP (varP al) conName (varP ar))
(normalB $ (varE (showParenName tsFun) `appE` infixApp (varE p) [| (>) |] (integerE conPrec))
`appE` (infixApp (makeTextShowForArg (conPrec + 1) tsClass tsFun conName tvMap alTy al)
[| (<>) |]
(infixApp infixOpE
[| (<>) |]
(makeTextShowForArg (conPrec + 1) tsClass tsFun conName tvMap arTy ar)))
)
[]
makeTextShowForArg :: Int
-> TextShowClass
-> TextShowFun
-> Name
-> TyVarMap
-> Type
-> Name
-> Q Exp
makeTextShowForArg p _ tsFun _ _ (ConT tyName) tyExpName =
showE
where
tyVarE, showPrecE :: Q Exp
tyVarE = varE tyExpName
showPrecE = varE (showPrecName TextShow tsFun)
showE :: Q Exp
showE =
case Map.lookup tyName primShowTbl of
Just ps -> showPrimE ps
Nothing -> showPrecE `appE` integerE p `appE` tyVarE
showPrimE :: PrimShow -> Q Exp
showPrimE PrimShow{ primShowBoxer
#if __GLASGOW_HASKELL__ >= 800
, primShowPostfixMod, primShowConv
#endif
}
#if __GLASGOW_HASKELL__ >= 800
= primShowConv tsFun $ infixApp (primE 0) [| (<>) |] (primShowPostfixMod tsFun)
#else
= primE p
#endif
where
primE :: Int -> Q Exp
primE prec = showPrecE `appE` integerE prec `appE` primShowBoxer tyVarE
makeTextShowForArg p tsClass tsFun conName tvMap ty tyExpName =
[| $(makeTextShowForType tsClass tsFun conName tvMap False ty) p $(varE tyExpName) |]
makeTextShowForType :: TextShowClass
-> TextShowFun
-> Name
-> TyVarMap
-> Bool
-> Type
-> Q Exp
makeTextShowForType _ tsFun _ tvMap sl (VarT tyName) =
varE $ case Map.lookup tyName tvMap of
Just (spExp, slExp) -> if sl then slExp else spExp
Nothing -> if sl then showListName TextShow tsFun
else showPrecName TextShow tsFun
makeTextShowForType tsClass tsFun conName tvMap sl (SigT ty _) =
makeTextShowForType tsClass tsFun conName tvMap sl ty
makeTextShowForType tsClass tsFun conName tvMap sl (ForallT _ _ ty) =
makeTextShowForType tsClass tsFun conName tvMap sl ty
makeTextShowForType tsClass tsFun conName tvMap sl ty = do
let tyCon :: Type
tyArgs :: [Type]
tyCon :| tyArgs = unapplyTy ty
numLastArgs :: Int
numLastArgs = min (fromEnum tsClass) (length tyArgs)
lhsArgs, rhsArgs :: [Type]
(lhsArgs, rhsArgs) = splitAt (length tyArgs - numLastArgs) tyArgs
tyVarNames :: [Name]
tyVarNames = Map.keys tvMap
itf <- isTyFamily tyCon
if any (`mentionsName` tyVarNames) lhsArgs
|| itf && any (`mentionsName` tyVarNames) tyArgs
then outOfPlaceTyVarError tsClass conName
else if any (`mentionsName` tyVarNames) rhsArgs
then appsE $ [ varE $ showPrecOrListName sl (toEnum numLastArgs) tsFun]
++ zipWith (makeTextShowForType tsClass tsFun conName tvMap)
(cycle [False,True])
(interleave rhsArgs rhsArgs)
else varE $ if sl then showListName TextShow tsFun
else showPrecName TextShow tsFun
buildTypeInstance :: TextShowClass
-> Name
-> Cxt
-> [Type]
-> DatatypeVariant
-> Q (Cxt, Type)
buildTypeInstance tsClass tyConName dataCxt varTysOrig variant = do
varTysExp <- mapM resolveTypeSynonyms varTysOrig
let remainingLength :: Int
remainingLength = length varTysOrig - fromEnum tsClass
droppedTysExp :: [Type]
droppedTysExp = drop remainingLength varTysExp
droppedStarKindStati :: [StarKindStatus]
droppedStarKindStati = map canRealizeKindStar droppedTysExp
when (remainingLength < 0 || any (== NotKindStar) droppedStarKindStati) $
derivingKindError tsClass tyConName
let droppedKindVarNames :: [Name]
droppedKindVarNames = catKindVarNames droppedStarKindStati
varTysExpSubst :: [Type]
varTysExpSubst = map (substNamesWithKindStar droppedKindVarNames) varTysExp
remainingTysExpSubst, droppedTysExpSubst :: [Type]
(remainingTysExpSubst, droppedTysExpSubst) =
splitAt remainingLength varTysExpSubst
droppedTyVarNames :: [Name]
droppedTyVarNames = freeVariables droppedTysExpSubst
unless (all hasKindStar droppedTysExpSubst) $
derivingKindError tsClass tyConName
let preds :: [Maybe Pred]
kvNames :: [[Name]]
kvNames' :: [Name]
(preds, kvNames) = unzip $ map (deriveConstraint tsClass) remainingTysExpSubst
kvNames' = concat kvNames
remainingTysExpSubst' :: [Type]
remainingTysExpSubst' =
map (substNamesWithKindStar kvNames') remainingTysExpSubst
remainingTysOrigSubst :: [Type]
remainingTysOrigSubst =
map (substNamesWithKindStar (union droppedKindVarNames kvNames'))
$ take remainingLength varTysOrig
isDataFamily :: Bool
isDataFamily = case variant of
Datatype -> False
Newtype -> False
DataInstance -> True
NewtypeInstance -> True
remainingTysOrigSubst' :: [Type]
remainingTysOrigSubst' =
if isDataFamily
then remainingTysOrigSubst
else map unSigT remainingTysOrigSubst
instanceCxt :: Cxt
instanceCxt = catMaybes preds
instanceType :: Type
instanceType = AppT (ConT $ textShowClassName tsClass)
$ applyTyCon tyConName remainingTysOrigSubst'
when (any (`predMentionsName` droppedTyVarNames) dataCxt) $
datatypeContextError tyConName instanceType
unless (canEtaReduce remainingTysExpSubst' droppedTysExpSubst) $
etaReductionError instanceType
return (instanceCxt, instanceType)
deriveConstraint :: TextShowClass -> Type -> (Maybe Pred, [Name])
deriveConstraint tsClass t
| not (isTyVar t) = (Nothing, [])
| hasKindStar t = (Just (applyClass ''TextShow tName), [])
| otherwise = case hasKindVarChain 1 t of
Just ns | tsClass >= TextShow1
-> (Just (applyClass ''TextShow1 tName), ns)
_ -> case hasKindVarChain 2 t of
Just ns | tsClass == TextShow2
-> (Just (applyClass ''TextShow2 tName), ns)
_ -> (Nothing, [])
where
tName :: Name
tName = varTToName t
derivingKindError :: TextShowClass -> Name -> a
derivingKindError tsClass tyConName = error
. showString "Cannot derive well-kinded instance of form ‘"
. showString className
. showChar ' '
. showParen True
( showString (nameBase tyConName)
. showString " ..."
)
. showString "‘\n\tClass "
. showString className
. showString " expects an argument of kind "
. showString (pprint . createKindChain $ fromEnum tsClass)
$ ""
where
className :: String
className = nameBase $ textShowClassName tsClass
etaReductionError :: Type -> a
etaReductionError instanceType = error $
"Cannot eta-reduce to an instance of form \n\tinstance (...) => "
++ pprint instanceType
datatypeContextError :: Name -> Type -> a
datatypeContextError dataName instanceType = error
. showString "Can't make a derived instance of ‘"
. showString (pprint instanceType)
. showString "‘:\n\tData type ‘"
. showString (nameBase dataName)
. showString "‘ must not have a class context involving the last type argument(s)"
$ ""
outOfPlaceTyVarError :: TextShowClass -> Name -> a
outOfPlaceTyVarError tsClass conName = error
. showString "Constructor ‘"
. showString (nameBase conName)
. showString "‘ must only use its last "
. shows n
. showString " type variable(s) within the last "
. shows n
. showString " argument(s) of a data type"
$ ""
where
n :: Int
n = fromEnum tsClass
applySubstitutionKind :: Map Name Kind -> Type -> Type
#if MIN_VERSION_template_haskell(2,8,0)
applySubstitutionKind = applySubstitution
#else
applySubstitutionKind _ t = t
#endif
substNameWithKind :: Name -> Kind -> Type -> Type
substNameWithKind n k = applySubstitutionKind (Map.singleton n k)
substNamesWithKindStar :: [Name] -> Type -> Type
substNamesWithKindStar ns t = foldr' (flip substNameWithKind starK) t ns
data TextShowClass = TextShow | TextShow1 | TextShow2
deriving (Enum, Eq, Ord)
data TextShowFun = ShowbPrec | ShowtPrec | ShowtlPrec
fromStringName :: TextShowFun -> Name
fromStringName ShowbPrec = 'TB.fromString
fromStringName ShowtPrec = 'TS.pack
fromStringName ShowtlPrec = 'TL.pack
singletonName :: TextShowFun -> Name
singletonName ShowbPrec = 'TB.singleton
singletonName ShowtPrec = 'TS.singleton
singletonName ShowtlPrec = 'TL.singleton
showParenName :: TextShowFun -> Name
showParenName ShowbPrec = 'showbParen
showParenName ShowtPrec = 'showtParen
showParenName ShowtlPrec = 'showtlParen
showCommaSpaceName :: TextShowFun -> Name
showCommaSpaceName ShowbPrec = 'showbCommaSpace
showCommaSpaceName ShowtPrec = 'showtCommaSpace
showCommaSpaceName ShowtlPrec = 'showtlCommaSpace
showSpaceName :: TextShowFun -> Name
showSpaceName ShowbPrec = 'showbSpace
showSpaceName ShowtPrec = 'showtSpace
showSpaceName ShowtlPrec = 'showtlSpace
showPrecConstName :: TextShowClass -> TextShowFun -> Name
showPrecConstName tsClass ShowbPrec = showbPrecConstName tsClass
showPrecConstName TextShow ShowtPrec = 'showtPrecConst
showPrecConstName TextShow ShowtlPrec = 'showtlPrecConst
showPrecConstName _ _ = error "showPrecConstName"
showbPrecConstName :: TextShowClass -> Name
showbPrecConstName TextShow = 'showbPrecConst
showbPrecConstName TextShow1 = 'liftShowbPrecConst
showbPrecConstName TextShow2 = 'liftShowbPrec2Const
textShowClassName :: TextShowClass -> Name
textShowClassName TextShow = ''TextShow
textShowClassName TextShow1 = ''TextShow1
textShowClassName TextShow2 = ''TextShow2
showPrecName :: TextShowClass -> TextShowFun -> Name
showPrecName tsClass ShowbPrec = showbPrecName tsClass
showPrecName TextShow ShowtPrec = 'showtPrec
showPrecName TextShow ShowtlPrec = 'showtlPrec
showPrecName _ _ = error "showPrecName"
showbPrecName :: TextShowClass -> Name
showbPrecName TextShow = 'showbPrec
showbPrecName TextShow1 = 'liftShowbPrec
showbPrecName TextShow2 = 'liftShowbPrec2
showListName :: TextShowClass -> TextShowFun -> Name
showListName tsClass ShowbPrec = showbListName tsClass
showListName TextShow ShowtPrec = 'showtPrec
showListName TextShow ShowtlPrec = 'showtlPrec
showListName _ _ = error "showListName"
showbListName :: TextShowClass -> Name
showbListName TextShow = 'showbList
showbListName TextShow1 = 'liftShowbList
showbListName TextShow2 = 'liftShowbList2
showPrecOrListName :: Bool
-> TextShowClass
-> TextShowFun
-> Name
showPrecOrListName False = showPrecName
showPrecOrListName True = showListName
showbPrecConst :: Builder
-> Int -> a -> Builder
showbPrecConst b _ _ = b
showtPrecConst :: TS.Text
-> Int -> a -> TS.Text
showtPrecConst t _ _ = t
showtlPrecConst :: TL.Text
-> Int -> a -> TL.Text
showtlPrecConst tl _ _ = tl
liftShowbPrecConst :: Builder
-> (Int -> a -> Builder) -> ([a] -> Builder)
-> Int -> f a -> Builder
liftShowbPrecConst b _ _ _ _ = b
liftShowbPrec2Const :: Builder
-> (Int -> a -> Builder) -> ([a] -> Builder)
-> (Int -> b -> Builder) -> ([b] -> Builder)
-> Int -> f a b -> Builder
liftShowbPrec2Const b _ _ _ _ _ _ = b
data StarKindStatus = NotKindStar
| KindStar
| IsKindVar Name
deriving Eq
canRealizeKindStar :: Type -> StarKindStatus
canRealizeKindStar t
| hasKindStar t = KindStar
| otherwise = case t of
#if MIN_VERSION_template_haskell(2,8,0)
SigT _ (VarT k) -> IsKindVar k
#endif
_ -> NotKindStar
starKindStatusToName :: StarKindStatus -> Maybe Name
starKindStatusToName (IsKindVar n) = Just n
starKindStatusToName _ = Nothing
catKindVarNames :: [StarKindStatus] -> [Name]
catKindVarNames = mapMaybe starKindStatusToName
data PrimShow = PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
, primShowPostfixMod :: TextShowFun -> Q Exp
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
}
primShowTbl :: Map Name PrimShow
primShowTbl = Map.fromList
[ (''Char#, PrimShow
{ primShowBoxer = appE (conE 'C#)
, primShowPostfixMod = oneHashE
, primShowConv = \_ x -> x
})
, (''Double#, PrimShow
{ primShowBoxer = appE (conE 'D#)
, primShowPostfixMod = twoHashE
, primShowConv = \_ x -> x
})
, (''Float#, PrimShow
{ primShowBoxer = appE (conE 'F#)
, primShowPostfixMod = oneHashE
, primShowConv = \_ x -> x
})
, (''Int#, PrimShow
{ primShowBoxer = appE (conE 'I#)
, primShowPostfixMod = oneHashE
, primShowConv = \_ x -> x
})
, (''Word#, PrimShow
{ primShowBoxer = appE (conE 'W#)
, primShowPostfixMod = twoHashE
, primShowConv = \_ x -> x
})
#if MIN_VERSION_base(4,13,0)
, (''Int8#, PrimShow
{ primShowBoxer = appE (conE 'I#) . appE (varE 'extendInt8#)
, primShowPostfixMod = oneHashE
, primShowConv = mkNarrowE "narrowInt8#"
})
, (''Int16#, PrimShow
{ primShowBoxer = appE (conE 'I#) . appE (varE 'extendInt16#)
, primShowPostfixMod = oneHashE
, primShowConv = mkNarrowE "narrowInt16#"
})
, (''Word8#, PrimShow
{ primShowBoxer = appE (conE 'W#) . appE (varE 'extendWord8#)
, primShowPostfixMod = twoHashE
, primShowConv = mkNarrowE "narrowWord8#"
})
, (''Word16#, PrimShow
{ primShowBoxer = appE (conE 'W#) . appE (varE 'extendWord16#)
, primShowPostfixMod = twoHashE
, primShowConv = mkNarrowE "narrowWord16#"
})
#endif
]
#if MIN_VERSION_base(4,13,0)
mkNarrowE :: String -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE narrowStr tsFun e =
foldr (`infixApp` [| (<>) |])
(varE (singletonName tsFun) `appE` charE ')')
[ varE (fromStringName tsFun) `appE` stringE ('(':narrowStr ++ " ")
, e
]
#endif
oneHashE, twoHashE :: TextShowFun -> Q Exp
oneHashE tsFun = varE (singletonName tsFun) `appE` charE '#'
twoHashE tsFun = varE (fromStringName tsFun) `appE` stringE "##"
integerE :: Int -> Q Exp
integerE = litE . integerL . fromIntegral
charE :: Char -> Q Exp
charE = litE . charL
hasKindStar :: Type -> Bool
hasKindStar VarT{} = True
#if MIN_VERSION_template_haskell(2,8,0)
hasKindStar (SigT _ StarT) = True
#else
hasKindStar (SigT _ StarK) = True
#endif
hasKindStar _ = False
isStarOrVar :: Kind -> Bool
#if MIN_VERSION_template_haskell(2,8,0)
isStarOrVar StarT = True
isStarOrVar VarT{} = True
#else
isStarOrVar StarK = True
#endif
isStarOrVar _ = False
newNameList :: String -> Int -> Q [Name]
newNameList prefix n = mapM (newName . (prefix ++) . show) [1..n]
hasKindVarChain :: Int -> Type -> Maybe [Name]
hasKindVarChain kindArrows t =
let uk = uncurryKind (tyKind t)
in if (length uk - 1 == kindArrows) && all isStarOrVar uk
then Just (concatMap freeVariables uk)
else Nothing
tyKind :: Type -> Kind
tyKind (SigT _ k) = k
tyKind _ = starK
type TyVarMap = Map Name (Name, Name)
isNonUnitTuple :: Name -> Bool
isNonUnitTuple = isTupleString . nameBase
parenInfixConName :: Name -> ShowS
parenInfixConName conName =
let conNameBase = nameBase conName
in showParen (isInfixDataCon conNameBase) $ showString conNameBase
applyClass :: Name -> Name -> Pred
#if MIN_VERSION_template_haskell(2,10,0)
applyClass con t = AppT (ConT con) (VarT t)
#else
applyClass con t = ClassP con [VarT t]
#endif
canEtaReduce :: [Type] -> [Type] -> Bool
canEtaReduce remaining dropped =
all isTyVar dropped
&& allDistinct droppedNames
&& not (any (`mentionsName` droppedNames) remaining)
where
droppedNames :: [Name]
droppedNames = map varTToName dropped
varTToName_maybe :: Type -> Maybe Name
varTToName_maybe (VarT n) = Just n
varTToName_maybe (SigT t _) = varTToName_maybe t
varTToName_maybe _ = Nothing
varTToName :: Type -> Name
varTToName = fromMaybe (error "Not a type variable!") . varTToName_maybe
unSigT :: Type -> Type
unSigT (SigT t _) = t
unSigT t = t
isTyVar :: Type -> Bool
isTyVar (VarT _) = True
isTyVar (SigT t _) = isTyVar t
isTyVar _ = False
isTyFamily :: Type -> Q Bool
isTyFamily (ConT n) = do
info <- reify n
return $ case info of
#if MIN_VERSION_template_haskell(2,11,0)
FamilyI OpenTypeFamilyD{} _ -> True
#else
FamilyI (FamilyD TypeFam _ _ _) _ -> True
#endif
#if MIN_VERSION_template_haskell(2,9,0)
FamilyI ClosedTypeFamilyD{} _ -> True
#endif
_ -> False
isTyFamily _ = return False
allDistinct :: Ord a => [a] -> Bool
allDistinct = allDistinct' Set.empty
where
allDistinct' :: Ord a => Set a -> [a] -> Bool
allDistinct' uniqs (x:xs)
| x `Set.member` uniqs = False
| otherwise = allDistinct' (Set.insert x uniqs) xs
allDistinct' _ _ = True
mentionsName :: Type -> [Name] -> Bool
mentionsName = go
where
go :: Type -> [Name] -> Bool
go (AppT t1 t2) names = go t1 names || go t2 names
go (SigT t _k) names = go t names
#if MIN_VERSION_template_haskell(2,8,0)
|| go _k names
#endif
go (VarT n) names = n `elem` names
go _ _ = False
predMentionsName :: Pred -> [Name] -> Bool
#if MIN_VERSION_template_haskell(2,10,0)
predMentionsName = mentionsName
#else
predMentionsName (ClassP n tys) names = n `elem` names || any (`mentionsName` names) tys
predMentionsName (EqualP t1 t2) names = mentionsName t1 names || mentionsName t2 names
#endif
applyTy :: Type -> [Type] -> Type
applyTy = foldl' AppT
applyTyCon :: Name -> [Type] -> Type
applyTyCon = applyTy . ConT
unapplyTy :: Type -> NonEmpty Type
unapplyTy = NE.reverse . go
where
go :: Type -> NonEmpty Type
go (AppT t1 t2) = t2 <| go t1
go (SigT t _) = go t
go (ForallT _ _ t) = go t
go t = t :| []
uncurryTy :: Type -> NonEmpty Type
uncurryTy (AppT (AppT ArrowT t1) t2) = t1 <| uncurryTy t2
uncurryTy (SigT t _) = uncurryTy t
uncurryTy (ForallT _ _ t) = uncurryTy t
uncurryTy t = t :| []
uncurryKind :: Kind -> NonEmpty Kind
#if MIN_VERSION_template_haskell(2,8,0)
uncurryKind = uncurryTy
#else
uncurryKind (ArrowK k1 k2) = k1 <| uncurryKind k2
uncurryKind k = k :| []
#endif
createKindChain :: Int -> Kind
createKindChain = go starK
where
go :: Kind -> Int -> Kind
go k !0 = k
go k !n = go (arrowKCompat starK k) (n - 1)
isNullaryCon :: ConstructorInfo -> Bool
isNullaryCon (ConstructorInfo { constructorFields = [] }) = True
isNullaryCon _ = False
interleave :: [a] -> [a] -> [a]
interleave (a1:a1s) (a2:a2s) = a1:a2:interleave a1s a2s
interleave _ _ = []