{-# 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 qualified Control.Monad as Monad (fail)
import Data.Foldable.Compat
import qualified Data.List.Compat as List
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#
# if MIN_VERSION_base(4,16,0)
, Int32#, Word32#
, int8ToInt#, int16ToInt#, int32ToInt#
, intToInt8#, intToInt16#, intToInt32#
, word8ToWord#, word16ToWord#, word32ToWord#
, wordToWord8#, wordToWord16#, wordToWord32#
# else
, extendInt8#, extendInt16#, extendWord8#, extendWord16#
, narrowInt8#, narrowInt16#, narrowWord8#, narrowWord16#
# endif
#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 :: Name -> Q [Dec]
deriveTextShow = Options -> Name -> Q [Dec]
deriveTextShowOptions Options
defaultOptions
deriveTextShowOptions :: Options -> Name -> Q [Dec]
deriveTextShowOptions :: Options -> Name -> Q [Dec]
deriveTextShowOptions = TextShowClass -> Options -> Name -> Q [Dec]
deriveTextShowClass TextShowClass
TextShow
deriveTextShow1 :: Name -> Q [Dec]
deriveTextShow1 :: Name -> Q [Dec]
deriveTextShow1 = Options -> Name -> Q [Dec]
deriveTextShow1Options Options
defaultOptions
deriveTextShow1Options :: Options -> Name -> Q [Dec]
deriveTextShow1Options :: Options -> Name -> Q [Dec]
deriveTextShow1Options = TextShowClass -> Options -> Name -> Q [Dec]
deriveTextShowClass TextShowClass
TextShow1
deriveTextShow2 :: Name -> Q [Dec]
deriveTextShow2 :: Name -> Q [Dec]
deriveTextShow2 = Options -> Name -> Q [Dec]
deriveTextShow2Options Options
defaultOptions
deriveTextShow2Options :: Options -> Name -> Q [Dec]
deriveTextShow2Options :: Options -> Name -> Q [Dec]
deriveTextShow2Options = TextShowClass -> Options -> Name -> Q [Dec]
deriveTextShowClass TextShowClass
TextShow2
makeShowt :: Name -> Q Exp
makeShowt :: Name -> Q Exp
makeShowt Name
name = Name -> Q Exp
makeShowtPrec Name
name forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Int -> Q Exp
integerE Int
0
makeShowtl :: Name -> Q Exp
makeShowtl :: Name -> Q Exp
makeShowtl Name
name = Name -> Q Exp
makeShowtlPrec Name
name forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Int -> Q Exp
integerE Int
0
makeShowtPrec :: Name -> Q Exp
makeShowtPrec :: Name -> Q Exp
makeShowtPrec = TextShowClass -> TextShowFun -> Options -> Name -> Q Exp
makeShowbPrecClass TextShowClass
TextShow TextShowFun
ShowtPrec Options
defaultOptions
makeShowtlPrec :: Name -> Q Exp
makeShowtlPrec :: Name -> Q Exp
makeShowtlPrec = TextShowClass -> TextShowFun -> Options -> Name -> Q Exp
makeShowbPrecClass TextShowClass
TextShow TextShowFun
ShowtlPrec Options
defaultOptions
makeShowtList :: Name -> Q Exp
makeShowtList :: Name -> Q Exp
makeShowtList Name
name = [| toStrict . $(makeShowtlList name) |]
makeShowtlList :: Name -> Q Exp
makeShowtlList :: Name -> Q Exp
makeShowtlList Name
name = [| toLazyText . $(makeShowbList name) |]
makeShowb :: Name -> Q Exp
makeShowb :: Name -> Q Exp
makeShowb Name
name = Name -> Q Exp
makeShowbPrec Name
name forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Int -> Q Exp
integerE Int
0
makeShowbPrec :: Name -> Q Exp
makeShowbPrec :: Name -> Q Exp
makeShowbPrec = TextShowClass -> TextShowFun -> Options -> Name -> Q Exp
makeShowbPrecClass TextShowClass
TextShow TextShowFun
ShowbPrec Options
defaultOptions
makeLiftShowbPrec :: Name -> Q Exp
makeLiftShowbPrec :: Name -> Q Exp
makeLiftShowbPrec = TextShowClass -> TextShowFun -> Options -> Name -> Q Exp
makeShowbPrecClass TextShowClass
TextShow1 TextShowFun
ShowbPrec Options
defaultOptions
makeShowbPrec1 :: Name -> Q Exp
makeShowbPrec1 :: Name -> Q Exp
makeShowbPrec1 Name
name = [| $(makeLiftShowbPrec name) showbPrec showbList |]
makeLiftShowbPrec2 :: Name -> Q Exp
makeLiftShowbPrec2 :: Name -> Q Exp
makeLiftShowbPrec2 = TextShowClass -> TextShowFun -> Options -> Name -> Q Exp
makeShowbPrecClass TextShowClass
TextShow2 TextShowFun
ShowbPrec Options
defaultOptions
makeShowbPrec2 :: Name -> Q Exp
makeShowbPrec2 :: Name -> Q Exp
makeShowbPrec2 Name
name = [| $(makeLiftShowbPrec2 name) showbPrec showbList showbPrec showbList |]
makeShowbList :: Name -> Q Exp
makeShowbList :: Name -> Q Exp
makeShowbList Name
name = [| showbListWith $(makeShowb name) |]
makePrintT :: Name -> Q Exp
makePrintT :: Name -> Q Exp
makePrintT Name
name = [| TS.putStrLn . $(makeShowt name) |]
makePrintTL :: Name -> Q Exp
makePrintTL :: Name -> Q Exp
makePrintTL Name
name = [| TL.putStrLn . $(makeShowtl name) |]
makeHPrintT :: Name -> Q Exp
makeHPrintT :: Name -> Q Exp
makeHPrintT Name
name = [| \h -> TS.hPutStrLn h . $(makeShowt name) |]
makeHPrintTL :: Name -> Q Exp
makeHPrintTL :: Name -> Q Exp
makeHPrintTL Name
name = [| \h -> TL.hPutStrLn h . $(makeShowtl name) |]
deriveTextShowClass :: TextShowClass -> Options -> Name -> Q [Dec]
deriveTextShowClass :: TextShowClass -> Options -> Name -> Q [Dec]
deriveTextShowClass TextShowClass
tsClass Options
opts Name
name = do
DatatypeInfo
info <- Name -> Q DatatypeInfo
reifyDatatype Name
name
case DatatypeInfo
info of
DatatypeInfo { datatypeContext :: DatatypeInfo -> [Type]
datatypeContext = [Type]
ctxt
, datatypeName :: DatatypeInfo -> Name
datatypeName = Name
parentName
, datatypeInstTypes :: DatatypeInfo -> [Type]
datatypeInstTypes = [Type]
instTys
, datatypeVariant :: DatatypeInfo -> DatatypeVariant
datatypeVariant = DatatypeVariant
variant
, datatypeCons :: DatatypeInfo -> [ConstructorInfo]
datatypeCons = [ConstructorInfo]
cons
} -> do
([Type]
instanceCxt, Type
instanceType)
<- TextShowClass
-> Name -> [Type] -> [Type] -> DatatypeVariant -> Q ([Type], Type)
buildTypeInstance TextShowClass
tsClass Name
parentName [Type]
ctxt [Type]
instTys DatatypeVariant
variant
(forall a. a -> [a] -> [a]
:[]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *).
Quote m =>
m [Type] -> m Type -> [m Dec] -> m Dec
instanceD (forall (m :: * -> *) a. Monad m => a -> m a
return [Type]
instanceCxt)
(forall (m :: * -> *) a. Monad m => a -> m a
return Type
instanceType)
(TextShowClass -> Options -> [Type] -> [ConstructorInfo] -> [Q Dec]
showbPrecDecs TextShowClass
tsClass Options
opts [Type]
instTys [ConstructorInfo]
cons)
showbPrecDecs :: TextShowClass -> Options -> [Type] -> [ConstructorInfo] -> [Q Dec]
showbPrecDecs :: TextShowClass -> Options -> [Type] -> [ConstructorInfo] -> [Q Dec]
showbPrecDecs TextShowClass
tsClass Options
opts [Type]
instTys [ConstructorInfo]
cons =
[TextShowFun -> Name -> Q Dec
genMethod TextShowFun
ShowbPrec (TextShowClass -> Name
showbPrecName TextShowClass
tsClass)]
forall a. [a] -> [a] -> [a]
++ if TextShowClass
tsClass forall a. Eq a => a -> a -> Bool
== TextShowClass
TextShow Bool -> Bool -> Bool
&& Bool
shouldGenTextMethods
then [TextShowFun -> Name -> Q Dec
genMethod TextShowFun
ShowtPrec 'showtPrec, TextShowFun -> Name -> Q Dec
genMethod TextShowFun
ShowtlPrec 'showtlPrec]
else []
where
shouldGenTextMethods :: Bool
shouldGenTextMethods :: Bool
shouldGenTextMethods = case Options -> GenTextMethods
genTextMethods Options
opts of
GenTextMethods
AlwaysTextMethods -> Bool
True
GenTextMethods
SometimesTextMethods -> forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ConstructorInfo -> Bool
isNullaryCon [ConstructorInfo]
cons
GenTextMethods
NeverTextMethods -> Bool
False
genMethod :: TextShowFun -> Name -> Q Dec
genMethod :: TextShowFun -> Name -> Q Dec
genMethod TextShowFun
method Name
methodName
= forall (m :: * -> *). Quote m => Name -> [m Clause] -> m Dec
funD Name
methodName
[ forall (m :: * -> *).
Quote m =>
[m Pat] -> m Body -> [m Dec] -> m Clause
clause []
(forall (m :: * -> *). Quote m => m Exp -> m Body
normalB forall a b. (a -> b) -> a -> b
$ TextShowClass
-> TextShowFun -> Options -> [Type] -> [ConstructorInfo] -> Q Exp
makeTextShowForCons TextShowClass
tsClass TextShowFun
method Options
opts [Type]
instTys [ConstructorInfo]
cons)
[]
]
makeShowbPrecClass :: TextShowClass -> TextShowFun -> Options -> Name -> Q Exp
makeShowbPrecClass :: TextShowClass -> TextShowFun -> Options -> Name -> Q Exp
makeShowbPrecClass TextShowClass
tsClass TextShowFun
tsFun Options
opts Name
name = do
DatatypeInfo
info <- Name -> Q DatatypeInfo
reifyDatatype Name
name
case DatatypeInfo
info of
DatatypeInfo { datatypeContext :: DatatypeInfo -> [Type]
datatypeContext = [Type]
ctxt
, datatypeName :: DatatypeInfo -> Name
datatypeName = Name
parentName
, datatypeInstTypes :: DatatypeInfo -> [Type]
datatypeInstTypes = [Type]
instTys
, datatypeVariant :: DatatypeInfo -> DatatypeVariant
datatypeVariant = DatatypeVariant
variant
, datatypeCons :: DatatypeInfo -> [ConstructorInfo]
datatypeCons = [ConstructorInfo]
cons
} ->
TextShowClass
-> Name -> [Type] -> [Type] -> DatatypeVariant -> Q ([Type], Type)
buildTypeInstance TextShowClass
tsClass Name
parentName [Type]
ctxt [Type]
instTys DatatypeVariant
variant
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TextShowClass
-> TextShowFun -> Options -> [Type] -> [ConstructorInfo] -> Q Exp
makeTextShowForCons TextShowClass
tsClass TextShowFun
tsFun Options
opts [Type]
instTys [ConstructorInfo]
cons
makeTextShowForCons :: TextShowClass -> TextShowFun -> Options -> [Type] -> [ConstructorInfo]
-> Q Exp
makeTextShowForCons :: TextShowClass
-> TextShowFun -> Options -> [Type] -> [ConstructorInfo] -> Q Exp
makeTextShowForCons TextShowClass
tsClass TextShowFun
tsFun Options
opts [Type]
instTys [ConstructorInfo]
cons = do
Name
p <- forall (m :: * -> *). Quote m => String -> m Name
newName String
"p"
Name
value <- forall (m :: * -> *). Quote m => String -> m Name
newName String
"value"
[Name]
sps <- String -> Int -> Q [Name]
newNameList String
"sp" forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum TextShowClass
tsClass
[Name]
sls <- String -> Int -> Q [Name]
newNameList String
"sl" forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum TextShowClass
tsClass
let spls :: [(Name, Name)]
spls = forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
sps [Name]
sls
spsAndSls :: [Name]
spsAndSls = forall a. [a] -> [a] -> [a]
interleave [Name]
sps [Name]
sls
lastTyVars :: [Name]
lastTyVars = forall a b. (a -> b) -> [a] -> [b]
map Type -> Name
varTToName forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
drop (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
instTys forall a. Num a => a -> a -> a
- forall a. Enum a => a -> Int
fromEnum TextShowClass
tsClass) [Type]
instTys
splMap :: Map Name (Name, Name)
splMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
lastTyVars [(Name, Name)]
spls
makeFun :: Q Exp
makeFun
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ConstructorInfo]
cons Bool -> Bool -> Bool
&& Options -> Bool
emptyCaseBehavior Options
opts
= forall (m :: * -> *). Quote m => m Exp -> [m Match] -> m Exp
caseE (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
value) []
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ConstructorInfo]
cons
= forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE 'seq) (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
value) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE`
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE 'error)
(forall (m :: * -> *). Quote m => String -> m Exp
stringE forall a b. (a -> b) -> a -> b
$ String
"Void " forall a. [a] -> [a] -> [a]
++ Name -> String
nameBase (TextShowClass -> TextShowFun -> Name
showPrecName TextShowClass
tsClass TextShowFun
tsFun))
| Bool
otherwise
= forall (m :: * -> *). Quote m => m Exp -> [m Match] -> m Exp
caseE (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
value)
(forall a b. (a -> b) -> [a] -> [b]
map (Name
-> TextShowClass
-> TextShowFun
-> Map Name (Name, Name)
-> ConstructorInfo
-> Q Match
makeTextShowForCon Name
p TextShowClass
tsClass TextShowFun
tsFun Map Name (Name, Name)
splMap) [ConstructorInfo]
cons)
forall (m :: * -> *). Quote m => [m Pat] -> m Exp -> m Exp
lamE (forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Pat
varP forall a b. (a -> b) -> a -> b
$ [Name]
spsAndSls forall a. [a] -> [a] -> [a]
++ [Name
p, Name
value])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Quote m => [m Exp] -> m Exp
appsE
forall a b. (a -> b) -> a -> b
$ [ forall (m :: * -> *). Quote m => Name -> m Exp
varE forall a b. (a -> b) -> a -> b
$ TextShowClass -> TextShowFun -> Name
showPrecConstName TextShowClass
tsClass TextShowFun
tsFun
, Q Exp
makeFun
] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Exp
varE [Name]
spsAndSls
forall a. [a] -> [a] -> [a]
++ [forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
p, forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
value]
makeTextShowForCon :: Name
-> TextShowClass
-> TextShowFun
-> TyVarMap
-> ConstructorInfo
-> Q Match
makeTextShowForCon :: Name
-> TextShowClass
-> TextShowFun
-> Map Name (Name, Name)
-> ConstructorInfo
-> Q Match
makeTextShowForCon Name
_ TextShowClass
_ TextShowFun
tsFun Map Name (Name, Name)
_
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
conName, constructorFields :: ConstructorInfo -> [Type]
constructorFields = [] }) =
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match
(forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
conName [])
(forall (m :: * -> *). Quote m => m Exp -> m Body
normalB forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
fromStringName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => String -> m Exp
stringE (Name -> ShowS
parenInfixConName Name
conName String
""))
[]
makeTextShowForCon Name
p TextShowClass
tsClass TextShowFun
tsFun Map Name (Name, Name)
tvMap
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
conName
, constructorVariant :: ConstructorInfo -> ConstructorVariant
constructorVariant = ConstructorVariant
NormalConstructor
, constructorFields :: ConstructorInfo -> [Type]
constructorFields = [Type
argTy] }) = do
Type
argTy' <- Type -> Q Type
resolveTypeSynonyms Type
argTy
Name
arg <- forall (m :: * -> *). Quote m => String -> m Name
newName String
"arg"
let showArg :: Q Exp
showArg = Int
-> TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Type
-> Name
-> Q Exp
makeTextShowForArg Int
appPrec1 TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Type
argTy' Name
arg
namedArg :: Q Exp
namedArg = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
fromStringName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => String -> m Exp
stringE (Name -> ShowS
parenInfixConName Name
conName String
" "))
[| (<>) |]
Q Exp
showArg
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match
(forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
conName [forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
arg])
(forall (m :: * -> *). Quote m => m Exp -> m Body
normalB forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
showParenName TextShowFun
tsFun)
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
p) [| (>) |] (Int -> Q Exp
integerE Int
appPrec)
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Q Exp
namedArg)
[]
makeTextShowForCon Name
p TextShowClass
tsClass TextShowFun
tsFun Map Name (Name, Name)
tvMap
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
conName
, constructorVariant :: ConstructorInfo -> ConstructorVariant
constructorVariant = ConstructorVariant
NormalConstructor
, constructorFields :: ConstructorInfo -> [Type]
constructorFields = [Type]
argTys }) = do
[Type]
argTys' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Type -> Q Type
resolveTypeSynonyms [Type]
argTys
[Name]
args <- String -> Int -> Q [Name]
newNameList String
"arg" forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
argTys'
if Name -> Bool
isNonUnitTuple Name
conName
then do
let showArgs :: [Q Exp]
showArgs = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Int
-> TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Type
-> Name
-> Q Exp
makeTextShowForArg Int
0 TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap) [Type]
argTys' [Name]
args
parenCommaArgs :: [Q Exp]
parenCommaArgs = (forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
singletonName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Char -> Q Exp
charE Char
'(')
forall a. a -> [a] -> [a]
: forall a. a -> [a] -> [a]
List.intersperse (forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
singletonName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Char -> Q Exp
charE Char
',') [Q Exp]
showArgs
mappendArgs :: Q Exp
mappendArgs = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr' (forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
`infixApp` [| (<>) |])
(forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
singletonName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Char -> Q Exp
charE Char
')')
[Q Exp]
parenCommaArgs
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match (forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
conName forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Pat
varP [Name]
args)
(forall (m :: * -> *). Quote m => m Exp -> m Body
normalB Q Exp
mappendArgs)
[]
else do
let showArgs :: [Q Exp]
showArgs = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Int
-> TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Type
-> Name
-> Q Exp
makeTextShowForArg Int
appPrec1 TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap) [Type]
argTys' [Name]
args
mappendArgs :: Q Exp
mappendArgs = forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 (\Q Exp
v Q Exp
q -> forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp Q Exp
v
[| (<>) |]
(forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (forall (m :: * -> *). Quote m => Name -> m Exp
varE forall a b. (a -> b) -> a -> b
$ TextShowFun -> Name
showSpaceName TextShowFun
tsFun)
[| (<>) |]
Q Exp
q)) [Q Exp]
showArgs
namedArgs :: Q Exp
namedArgs = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
fromStringName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => String -> m Exp
stringE (Name -> ShowS
parenInfixConName Name
conName String
" "))
[| (<>) |]
Q Exp
mappendArgs
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match (forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
conName forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Pat
varP [Name]
args)
(forall (m :: * -> *). Quote m => m Exp -> m Body
normalB forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
showParenName TextShowFun
tsFun)
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
p) [| (>) |] (Int -> Q Exp
integerE Int
appPrec)
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Q Exp
namedArgs)
[]
makeTextShowForCon Name
p TextShowClass
tsClass TextShowFun
tsFun Map Name (Name, Name)
tvMap
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
conName
, constructorVariant :: ConstructorInfo -> ConstructorVariant
constructorVariant = RecordConstructor [Name]
argNames
, constructorFields :: ConstructorInfo -> [Type]
constructorFields = [Type]
argTys }) = do
[Type]
argTys' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Type -> Q Type
resolveTypeSynonyms [Type]
argTys
[Name]
args <- String -> Int -> Q [Name]
newNameList String
"arg" forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
argTys'
let showArgs :: [Q Exp]
showArgs = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(Name
argName, Type
argTy, Name
arg)
-> let argNameBase :: String
argNameBase = Name -> String
nameBase Name
argName
infixRec :: String
infixRec = Bool -> ShowS -> ShowS
showParen (String -> Bool
isSymVar String
argNameBase)
(String -> ShowS
showString String
argNameBase) String
""
in [ forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
fromStringName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => String -> m Exp
stringE (String
infixRec forall a. [a] -> [a] -> [a]
++ String
" = ")
, Int
-> TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Type
-> Name
-> Q Exp
makeTextShowForArg Int
0 TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Type
argTy Name
arg
, forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
showCommaSpaceName TextShowFun
tsFun)
]
)
(forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [Name]
argNames [Type]
argTys' [Name]
args)
braceCommaArgs :: [Q Exp]
braceCommaArgs = (forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
singletonName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Char -> Q Exp
charE Char
'{') forall a. a -> [a] -> [a]
: forall a. Int -> [a] -> [a]
take (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Q Exp]
showArgs forall a. Num a => a -> a -> a
- Int
1) [Q Exp]
showArgs
mappendArgs :: Q Exp
mappendArgs = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr' (forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
`infixApp` [| (<>) |])
(forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
singletonName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Char -> Q Exp
charE Char
'}')
[Q Exp]
braceCommaArgs
namedArgs :: Q Exp
namedArgs = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
fromStringName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => String -> m Exp
stringE (Name -> ShowS
parenInfixConName Name
conName String
" "))
[| (<>) |]
Q Exp
mappendArgs
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match
(forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
conName forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Pat
varP [Name]
args)
(forall (m :: * -> *). Quote m => m Exp -> m Body
normalB forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
showParenName TextShowFun
tsFun)
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
p) [| (>) |] (Int -> Q Exp
integerE Int
appPrec)
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Q Exp
namedArgs)
[]
makeTextShowForCon Name
p TextShowClass
tsClass TextShowFun
tsFun Map Name (Name, Name)
tvMap
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
conName
, constructorVariant :: ConstructorInfo -> ConstructorVariant
constructorVariant = ConstructorVariant
InfixConstructor
, constructorFields :: ConstructorInfo -> [Type]
constructorFields = [Type]
argTys }) = do
[Type
alTy, Type
arTy] <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Type -> Q Type
resolveTypeSynonyms [Type]
argTys
Name
al <- forall (m :: * -> *). Quote m => String -> m Name
newName String
"argL"
Name
ar <- forall (m :: * -> *). Quote m => String -> m Name
newName String
"argR"
Fixity
fi <- forall a. a -> Maybe a -> a
fromMaybe Fixity
defaultFixity forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> Q (Maybe Fixity)
reifyFixityCompat Name
conName
let conPrec :: Int
conPrec = case Fixity
fi of Fixity Int
prec FixityDirection
_ -> Int
prec
opName :: String
opName = Name -> String
nameBase Name
conName
infixOpE :: Q Exp
infixOpE = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE forall a b. (a -> b) -> a -> b
$ TextShowFun -> Name
fromStringName TextShowFun
tsFun) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Quote m => String -> m Exp
stringE forall a b. (a -> b) -> a -> b
$
if String -> Bool
isInfixDataCon String
opName
then String
" " forall a. [a] -> [a] -> [a]
++ String
opName forall a. [a] -> [a] -> [a]
++ String
" "
else String
" `" forall a. [a] -> [a] -> [a]
++ String
opName forall a. [a] -> [a] -> [a]
++ String
"` "
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match
(forall (m :: * -> *). Quote m => m Pat -> Name -> m Pat -> m Pat
infixP (forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
al) Name
conName (forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
ar))
(forall (m :: * -> *). Quote m => m Exp -> m Body
normalB forall a b. (a -> b) -> a -> b
$ (forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
showParenName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
p) [| (>) |] (Int -> Q Exp
integerE Int
conPrec))
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` (forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (Int
-> TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Type
-> Name
-> Q Exp
makeTextShowForArg (Int
conPrec forall a. Num a => a -> a -> a
+ Int
1) TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Type
alTy Name
al)
[| (<>) |]
(forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp Q Exp
infixOpE
[| (<>) |]
(Int
-> TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Type
-> Name
-> Q Exp
makeTextShowForArg (Int
conPrec forall a. Num a => a -> a -> a
+ Int
1) TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Type
arTy Name
ar)))
)
[]
makeTextShowForArg :: Int
-> TextShowClass
-> TextShowFun
-> Name
-> TyVarMap
-> Type
-> Name
-> Q Exp
makeTextShowForArg :: Int
-> TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Type
-> Name
-> Q Exp
makeTextShowForArg Int
p TextShowClass
_ TextShowFun
tsFun Name
_ Map Name (Name, Name)
_ (ConT Name
tyName) Name
tyExpName =
Q Exp
showE
where
tyVarE, showPrecE :: Q Exp
tyVarE :: Q Exp
tyVarE = forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
tyExpName
showPrecE :: Q Exp
showPrecE = forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowClass -> TextShowFun -> Name
showPrecName TextShowClass
TextShow TextShowFun
tsFun)
showE :: Q Exp
showE :: Q Exp
showE =
case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
tyName Map Name PrimShow
primShowTbl of
Just PrimShow
ps -> PrimShow -> Q Exp
showPrimE PrimShow
ps
Maybe PrimShow
Nothing -> Q Exp
showPrecE forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Int -> Q Exp
integerE Int
p forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Q Exp
tyVarE
showPrimE :: PrimShow -> Q Exp
showPrimE :: PrimShow -> Q Exp
showPrimE PrimShow{ Q Exp -> Q Exp
primShowBoxer :: PrimShow -> Q Exp -> Q Exp
primShowBoxer :: Q Exp -> Q Exp
primShowBoxer
#if __GLASGOW_HASKELL__ >= 800
, TextShowFun -> Q Exp
primShowPostfixMod :: PrimShow -> TextShowFun -> Q Exp
primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod, TextShowFun -> Q Exp -> Q Exp
primShowConv :: PrimShow -> TextShowFun -> Q Exp -> Q Exp
primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv
#endif
}
#if __GLASGOW_HASKELL__ >= 800
= TextShowFun -> Q Exp -> Q Exp
primShowConv TextShowFun
tsFun forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (Int -> Q Exp
primE Int
0) [| (<>) |] (TextShowFun -> Q Exp
primShowPostfixMod TextShowFun
tsFun)
#else
= primE p
#endif
where
primE :: Int -> Q Exp
primE :: Int -> Q Exp
primE Int
prec = Q Exp
showPrecE forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Int -> Q Exp
integerE Int
prec forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Q Exp -> Q Exp
primShowBoxer Q Exp
tyVarE
makeTextShowForArg Int
p TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Type
ty Name
tyExpName =
[| $(makeTextShowForType tsClass tsFun conName tvMap False ty) p $(varE tyExpName) |]
makeTextShowForType :: TextShowClass
-> TextShowFun
-> Name
-> TyVarMap
-> Bool
-> Type
-> Q Exp
makeTextShowForType :: TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Bool
-> Type
-> Q Exp
makeTextShowForType TextShowClass
_ TextShowFun
tsFun Name
_ Map Name (Name, Name)
tvMap Bool
sl (VarT Name
tyName) =
forall (m :: * -> *). Quote m => Name -> m Exp
varE forall a b. (a -> b) -> a -> b
$ case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
tyName Map Name (Name, Name)
tvMap of
Just (Name
spExp, Name
slExp) -> if Bool
sl then Name
slExp else Name
spExp
Maybe (Name, Name)
Nothing -> if Bool
sl then TextShowClass -> TextShowFun -> Name
showListName TextShowClass
TextShow TextShowFun
tsFun
else TextShowClass -> TextShowFun -> Name
showPrecName TextShowClass
TextShow TextShowFun
tsFun
makeTextShowForType TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Bool
sl (SigT Type
ty Type
_) =
TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Bool
-> Type
-> Q Exp
makeTextShowForType TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Bool
sl Type
ty
makeTextShowForType TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Bool
sl (ForallT [TyVarBndr Specificity]
_ [Type]
_ Type
ty) =
TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Bool
-> Type
-> Q Exp
makeTextShowForType TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Bool
sl Type
ty
makeTextShowForType TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap Bool
sl Type
ty = do
let tyCon :: Type
tyArgs :: [Type]
Type
tyCon :| [Type]
tyArgs = Type -> NonEmpty Type
unapplyTy Type
ty
numLastArgs :: Int
numLastArgs :: Int
numLastArgs = forall a. Ord a => a -> a -> a
min (forall a. Enum a => a -> Int
fromEnum TextShowClass
tsClass) (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
tyArgs)
lhsArgs, rhsArgs :: [Type]
([Type]
lhsArgs, [Type]
rhsArgs) = forall a. Int -> [a] -> ([a], [a])
splitAt (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
tyArgs forall a. Num a => a -> a -> a
- Int
numLastArgs) [Type]
tyArgs
tyVarNames :: [Name]
tyVarNames :: [Name]
tyVarNames = forall k a. Map k a -> [k]
Map.keys Map Name (Name, Name)
tvMap
Bool
itf <- [Name] -> Type -> [Type] -> Q Bool
isInTypeFamilyApp [Name]
tyVarNames Type
tyCon [Type]
tyArgs
if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`mentionsName` [Name]
tyVarNames) [Type]
lhsArgs Bool -> Bool -> Bool
|| Bool
itf
then forall a. TextShowClass -> Name -> Q a
outOfPlaceTyVarError TextShowClass
tsClass Name
conName
else if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`mentionsName` [Name]
tyVarNames) [Type]
rhsArgs
then forall (m :: * -> *). Quote m => [m Exp] -> m Exp
appsE forall a b. (a -> b) -> a -> b
$ [ forall (m :: * -> *). Quote m => Name -> m Exp
varE forall a b. (a -> b) -> a -> b
$ Bool -> TextShowClass -> TextShowFun -> Name
showPrecOrListName Bool
sl (forall a. Enum a => Int -> a
toEnum Int
numLastArgs) TextShowFun
tsFun]
forall a. [a] -> [a] -> [a]
++ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (TextShowClass
-> TextShowFun
-> Name
-> Map Name (Name, Name)
-> Bool
-> Type
-> Q Exp
makeTextShowForType TextShowClass
tsClass TextShowFun
tsFun Name
conName Map Name (Name, Name)
tvMap)
(forall a. [a] -> [a]
cycle [Bool
False,Bool
True])
(forall a. [a] -> [a] -> [a]
interleave [Type]
rhsArgs [Type]
rhsArgs)
else forall (m :: * -> *). Quote m => Name -> m Exp
varE forall a b. (a -> b) -> a -> b
$ if Bool
sl then TextShowClass -> TextShowFun -> Name
showListName TextShowClass
TextShow TextShowFun
tsFun
else TextShowClass -> TextShowFun -> Name
showPrecName TextShowClass
TextShow TextShowFun
tsFun
buildTypeInstance :: TextShowClass
-> Name
-> Cxt
-> [Type]
-> DatatypeVariant
-> Q (Cxt, Type)
buildTypeInstance :: TextShowClass
-> Name -> [Type] -> [Type] -> DatatypeVariant -> Q ([Type], Type)
buildTypeInstance TextShowClass
tsClass Name
tyConName [Type]
dataCxt [Type]
varTysOrig DatatypeVariant
variant = do
[Type]
varTysExp <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Type -> Q Type
resolveTypeSynonyms [Type]
varTysOrig
let remainingLength :: Int
remainingLength :: Int
remainingLength = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
varTysOrig forall a. Num a => a -> a -> a
- forall a. Enum a => a -> Int
fromEnum TextShowClass
tsClass
droppedTysExp :: [Type]
droppedTysExp :: [Type]
droppedTysExp = forall a. Int -> [a] -> [a]
drop Int
remainingLength [Type]
varTysExp
droppedStarKindStati :: [StarKindStatus]
droppedStarKindStati :: [StarKindStatus]
droppedStarKindStati = forall a b. (a -> b) -> [a] -> [b]
map Type -> StarKindStatus
canRealizeKindStar [Type]
droppedTysExp
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
remainingLength forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => a -> a -> Bool
== StarKindStatus
NotKindStar) [StarKindStatus]
droppedStarKindStati) forall a b. (a -> b) -> a -> b
$
forall a. TextShowClass -> Name -> Q a
derivingKindError TextShowClass
tsClass Name
tyConName
let droppedKindVarNames :: [Name]
droppedKindVarNames :: [Name]
droppedKindVarNames = [StarKindStatus] -> [Name]
catKindVarNames [StarKindStatus]
droppedStarKindStati
varTysExpSubst :: [Type]
varTysExpSubst :: [Type]
varTysExpSubst = forall a b. (a -> b) -> [a] -> [b]
map ([Name] -> Type -> Type
substNamesWithKindStar [Name]
droppedKindVarNames) [Type]
varTysExp
remainingTysExpSubst, droppedTysExpSubst :: [Type]
([Type]
remainingTysExpSubst, [Type]
droppedTysExpSubst) =
forall a. Int -> [a] -> ([a], [a])
splitAt Int
remainingLength [Type]
varTysExpSubst
droppedTyVarNames :: [Name]
droppedTyVarNames :: [Name]
droppedTyVarNames = forall a. TypeSubstitution a => a -> [Name]
freeVariables [Type]
droppedTysExpSubst
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Type -> Bool
hasKindStar [Type]
droppedTysExpSubst) forall a b. (a -> b) -> a -> b
$
forall a. TextShowClass -> Name -> Q a
derivingKindError TextShowClass
tsClass Name
tyConName
let preds :: [Maybe Pred]
kvNames :: [[Name]]
kvNames' :: [Name]
([Maybe Type]
preds, [[Name]]
kvNames) = forall a b. [(a, b)] -> ([a], [b])
unzip forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (TextShowClass -> Type -> (Maybe Type, [Name])
deriveConstraint TextShowClass
tsClass) [Type]
remainingTysExpSubst
kvNames' :: [Name]
kvNames' = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Name]]
kvNames
remainingTysExpSubst' :: [Type]
remainingTysExpSubst' :: [Type]
remainingTysExpSubst' =
forall a b. (a -> b) -> [a] -> [b]
map ([Name] -> Type -> Type
substNamesWithKindStar [Name]
kvNames') [Type]
remainingTysExpSubst
remainingTysOrigSubst :: [Type]
remainingTysOrigSubst :: [Type]
remainingTysOrigSubst =
forall a b. (a -> b) -> [a] -> [b]
map ([Name] -> Type -> Type
substNamesWithKindStar (forall a. Eq a => [a] -> [a] -> [a]
List.union [Name]
droppedKindVarNames [Name]
kvNames'))
forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
take Int
remainingLength [Type]
varTysOrig
isDataFamily :: Bool
isDataFamily :: Bool
isDataFamily = case DatatypeVariant
variant of
DatatypeVariant
Datatype -> Bool
False
DatatypeVariant
Newtype -> Bool
False
DatatypeVariant
DataInstance -> Bool
True
DatatypeVariant
NewtypeInstance -> Bool
True
remainingTysOrigSubst' :: [Type]
remainingTysOrigSubst' :: [Type]
remainingTysOrigSubst' =
if Bool
isDataFamily
then [Type]
remainingTysOrigSubst
else forall a b. (a -> b) -> [a] -> [b]
map Type -> Type
unSigT [Type]
remainingTysOrigSubst
instanceCxt :: Cxt
instanceCxt :: [Type]
instanceCxt = forall a. [Maybe a] -> [a]
catMaybes [Maybe Type]
preds
instanceType :: Type
instanceType :: Type
instanceType = Type -> Type -> Type
AppT (Name -> Type
ConT forall a b. (a -> b) -> a -> b
$ TextShowClass -> Name
textShowClassName TextShowClass
tsClass)
forall a b. (a -> b) -> a -> b
$ Name -> [Type] -> Type
applyTyCon Name
tyConName [Type]
remainingTysOrigSubst'
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`predMentionsName` [Name]
droppedTyVarNames) [Type]
dataCxt) forall a b. (a -> b) -> a -> b
$
forall a. Name -> Type -> Q a
datatypeContextError Name
tyConName Type
instanceType
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Type] -> [Type] -> Bool
canEtaReduce [Type]
remainingTysExpSubst' [Type]
droppedTysExpSubst) forall a b. (a -> b) -> a -> b
$
forall a. Type -> Q a
etaReductionError Type
instanceType
forall (m :: * -> *) a. Monad m => a -> m a
return ([Type]
instanceCxt, Type
instanceType)
deriveConstraint :: TextShowClass -> Type -> (Maybe Pred, [Name])
deriveConstraint :: TextShowClass -> Type -> (Maybe Type, [Name])
deriveConstraint TextShowClass
tsClass Type
t
| Bool -> Bool
not (Type -> Bool
isTyVar Type
t) = (forall a. Maybe a
Nothing, [])
| Type -> Bool
hasKindStar Type
t = (forall a. a -> Maybe a
Just (Name -> Name -> Type
applyClass ''TextShow Name
tName), [])
| Bool
otherwise = case Int -> Type -> Maybe [Name]
hasKindVarChain Int
1 Type
t of
Just [Name]
ns | TextShowClass
tsClass forall a. Ord a => a -> a -> Bool
>= TextShowClass
TextShow1
-> (forall a. a -> Maybe a
Just (Name -> Name -> Type
applyClass ''TextShow1 Name
tName), [Name]
ns)
Maybe [Name]
_ -> case Int -> Type -> Maybe [Name]
hasKindVarChain Int
2 Type
t of
Just [Name]
ns | TextShowClass
tsClass forall a. Eq a => a -> a -> Bool
== TextShowClass
TextShow2
-> (forall a. a -> Maybe a
Just (Name -> Name -> Type
applyClass ''TextShow2 Name
tName), [Name]
ns)
Maybe [Name]
_ -> (forall a. Maybe a
Nothing, [])
where
tName :: Name
tName :: Name
tName = Type -> Name
varTToName Type
t
derivingKindError :: TextShowClass -> Name -> Q a
derivingKindError :: forall a. TextShowClass -> Name -> Q a
derivingKindError TextShowClass
tsClass Name
tyConName = forall (m :: * -> *) a. MonadFail m => String -> m a
Monad.fail
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"Cannot derive well-kinded instance of form ‘"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
className
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ShowS -> ShowS
showParen Bool
True
( String -> ShowS
showString (Name -> String
nameBase Name
tyConName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" ..."
)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"‘\n\tClass "
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
className
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" expects an argument of kind "
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (forall a. Ppr a => a -> String
pprint forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Type
createKindChain forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum TextShowClass
tsClass)
forall a b. (a -> b) -> a -> b
$ String
""
where
className :: String
className :: String
className = Name -> String
nameBase forall a b. (a -> b) -> a -> b
$ TextShowClass -> Name
textShowClassName TextShowClass
tsClass
etaReductionError :: Type -> Q a
etaReductionError :: forall a. Type -> Q a
etaReductionError Type
instanceType = forall (m :: * -> *) a. MonadFail m => String -> m a
Monad.fail forall a b. (a -> b) -> a -> b
$
String
"Cannot eta-reduce to an instance of form \n\tinstance (...) => "
forall a. [a] -> [a] -> [a]
++ forall a. Ppr a => a -> String
pprint Type
instanceType
datatypeContextError :: Name -> Type -> Q a
datatypeContextError :: forall a. Name -> Type -> Q a
datatypeContextError Name
dataName Type
instanceType = forall (m :: * -> *) a. MonadFail m => String -> m a
Monad.fail
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"Can't make a derived instance of ‘"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (forall a. Ppr a => a -> String
pprint Type
instanceType)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"‘:\n\tData type ‘"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Name -> String
nameBase Name
dataName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"‘ must not have a class context involving the last type argument(s)"
forall a b. (a -> b) -> a -> b
$ String
""
outOfPlaceTyVarError :: TextShowClass -> Name -> Q a
outOfPlaceTyVarError :: forall a. TextShowClass -> Name -> Q a
outOfPlaceTyVarError TextShowClass
tsClass Name
conName = forall (m :: * -> *) a. MonadFail m => String -> m a
Monad.fail
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"Constructor ‘"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Name -> String
nameBase Name
conName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"‘ must only use its last "
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows Int
n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" type variable(s) within the last "
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> ShowS
shows Int
n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" argument(s) of a data type"
forall a b. (a -> b) -> a -> b
$ String
""
where
n :: Int
n :: Int
n = forall a. Enum a => a -> Int
fromEnum TextShowClass
tsClass
substNameWithKind :: Name -> Kind -> Type -> Type
substNameWithKind :: Name -> Type -> Type -> Type
substNameWithKind Name
n Type
k = forall a. TypeSubstitution a => Map Name Type -> a -> a
applySubstitution (forall k a. k -> a -> Map k a
Map.singleton Name
n Type
k)
substNamesWithKindStar :: [Name] -> Type -> Type
substNamesWithKindStar :: [Name] -> Type -> Type
substNamesWithKindStar [Name]
ns Type
t = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr' (forall a b c. (a -> b -> c) -> b -> a -> c
flip Name -> Type -> Type -> Type
substNameWithKind Type
starK) Type
t [Name]
ns
data TextShowClass = TextShow | TextShow1 | TextShow2
deriving (Int -> TextShowClass
TextShowClass -> Int
TextShowClass -> [TextShowClass]
TextShowClass -> TextShowClass
TextShowClass -> TextShowClass -> [TextShowClass]
TextShowClass -> TextShowClass -> TextShowClass -> [TextShowClass]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TextShowClass -> TextShowClass -> TextShowClass -> [TextShowClass]
$cenumFromThenTo :: TextShowClass -> TextShowClass -> TextShowClass -> [TextShowClass]
enumFromTo :: TextShowClass -> TextShowClass -> [TextShowClass]
$cenumFromTo :: TextShowClass -> TextShowClass -> [TextShowClass]
enumFromThen :: TextShowClass -> TextShowClass -> [TextShowClass]
$cenumFromThen :: TextShowClass -> TextShowClass -> [TextShowClass]
enumFrom :: TextShowClass -> [TextShowClass]
$cenumFrom :: TextShowClass -> [TextShowClass]
fromEnum :: TextShowClass -> Int
$cfromEnum :: TextShowClass -> Int
toEnum :: Int -> TextShowClass
$ctoEnum :: Int -> TextShowClass
pred :: TextShowClass -> TextShowClass
$cpred :: TextShowClass -> TextShowClass
succ :: TextShowClass -> TextShowClass
$csucc :: TextShowClass -> TextShowClass
Enum, TextShowClass -> TextShowClass -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextShowClass -> TextShowClass -> Bool
$c/= :: TextShowClass -> TextShowClass -> Bool
== :: TextShowClass -> TextShowClass -> Bool
$c== :: TextShowClass -> TextShowClass -> Bool
Eq, Eq TextShowClass
TextShowClass -> TextShowClass -> Bool
TextShowClass -> TextShowClass -> Ordering
TextShowClass -> TextShowClass -> TextShowClass
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 :: TextShowClass -> TextShowClass -> TextShowClass
$cmin :: TextShowClass -> TextShowClass -> TextShowClass
max :: TextShowClass -> TextShowClass -> TextShowClass
$cmax :: TextShowClass -> TextShowClass -> TextShowClass
>= :: TextShowClass -> TextShowClass -> Bool
$c>= :: TextShowClass -> TextShowClass -> Bool
> :: TextShowClass -> TextShowClass -> Bool
$c> :: TextShowClass -> TextShowClass -> Bool
<= :: TextShowClass -> TextShowClass -> Bool
$c<= :: TextShowClass -> TextShowClass -> Bool
< :: TextShowClass -> TextShowClass -> Bool
$c< :: TextShowClass -> TextShowClass -> Bool
compare :: TextShowClass -> TextShowClass -> Ordering
$ccompare :: TextShowClass -> TextShowClass -> Ordering
Ord)
data TextShowFun = ShowbPrec | ShowtPrec | ShowtlPrec
fromStringName :: TextShowFun -> Name
fromStringName :: TextShowFun -> Name
fromStringName TextShowFun
ShowbPrec = 'TB.fromString
fromStringName TextShowFun
ShowtPrec = 'TS.pack
fromStringName TextShowFun
ShowtlPrec = 'TL.pack
singletonName :: TextShowFun -> Name
singletonName :: TextShowFun -> Name
singletonName TextShowFun
ShowbPrec = 'TB.singleton
singletonName TextShowFun
ShowtPrec = 'TS.singleton
singletonName TextShowFun
ShowtlPrec = 'TL.singleton
showParenName :: TextShowFun -> Name
showParenName :: TextShowFun -> Name
showParenName TextShowFun
ShowbPrec = 'showbParen
showParenName TextShowFun
ShowtPrec = 'showtParen
showParenName TextShowFun
ShowtlPrec = 'showtlParen
showCommaSpaceName :: TextShowFun -> Name
showCommaSpaceName :: TextShowFun -> Name
showCommaSpaceName TextShowFun
ShowbPrec = 'showbCommaSpace
showCommaSpaceName TextShowFun
ShowtPrec = 'showtCommaSpace
showCommaSpaceName TextShowFun
ShowtlPrec = 'showtlCommaSpace
showSpaceName :: TextShowFun -> Name
showSpaceName :: TextShowFun -> Name
showSpaceName TextShowFun
ShowbPrec = 'showbSpace
showSpaceName TextShowFun
ShowtPrec = 'showtSpace
showSpaceName TextShowFun
ShowtlPrec = 'showtlSpace
showPrecConstName :: TextShowClass -> TextShowFun -> Name
showPrecConstName :: TextShowClass -> TextShowFun -> Name
showPrecConstName TextShowClass
tsClass TextShowFun
ShowbPrec = TextShowClass -> Name
showbPrecConstName TextShowClass
tsClass
showPrecConstName TextShowClass
TextShow TextShowFun
ShowtPrec = 'showtPrecConst
showPrecConstName TextShowClass
TextShow TextShowFun
ShowtlPrec = 'showtlPrecConst
showPrecConstName TextShowClass
_ TextShowFun
_ = forall a. HasCallStack => String -> a
error String
"showPrecConstName"
showbPrecConstName :: TextShowClass -> Name
showbPrecConstName :: TextShowClass -> Name
showbPrecConstName TextShowClass
TextShow = 'showbPrecConst
showbPrecConstName TextShowClass
TextShow1 = 'liftShowbPrecConst
showbPrecConstName TextShowClass
TextShow2 = 'liftShowbPrec2Const
textShowClassName :: TextShowClass -> Name
textShowClassName :: TextShowClass -> Name
textShowClassName TextShowClass
TextShow = ''TextShow
textShowClassName TextShowClass
TextShow1 = ''TextShow1
textShowClassName TextShowClass
TextShow2 = ''TextShow2
showPrecName :: TextShowClass -> TextShowFun -> Name
showPrecName :: TextShowClass -> TextShowFun -> Name
showPrecName TextShowClass
tsClass TextShowFun
ShowbPrec = TextShowClass -> Name
showbPrecName TextShowClass
tsClass
showPrecName TextShowClass
TextShow TextShowFun
ShowtPrec = 'showtPrec
showPrecName TextShowClass
TextShow TextShowFun
ShowtlPrec = 'showtlPrec
showPrecName TextShowClass
_ TextShowFun
_ = forall a. HasCallStack => String -> a
error String
"showPrecName"
showbPrecName :: TextShowClass -> Name
showbPrecName :: TextShowClass -> Name
showbPrecName TextShowClass
TextShow = 'showbPrec
showbPrecName TextShowClass
TextShow1 = 'liftShowbPrec
showbPrecName TextShowClass
TextShow2 = 'liftShowbPrec2
showListName :: TextShowClass -> TextShowFun -> Name
showListName :: TextShowClass -> TextShowFun -> Name
showListName TextShowClass
tsClass TextShowFun
ShowbPrec = TextShowClass -> Name
showbListName TextShowClass
tsClass
showListName TextShowClass
TextShow TextShowFun
ShowtPrec = 'showtPrec
showListName TextShowClass
TextShow TextShowFun
ShowtlPrec = 'showtlPrec
showListName TextShowClass
_ TextShowFun
_ = forall a. HasCallStack => String -> a
error String
"showListName"
showbListName :: TextShowClass -> Name
showbListName :: TextShowClass -> Name
showbListName TextShowClass
TextShow = 'showbList
showbListName TextShowClass
TextShow1 = 'liftShowbList
showbListName TextShowClass
TextShow2 = 'liftShowbList2
showPrecOrListName :: Bool
-> TextShowClass
-> TextShowFun
-> Name
showPrecOrListName :: Bool -> TextShowClass -> TextShowFun -> Name
showPrecOrListName Bool
False = TextShowClass -> TextShowFun -> Name
showPrecName
showPrecOrListName Bool
True = TextShowClass -> TextShowFun -> Name
showListName
showbPrecConst :: Builder
-> Int -> a -> Builder
showbPrecConst :: forall a. Builder -> Int -> a -> Builder
showbPrecConst Builder
b Int
_ a
_ = Builder
b
showtPrecConst :: TS.Text
-> Int -> a -> TS.Text
showtPrecConst :: forall a. Text -> Int -> a -> Text
showtPrecConst Text
t Int
_ a
_ = Text
t
showtlPrecConst :: TL.Text
-> Int -> a -> TL.Text
showtlPrecConst :: forall a. Text -> Int -> a -> Text
showtlPrecConst Text
tl Int
_ a
_ = Text
tl
liftShowbPrecConst :: Builder
-> (Int -> a -> Builder) -> ([a] -> Builder)
-> Int -> f a -> Builder
liftShowbPrecConst :: forall a (f :: * -> *).
Builder
-> (Int -> a -> Builder)
-> ([a] -> Builder)
-> Int
-> f a
-> Builder
liftShowbPrecConst Builder
b Int -> a -> Builder
_ [a] -> Builder
_ Int
_ f a
_ = Builder
b
liftShowbPrec2Const :: Builder
-> (Int -> a -> Builder) -> ([a] -> Builder)
-> (Int -> b -> Builder) -> ([b] -> Builder)
-> Int -> f a b -> Builder
liftShowbPrec2Const :: forall a b (f :: * -> * -> *).
Builder
-> (Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
liftShowbPrec2Const Builder
b Int -> a -> Builder
_ [a] -> Builder
_ Int -> b -> Builder
_ [b] -> Builder
_ Int
_ f a b
_ = Builder
b
data StarKindStatus = NotKindStar
| KindStar
| IsKindVar Name
deriving StarKindStatus -> StarKindStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StarKindStatus -> StarKindStatus -> Bool
$c/= :: StarKindStatus -> StarKindStatus -> Bool
== :: StarKindStatus -> StarKindStatus -> Bool
$c== :: StarKindStatus -> StarKindStatus -> Bool
Eq
canRealizeKindStar :: Type -> StarKindStatus
canRealizeKindStar :: Type -> StarKindStatus
canRealizeKindStar Type
t
| Type -> Bool
hasKindStar Type
t = StarKindStatus
KindStar
| Bool
otherwise = case Type
t of
SigT Type
_ (VarT Name
k) -> Name -> StarKindStatus
IsKindVar Name
k
Type
_ -> StarKindStatus
NotKindStar
starKindStatusToName :: StarKindStatus -> Maybe Name
starKindStatusToName :: StarKindStatus -> Maybe Name
starKindStatusToName (IsKindVar Name
n) = forall a. a -> Maybe a
Just Name
n
starKindStatusToName StarKindStatus
_ = forall a. Maybe a
Nothing
catKindVarNames :: [StarKindStatus] -> [Name]
catKindVarNames :: [StarKindStatus] -> [Name]
catKindVarNames = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe StarKindStatus -> Maybe Name
starKindStatusToName
data PrimShow = PrimShow
{ PrimShow -> Q Exp -> Q Exp
primShowBoxer :: Q Exp -> Q Exp
, PrimShow -> TextShowFun -> Q Exp
primShowPostfixMod :: TextShowFun -> Q Exp
, PrimShow -> TextShowFun -> Q Exp -> Q Exp
primShowConv :: TextShowFun -> Q Exp -> Q Exp
}
primShowTbl :: Map Name PrimShow
primShowTbl :: Map Name PrimShow
primShowTbl = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
[ (''Char#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'C#)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
oneHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = \TextShowFun
_ Q Exp
x -> Q Exp
x
})
, (''Double#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'D#)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
twoHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = \TextShowFun
_ Q Exp
x -> Q Exp
x
})
, (''Float#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'F#)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
oneHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = \TextShowFun
_ Q Exp
x -> Q Exp
x
})
, (''Int#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'I#)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
oneHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = \TextShowFun
_ Q Exp
x -> Q Exp
x
})
, (''Word#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'W#)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
twoHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = \TextShowFun
_ Q Exp
x -> Q Exp
x
})
#if MIN_VERSION_base(4,13,0)
, (''Int8#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'I#) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
int8ToIntHashValName)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
oneHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = Name -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE Name
intToInt8HashValName
})
, (''Int16#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'I#) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
int16ToIntHashValName)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
oneHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = Name -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE Name
intToInt16HashValName
})
, (''Word8#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'W#) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
word8ToWordHashValName)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
twoHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = Name -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE Name
wordToWord8HashValName
})
, (''Word16#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'W#) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
word16ToWordHashValName)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
twoHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = Name -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE Name
wordToWord16HashValName
})
#endif
#if MIN_VERSION_base(4,16,0)
, (''Int32#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'I#) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE 'int32ToInt#)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
oneHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = Name -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE 'intToInt32#
})
, (''Word32#, PrimShow
{ primShowBoxer :: Q Exp -> Q Exp
primShowBoxer = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
conE 'W#) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE 'word32ToWord#)
, primShowPostfixMod :: TextShowFun -> Q Exp
primShowPostfixMod = TextShowFun -> Q Exp
twoHashE
, primShowConv :: TextShowFun -> Q Exp -> Q Exp
primShowConv = Name -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE 'wordToWord32#
})
#endif
]
#if MIN_VERSION_base(4,13,0)
mkNarrowE :: Name -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE :: Name -> TextShowFun -> Q Exp -> Q Exp
mkNarrowE Name
narrowName TextShowFun
tsFun Q Exp
e =
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
`infixApp` [| (<>) |])
(forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
singletonName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Char -> Q Exp
charE Char
')')
[ forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
fromStringName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => String -> m Exp
stringE (Char
'('forall a. a -> [a] -> [a]
:Name -> String
nameBase Name
narrowName forall a. [a] -> [a] -> [a]
++ String
" ")
, Q Exp
e
]
int8ToIntHashValName :: Name
int8ToIntHashValName :: Name
int8ToIntHashValName =
# if MIN_VERSION_base(4,16,0)
'int8ToInt#
# else
'extendInt8#
# endif
int16ToIntHashValName :: Name
int16ToIntHashValName :: Name
int16ToIntHashValName =
# if MIN_VERSION_base(4,16,0)
'int16ToInt#
# else
'extendInt16#
# endif
intToInt8HashValName :: Name
intToInt8HashValName :: Name
intToInt8HashValName =
# if MIN_VERSION_base(4,16,0)
'intToInt8#
# else
'narrowInt8#
# endif
intToInt16HashValName :: Name
intToInt16HashValName :: Name
intToInt16HashValName =
# if MIN_VERSION_base(4,16,0)
'intToInt16#
# else
'narrowInt16#
# endif
word8ToWordHashValName :: Name
word8ToWordHashValName :: Name
word8ToWordHashValName =
# if MIN_VERSION_base(4,16,0)
'word8ToWord#
# else
'extendWord8#
# endif
word16ToWordHashValName :: Name
word16ToWordHashValName :: Name
word16ToWordHashValName =
# if MIN_VERSION_base(4,16,0)
'word16ToWord#
# else
'extendWord16#
# endif
wordToWord8HashValName :: Name
wordToWord8HashValName :: Name
wordToWord8HashValName =
# if MIN_VERSION_base(4,16,0)
'wordToWord8#
# else
'narrowWord8#
# endif
wordToWord16HashValName :: Name
wordToWord16HashValName :: Name
wordToWord16HashValName =
# if MIN_VERSION_base(4,16,0)
'wordToWord16#
# else
'narrowWord16#
# endif
#endif
oneHashE, twoHashE :: TextShowFun -> Q Exp
oneHashE :: TextShowFun -> Q Exp
oneHashE TextShowFun
tsFun = forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
singletonName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Char -> Q Exp
charE Char
'#'
twoHashE :: TextShowFun -> Q Exp
twoHashE TextShowFun
tsFun = forall (m :: * -> *). Quote m => Name -> m Exp
varE (TextShowFun -> Name
fromStringName TextShowFun
tsFun) forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` forall (m :: * -> *). Quote m => String -> m Exp
stringE String
"##"
integerE :: Int -> Q Exp
integerE :: Int -> Q Exp
integerE = forall (m :: * -> *). Quote m => Lit -> m Exp
litE forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Lit
integerL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
charE :: Char -> Q Exp
charE :: Char -> Q Exp
charE = forall (m :: * -> *). Quote m => Lit -> m Exp
litE forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Lit
charL
hasKindStar :: Type -> Bool
hasKindStar :: Type -> Bool
hasKindStar VarT{} = Bool
True
hasKindStar (SigT Type
_ Type
StarT) = Bool
True
hasKindStar Type
_ = Bool
False
isStarOrVar :: Kind -> Bool
isStarOrVar :: Type -> Bool
isStarOrVar Type
StarT = Bool
True
isStarOrVar VarT{} = Bool
True
isStarOrVar Type
_ = Bool
False
newNameList :: String -> Int -> Q [Name]
newNameList :: String -> Int -> Q [Name]
newNameList String
prefix Int
n = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *). Quote m => String -> m Name
newName forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
prefix forall a. [a] -> [a] -> [a]
++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show) [Int
1..Int
n]
hasKindVarChain :: Int -> Type -> Maybe [Name]
hasKindVarChain :: Int -> Type -> Maybe [Name]
hasKindVarChain Int
kindArrows Type
t =
let uk :: NonEmpty Type
uk = Type -> NonEmpty Type
uncurryTy (Type -> Type
tyKind Type
t)
in if (forall (t :: * -> *) a. Foldable t => t a -> Int
length NonEmpty Type
uk forall a. Num a => a -> a -> a
- Int
1 forall a. Eq a => a -> a -> Bool
== Int
kindArrows) Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Type -> Bool
isStarOrVar NonEmpty Type
uk
then forall a. a -> Maybe a
Just (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. TypeSubstitution a => a -> [Name]
freeVariables NonEmpty Type
uk)
else forall a. Maybe a
Nothing
tyKind :: Type -> Kind
tyKind :: Type -> Type
tyKind (SigT Type
_ Type
k) = Type
k
tyKind Type
_ = Type
starK
type TyVarMap = Map Name (Name, Name)
isNonUnitTuple :: Name -> Bool
isNonUnitTuple :: Name -> Bool
isNonUnitTuple = String -> Bool
isTupleString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase
parenInfixConName :: Name -> ShowS
parenInfixConName :: Name -> ShowS
parenInfixConName Name
conName =
let conNameBase :: String
conNameBase = Name -> String
nameBase Name
conName
in Bool -> ShowS -> ShowS
showParen (String -> Bool
isInfixDataCon String
conNameBase) forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
conNameBase
applyClass :: Name -> Name -> Pred
#if MIN_VERSION_template_haskell(2,10,0)
applyClass :: Name -> Name -> Type
applyClass Name
con Name
t = Type -> Type -> Type
AppT (Name -> Type
ConT Name
con) (Name -> Type
VarT Name
t)
#else
applyClass con t = ClassP con [VarT t]
#endif
canEtaReduce :: [Type] -> [Type] -> Bool
canEtaReduce :: [Type] -> [Type] -> Bool
canEtaReduce [Type]
remaining [Type]
dropped =
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Type -> Bool
isTyVar [Type]
dropped
Bool -> Bool -> Bool
&& forall a. Ord a => [a] -> Bool
allDistinct [Name]
droppedNames
Bool -> Bool -> Bool
&& Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`mentionsName` [Name]
droppedNames) [Type]
remaining)
where
droppedNames :: [Name]
droppedNames :: [Name]
droppedNames = forall a b. (a -> b) -> [a] -> [b]
map Type -> Name
varTToName [Type]
dropped
varTToName_maybe :: Type -> Maybe Name
varTToName_maybe :: Type -> Maybe Name
varTToName_maybe (VarT Name
n) = forall a. a -> Maybe a
Just Name
n
varTToName_maybe (SigT Type
t Type
_) = Type -> Maybe Name
varTToName_maybe Type
t
varTToName_maybe Type
_ = forall a. Maybe a
Nothing
varTToName :: Type -> Name
varTToName :: Type -> Name
varTToName = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"Not a type variable!") forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Maybe Name
varTToName_maybe
unSigT :: Type -> Type
unSigT :: Type -> Type
unSigT (SigT Type
t Type
_) = Type
t
unSigT Type
t = Type
t
isTyVar :: Type -> Bool
isTyVar :: Type -> Bool
isTyVar (VarT Name
_) = Bool
True
isTyVar (SigT Type
t Type
_) = Type -> Bool
isTyVar Type
t
isTyVar Type
_ = Bool
False
isInTypeFamilyApp :: [Name] -> Type -> [Type] -> Q Bool
isInTypeFamilyApp :: [Name] -> Type -> [Type] -> Q Bool
isInTypeFamilyApp [Name]
names Type
tyFun [Type]
tyArgs =
case Type
tyFun of
ConT Name
tcName -> Name -> Q Bool
go Name
tcName
Type
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
where
go :: Name -> Q Bool
go :: Name -> Q Bool
go Name
tcName = do
Info
info <- Name -> Q Info
reify Name
tcName
case Info
info of
#if MIN_VERSION_template_haskell(2,11,0)
FamilyI (OpenTypeFamilyD (TypeFamilyHead Name
_ [TyVarBndr ()]
bndrs FamilyResultSig
_ Maybe InjectivityAnn
_)) [Dec]
_
-> forall a. [a] -> Q Bool
withinFirstArgs [TyVarBndr ()]
bndrs
#else
FamilyI (FamilyD TypeFam _ bndrs _) _
-> withinFirstArgs bndrs
#endif
#if MIN_VERSION_template_haskell(2,11,0)
FamilyI (ClosedTypeFamilyD (TypeFamilyHead Name
_ [TyVarBndr ()]
bndrs FamilyResultSig
_ Maybe InjectivityAnn
_) [TySynEqn]
_) [Dec]
_
-> forall a. [a] -> Q Bool
withinFirstArgs [TyVarBndr ()]
bndrs
#else
FamilyI (ClosedTypeFamilyD _ bndrs _ _) _
-> withinFirstArgs bndrs
#endif
Info
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
where
withinFirstArgs :: [a] -> Q Bool
withinFirstArgs :: forall a. [a] -> Q Bool
withinFirstArgs [a]
bndrs =
let firstArgs :: [Type]
firstArgs = forall a. Int -> [a] -> [a]
take (forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
bndrs) [Type]
tyArgs
argFVs :: [Name]
argFVs = forall a. TypeSubstitution a => a -> [Name]
freeVariables [Type]
firstArgs
in forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Name]
argFVs) [Name]
names
allDistinct :: Ord a => [a] -> Bool
allDistinct :: forall a. Ord a => [a] -> Bool
allDistinct = forall a. Ord a => Set a -> [a] -> Bool
allDistinct' forall a. Set a
Set.empty
where
allDistinct' :: Ord a => Set a -> [a] -> Bool
allDistinct' :: forall a. Ord a => Set a -> [a] -> Bool
allDistinct' Set a
uniqs (a
x:[a]
xs)
| a
x forall a. Ord a => a -> Set a -> Bool
`Set.member` Set a
uniqs = Bool
False
| Bool
otherwise = forall a. Ord a => Set a -> [a] -> Bool
allDistinct' (forall a. Ord a => a -> Set a -> Set a
Set.insert a
x Set a
uniqs) [a]
xs
allDistinct' Set a
_ [a]
_ = Bool
True
mentionsName :: Type -> [Name] -> Bool
mentionsName :: Type -> [Name] -> Bool
mentionsName = Type -> [Name] -> Bool
go
where
go :: Type -> [Name] -> Bool
go :: Type -> [Name] -> Bool
go (AppT Type
t1 Type
t2) [Name]
names = Type -> [Name] -> Bool
go Type
t1 [Name]
names Bool -> Bool -> Bool
|| Type -> [Name] -> Bool
go Type
t2 [Name]
names
go (SigT Type
t Type
k) [Name]
names = Type -> [Name] -> Bool
go Type
t [Name]
names Bool -> Bool -> Bool
|| Type -> [Name] -> Bool
go Type
k [Name]
names
go (VarT Name
n) [Name]
names = Name
n forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Name]
names
go Type
_ [Name]
_ = Bool
False
predMentionsName :: Pred -> [Name] -> Bool
#if MIN_VERSION_template_haskell(2,10,0)
predMentionsName :: Type -> [Name] -> Bool
predMentionsName = Type -> [Name] -> Bool
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 :: Type -> [Type] -> Type
applyTy = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Type -> Type -> Type
AppT
applyTyCon :: Name -> [Type] -> Type
applyTyCon :: Name -> [Type] -> Type
applyTyCon = Type -> [Type] -> Type
applyTy forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Type
ConT
unapplyTy :: Type -> NonEmpty Type
unapplyTy :: Type -> NonEmpty Type
unapplyTy Type
ty = Type -> Type -> [Type] -> NonEmpty Type
go Type
ty Type
ty []
where
go :: Type -> Type -> [Type] -> NonEmpty Type
go :: Type -> Type -> [Type] -> NonEmpty Type
go Type
_ (AppT Type
ty1 Type
ty2) [Type]
args = Type -> Type -> [Type] -> NonEmpty Type
go Type
ty1 Type
ty1 (Type
ty2forall a. a -> [a] -> [a]
:[Type]
args)
go Type
origTy (SigT Type
ty' Type
_) [Type]
args = Type -> Type -> [Type] -> NonEmpty Type
go Type
origTy Type
ty' [Type]
args
#if MIN_VERSION_template_haskell(2,11,0)
go Type
origTy (InfixT Type
ty1 Name
n Type
ty2) [Type]
args = Type -> Type -> [Type] -> NonEmpty Type
go Type
origTy (Name -> Type
ConT Name
n Type -> Type -> Type
`AppT` Type
ty1 Type -> Type -> Type
`AppT` Type
ty2) [Type]
args
go Type
origTy (ParensT Type
ty') [Type]
args = Type -> Type -> [Type] -> NonEmpty Type
go Type
origTy Type
ty' [Type]
args
#endif
go Type
origTy Type
_ [Type]
args = Type
origTy forall a. a -> [a] -> NonEmpty a
:| [Type]
args
uncurryTy :: Type -> NonEmpty Type
uncurryTy :: Type -> NonEmpty Type
uncurryTy (AppT (AppT Type
ArrowT Type
t1) Type
t2) = Type
t1 forall a. a -> NonEmpty a -> NonEmpty a
<| Type -> NonEmpty Type
uncurryTy Type
t2
uncurryTy (SigT Type
t Type
_) = Type -> NonEmpty Type
uncurryTy Type
t
uncurryTy (ForallT [TyVarBndr Specificity]
_ [Type]
_ Type
t) = Type -> NonEmpty Type
uncurryTy Type
t
uncurryTy Type
t = Type
t forall a. a -> [a] -> NonEmpty a
:| []
createKindChain :: Int -> Kind
createKindChain :: Int -> Type
createKindChain = Type -> Int -> Type
go Type
starK
where
go :: Kind -> Int -> Kind
go :: Type -> Int -> Type
go Type
k !Int
0 = Type
k
go Type
k !Int
n = Type -> Int -> Type
go (Type -> Type -> Type
arrowKCompat Type
starK Type
k) (Int
n forall a. Num a => a -> a -> a
- Int
1)
isNullaryCon :: ConstructorInfo -> Bool
isNullaryCon :: ConstructorInfo -> Bool
isNullaryCon (ConstructorInfo { constructorFields :: ConstructorInfo -> [Type]
constructorFields = [] }) = Bool
True
isNullaryCon ConstructorInfo
_ = Bool
False
interleave :: [a] -> [a] -> [a]
interleave :: forall a. [a] -> [a] -> [a]
interleave (a
a1:[a]
a1s) (a
a2:[a]
a2s) = a
a1forall a. a -> [a] -> [a]
:a
a2forall a. a -> [a] -> [a]
:forall a. [a] -> [a] -> [a]
interleave [a]
a1s [a]
a2s
interleave [a]
_ [a]
_ = []