{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DeriveTraversable #-}
module GHC.Iface.Syntax (
module GHC.Iface.Type,
IfaceDecl(..), IfaceFamTyConFlav(..), IfaceClassOp(..), IfaceAT(..),
IfaceConDecl(..), IfaceConDecls(..), IfaceEqSpec,
IfaceExpr(..), IfaceAlt(..), IfaceLetBndr(..), IfaceBinding,
IfaceBindingX(..), IfaceMaybeRhs(..), IfaceConAlt(..),
IfaceIdInfo, IfaceIdDetails(..), IfaceUnfolding(..), IfGuidance(..),
IfaceInfoItem(..), IfaceRule(..), IfaceAnnotation(..), IfaceAnnTarget,
IfaceWarnings(..), IfaceWarningTxt(..), IfaceStringLiteral(..),
IfaceDefault(..), IfaceClsInst(..), IfaceFamInst(..), IfaceTickish(..),
IfaceClassBody(..), IfaceBooleanFormula(..),
IfaceBang(..),
IfaceSrcBang(..), SrcUnpackedness(..), SrcStrictness(..),
IfaceAxBranch(..),
IfaceTyConParent(..),
IfaceCompleteMatch(..),
IfaceLFInfo(..), IfaceTopBndrInfo(..),
IfaceImport(..),
ImpIfaceList(..),
IfaceTopBndr,
putIfaceTopBndr, getIfaceTopBndr,
ifaceDeclImplicitBndrs, visibleIfConDecls,
ifaceDeclFingerprints,
fromIfaceBooleanFormula,
fromIfaceWarnings,
fromIfaceWarningTxt,
freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInst,
freeNamesIfConDecls,
pprIfaceExpr,
pprIfaceDecl,
AltPpr(..), ShowSub(..), ShowHowMuch(..), showToIface, showToHeader
) where
import GHC.Prelude
import GHC.Data.FastString
import GHC.Builtin.Names ( unrestrictedFunTyConKey, liftedTypeKindTyConKey,
constraintKindTyConKey )
import GHC.Types.Unique ( hasKey )
import GHC.Iface.Type
import GHC.Iface.Recomp.Binary
import GHC.Core( IsOrphan, isOrphan, UnfoldingCache(..) )
import GHC.Types.Demand
import GHC.Types.Cpr
import GHC.Core.Class
import GHC.Types.FieldLabel
import GHC.Types.Name.Set
import GHC.Core.Coercion.Axiom ( BranchIndex )
import GHC.Types.Name
import GHC.Types.Name.Reader
import GHC.Types.CostCentre
import GHC.Types.Literal
import GHC.Types.ForeignCall
import GHC.Types.Annotations( AnnPayload, AnnTarget )
import GHC.Types.Basic
import GHC.Unit.Module
import GHC.Unit.Module.Warnings
import GHC.Types.SrcLoc
import GHC.Types.SourceText
import GHC.Data.BooleanFormula ( BooleanFormula(..), pprBooleanFormula, isTrue )
import GHC.Types.Var( VarBndr(..), binderVar, tyVarSpecToBinders, visArgTypeLike )
import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag )
import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
import GHC.Builtin.Types ( constraintKindTyConName )
import GHC.Stg.EnforceEpt.TagSig
import GHC.Parser.Annotation (noLocA)
import GHC.Hs.Extension ( GhcRn )
import GHC.Hs.Doc ( WithHsDocIdentifiers(..) )
import GHC.Utils.Lexeme (isLexSym)
import GHC.Utils.Fingerprint
import GHC.Utils.Binary
import GHC.Utils.Binary.Typeable ()
import GHC.Utils.Outputable as Outputable
import GHC.Utils.Panic
import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith,
seqList, zipWithEqual )
import Control.Monad
import System.IO.Unsafe
import Control.DeepSeq
import Data.Proxy
infixl 3 &&&
data IfaceImport = IfaceImport ImpDeclSpec ImpIfaceList
data ImpIfaceList
= ImpIfaceAll
| ImpIfaceExplicit !IfGlobalRdrEnv
| ImpIfaceEverythingBut !NameSet
type IfaceTopBndr = Name
getIfaceTopBndr :: ReadBinHandle -> IO IfaceTopBndr
getIfaceTopBndr :: ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh = ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
putIfaceTopBndr :: WriteBinHandle -> IfaceTopBndr -> IO ()
putIfaceTopBndr :: WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
name =
case Proxy BindingName -> WriteBinHandle -> BinaryWriter BindingName
forall a. Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a
findUserDataWriter (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @BindingName) WriteBinHandle
bh of
BinaryWriter BindingName
tbl ->
BinaryWriter BindingName -> WriteBinHandle -> BindingName -> IO ()
forall s. BinaryWriter s -> WriteBinHandle -> s -> IO ()
putEntry BinaryWriter BindingName
tbl WriteBinHandle
bh (IfExtName -> BindingName
BindingName IfExtName
name)
data IfaceDecl
= IfaceId { IfaceDecl -> IfExtName
ifName :: IfaceTopBndr,
IfaceDecl -> IfaceType
ifType :: IfaceType,
IfaceDecl -> IfaceIdDetails
ifIdDetails :: IfaceIdDetails,
IfaceDecl -> IfaceIdInfo
ifIdInfo :: IfaceIdInfo
}
| IfaceData { ifName :: IfaceTopBndr,
IfaceDecl -> [IfaceTyConBinder]
ifBinders :: [IfaceTyConBinder],
IfaceDecl -> IfaceType
ifResKind :: IfaceType,
IfaceDecl -> Maybe CType
ifCType :: Maybe CType,
IfaceDecl -> [Role]
ifRoles :: [Role],
IfaceDecl -> IfaceContext
ifCtxt :: IfaceContext,
IfaceDecl -> IfaceConDecls
ifCons :: IfaceConDecls,
IfaceDecl -> Bool
ifGadtSyntax :: Bool,
IfaceDecl -> IfaceTyConParent
ifParent :: IfaceTyConParent
}
| IfaceSynonym { ifName :: IfaceTopBndr,
ifRoles :: [Role],
ifBinders :: [IfaceTyConBinder],
ifResKind :: IfaceKind,
IfaceDecl -> IfaceType
ifSynRhs :: IfaceType }
| IfaceFamily { ifName :: IfaceTopBndr,
IfaceDecl -> Maybe IfLclName
ifResVar :: Maybe IfLclName,
ifBinders :: [IfaceTyConBinder],
ifResKind :: IfaceKind,
IfaceDecl -> IfaceFamTyConFlav
ifFamFlav :: IfaceFamTyConFlav,
IfaceDecl -> Injectivity
ifFamInj :: Injectivity }
| IfaceClass { ifName :: IfaceTopBndr,
ifRoles :: [Role],
ifBinders :: [IfaceTyConBinder],
IfaceDecl -> [FunDep IfLclName]
ifFDs :: [FunDep IfLclName],
IfaceDecl -> IfaceClassBody
ifBody :: IfaceClassBody
}
| IfaceAxiom { ifName :: IfaceTopBndr,
IfaceDecl -> IfaceTyCon
ifTyCon :: IfaceTyCon,
IfaceDecl -> Role
ifRole :: Role,
IfaceDecl -> [IfaceAxBranch]
ifAxBranches :: [IfaceAxBranch]
}
| IfacePatSyn { ifName :: IfaceTopBndr,
IfaceDecl -> Bool
ifPatIsInfix :: Bool,
IfaceDecl -> (IfExtName, Bool)
ifPatMatcher :: (IfExtName, Bool),
IfaceDecl -> Maybe (IfExtName, Bool)
ifPatBuilder :: Maybe (IfExtName, Bool),
IfaceDecl -> [IfaceForAllSpecBndr]
ifPatUnivBndrs :: [IfaceForAllSpecBndr],
IfaceDecl -> [IfaceForAllSpecBndr]
ifPatExBndrs :: [IfaceForAllSpecBndr],
IfaceDecl -> IfaceContext
ifPatProvCtxt :: IfaceContext,
IfaceDecl -> IfaceContext
ifPatReqCtxt :: IfaceContext,
IfaceDecl -> IfaceContext
ifPatArgs :: [IfaceType],
IfaceDecl -> IfaceType
ifPatTy :: IfaceType,
IfaceDecl -> [FieldLabel]
ifFieldLabels :: [FieldLabel] }
data IfaceClassBody
= IfAbstractClass
| IfConcreteClass {
IfaceClassBody -> IfaceContext
ifClassCtxt :: IfaceContext,
IfaceClassBody -> [IfaceAT]
ifATs :: [IfaceAT],
IfaceClassBody -> [IfaceClassOp]
ifSigs :: [IfaceClassOp],
IfaceClassBody -> IfaceBooleanFormula
ifMinDef :: IfaceBooleanFormula
}
data IfaceBooleanFormula
= IfVar IfLclName
| IfAnd [IfaceBooleanFormula]
| IfOr [IfaceBooleanFormula]
| IfParens IfaceBooleanFormula
fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula IfLclName
fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula IfLclName
fromIfaceBooleanFormula = \case
IfVar IfLclName
nm -> IfLclName -> BooleanFormula IfLclName
forall a. a -> BooleanFormula a
Var IfLclName
nm
IfAnd [IfaceBooleanFormula]
ibfs -> [LBooleanFormula IfLclName] -> BooleanFormula IfLclName
forall a. [LBooleanFormula a] -> BooleanFormula a
And ((IfaceBooleanFormula -> LBooleanFormula IfLclName)
-> [IfaceBooleanFormula] -> [LBooleanFormula IfLclName]
forall a b. (a -> b) -> [a] -> [b]
map (BooleanFormula IfLclName -> LBooleanFormula IfLclName
forall e a. HasAnnotation e => a -> GenLocated e a
noLocA (BooleanFormula IfLclName -> LBooleanFormula IfLclName)
-> (IfaceBooleanFormula -> BooleanFormula IfLclName)
-> IfaceBooleanFormula
-> LBooleanFormula IfLclName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IfaceBooleanFormula -> BooleanFormula IfLclName
fromIfaceBooleanFormula) [IfaceBooleanFormula]
ibfs)
IfOr [IfaceBooleanFormula]
ibfs -> [LBooleanFormula IfLclName] -> BooleanFormula IfLclName
forall a. [LBooleanFormula a] -> BooleanFormula a
Or ((IfaceBooleanFormula -> LBooleanFormula IfLclName)
-> [IfaceBooleanFormula] -> [LBooleanFormula IfLclName]
forall a b. (a -> b) -> [a] -> [b]
map (BooleanFormula IfLclName -> LBooleanFormula IfLclName
forall e a. HasAnnotation e => a -> GenLocated e a
noLocA (BooleanFormula IfLclName -> LBooleanFormula IfLclName)
-> (IfaceBooleanFormula -> BooleanFormula IfLclName)
-> IfaceBooleanFormula
-> LBooleanFormula IfLclName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IfaceBooleanFormula -> BooleanFormula IfLclName
fromIfaceBooleanFormula) [IfaceBooleanFormula]
ibfs)
IfParens IfaceBooleanFormula
ibf -> LBooleanFormula IfLclName -> BooleanFormula IfLclName
forall a. LBooleanFormula a -> BooleanFormula a
Parens (BooleanFormula IfLclName -> LBooleanFormula IfLclName
forall e a. HasAnnotation e => a -> GenLocated e a
noLocA (BooleanFormula IfLclName -> LBooleanFormula IfLclName)
-> (IfaceBooleanFormula -> BooleanFormula IfLclName)
-> IfaceBooleanFormula
-> LBooleanFormula IfLclName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IfaceBooleanFormula -> BooleanFormula IfLclName
fromIfaceBooleanFormula (IfaceBooleanFormula -> LBooleanFormula IfLclName)
-> IfaceBooleanFormula -> LBooleanFormula IfLclName
forall a b. (a -> b) -> a -> b
$ IfaceBooleanFormula
ibf)
data IfaceTyConParent
= IfNoParent
| IfDataInstance
IfExtName
IfaceTyCon
IfaceAppArgs
data IfaceFamTyConFlav
= IfaceDataFamilyTyCon
| IfaceOpenSynFamilyTyCon
| IfaceClosedSynFamilyTyCon (Maybe (IfExtName, [IfaceAxBranch]))
| IfaceAbstractClosedSynFamilyTyCon
| IfaceBuiltInSynFamTyCon
data IfaceClassOp
= IfaceClassOp IfaceTopBndr
IfaceType
(Maybe (DefMethSpec IfaceType))
data IfaceAT = IfaceAT
IfaceDecl
(Maybe IfaceType)
data IfaceAxBranch = IfaceAxBranch { IfaceAxBranch -> [IfaceTvBndr]
ifaxbTyVars :: [IfaceTvBndr]
, IfaceAxBranch -> [IfaceTvBndr]
ifaxbEtaTyVars :: [IfaceTvBndr]
, IfaceAxBranch -> [IfaceIdBndr]
ifaxbCoVars :: [IfaceIdBndr]
, IfaceAxBranch -> IfaceAppArgs
ifaxbLHS :: IfaceAppArgs
, IfaceAxBranch -> [Role]
ifaxbRoles :: [Role]
, IfaceAxBranch -> IfaceType
ifaxbRHS :: IfaceType
, IfaceAxBranch -> [Int]
ifaxbIncomps :: [BranchIndex] }
data IfaceConDecls
= IfAbstractTyCon
| IfDataTyCon !Bool [IfaceConDecl]
| IfNewTyCon IfaceConDecl
data IfaceConDecl
= IfCon {
IfaceConDecl -> IfExtName
ifConName :: IfaceTopBndr,
IfaceConDecl -> Bool
ifConWrapper :: Bool,
IfaceConDecl -> Bool
ifConInfix :: Bool,
IfaceConDecl -> [IfaceBndr]
ifConExTCvs :: [IfaceBndr],
IfaceConDecl -> [IfaceForAllSpecBndr]
ifConUserTvBinders :: [IfaceForAllSpecBndr],
IfaceConDecl -> [IfaceTvBndr]
ifConEqSpec :: IfaceEqSpec,
IfaceConDecl -> IfaceContext
ifConCtxt :: IfaceContext,
IfaceConDecl -> [(IfaceType, IfaceType)]
ifConArgTys :: [(IfaceMult, IfaceType)],
IfaceConDecl -> [FieldLabel]
ifConFields :: [FieldLabel],
IfaceConDecl -> [IfaceBang]
ifConStricts :: [IfaceBang],
IfaceConDecl -> [IfaceSrcBang]
ifConSrcStricts :: [IfaceSrcBang] }
type IfaceEqSpec = [(IfLclName,IfaceType)]
data IfaceBang
= IfNoBang | IfStrict | IfUnpack | IfUnpackCo IfaceCoercion
data IfaceSrcBang
= IfSrcBang SrcUnpackedness SrcStrictness
data IfaceDefault
= IfaceDefault { IfaceDefault -> IfaceTyCon
ifDefaultCls :: IfaceTyCon,
IfaceDefault -> IfaceContext
ifDefaultTys :: [IfaceType],
IfaceDefault -> Maybe IfaceWarningTxt
ifDefaultWarn :: Maybe IfaceWarningTxt }
data IfaceClsInst
= IfaceClsInst { IfaceClsInst -> IfExtName
ifInstCls :: IfExtName,
IfaceClsInst -> [Maybe IfaceTyCon]
ifInstTys :: [Maybe IfaceTyCon],
IfaceClsInst -> IfExtName
ifDFun :: IfExtName,
IfaceClsInst -> OverlapFlag
ifOFlag :: OverlapFlag,
IfaceClsInst -> IsOrphan
ifInstOrph :: IsOrphan,
IfaceClsInst -> Maybe IfaceWarningTxt
ifInstWarn :: Maybe IfaceWarningTxt }
data IfaceFamInst
= IfaceFamInst { IfaceFamInst -> IfExtName
ifFamInstFam :: IfExtName
, IfaceFamInst -> [Maybe IfaceTyCon]
ifFamInstTys :: [Maybe IfaceTyCon]
, IfaceFamInst -> IfExtName
ifFamInstAxiom :: IfExtName
, IfaceFamInst -> IsOrphan
ifFamInstOrph :: IsOrphan
}
data IfaceRule
= IfaceRule {
IfaceRule -> FastString
ifRuleName :: RuleName,
IfaceRule -> Activation
ifActivation :: Activation,
IfaceRule -> [IfaceBndr]
ifRuleBndrs :: [IfaceBndr],
IfaceRule -> IfExtName
ifRuleHead :: IfExtName,
IfaceRule -> [IfaceExpr]
ifRuleArgs :: [IfaceExpr],
IfaceRule -> IfaceExpr
ifRuleRhs :: IfaceExpr,
IfaceRule -> Bool
ifRuleAuto :: Bool,
IfaceRule -> IsOrphan
ifRuleOrph :: IsOrphan
}
data IfaceWarnings
= IfWarnAll IfaceWarningTxt
| IfWarnSome [(OccName, IfaceWarningTxt)]
[(IfExtName, IfaceWarningTxt)]
data IfaceWarningTxt
= IfWarningTxt (Maybe WarningCategory) SourceText [(IfaceStringLiteral, [IfExtName])]
| IfDeprecatedTxt SourceText [(IfaceStringLiteral, [IfExtName])]
data IfaceStringLiteral
= IfStringLiteral SourceText FastString
data IfaceAnnotation
= IfaceAnnotation {
IfaceAnnotation -> IfaceAnnTarget
ifAnnotatedTarget :: IfaceAnnTarget,
IfaceAnnotation -> AnnPayload
ifAnnotatedValue :: AnnPayload
}
type IfaceAnnTarget = AnnTarget OccName
data IfaceCompleteMatch = IfaceCompleteMatch [IfExtName] (Maybe IfExtName)
instance Outputable IfaceCompleteMatch where
ppr :: IfaceCompleteMatch -> SDoc
ppr (IfaceCompleteMatch [IfExtName]
cls Maybe IfExtName
mtc) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"COMPLETE" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
colon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [IfExtName] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfExtName]
cls SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> case Maybe IfExtName
mtc of
Maybe IfExtName
Nothing -> SDoc
forall doc. IsOutput doc => doc
empty
Just IfExtName
tc -> SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
tc
type IfaceIdInfo = [IfaceInfoItem]
data IfaceInfoItem
= HsArity Arity
| HsDmdSig DmdSig
| HsCprSig CprSig
| HsInline InlinePragma
| HsUnfold Bool
IfaceUnfolding
| HsNoCafRefs
| HsLFInfo IfaceLFInfo
| HsTagSig TagSig
data IfaceUnfolding
= IfCoreUnfold UnfoldingSource
IfUnfoldingCache
IfGuidance
IfaceExpr
| IfDFunUnfold [IfaceBndr] [IfaceExpr]
type IfUnfoldingCache = UnfoldingCache
data IfGuidance
= IfNoGuidance
| IfWhen Arity Bool Bool
data IfaceIdDetails
= IfVanillaId
| IfWorkerLikeId [CbvMark]
| IfRecSelId
{ IfaceIdDetails -> Either IfaceTyCon IfaceDecl
ifRecSelIdParent :: Either IfaceTyCon IfaceDecl
, IfaceIdDetails -> IfExtName
ifRecSelFirstCon :: IfaceTopBndr
, IfaceIdDetails -> Bool
ifRecSelIdIsNaughty :: Bool
, IfaceIdDetails -> FieldLabel
ifRecSelIdFieldLabel :: FieldLabel }
| IfDFunId
data IfaceLFInfo
= IfLFReEntrant !RepArity
| IfLFThunk
!Bool
!Bool
| IfLFCon !Name
| IfLFUnknown !Bool
| IfLFUnlifted
instance Outputable IfaceLFInfo where
ppr :: IfaceLFInfo -> SDoc
ppr (IfLFReEntrant Int
arity) =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFReEntrant" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
arity
ppr (IfLFThunk Bool
updatable Bool
mb_fun) =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFThunk" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens
(String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"updatable=" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Bool -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bool
updatable SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"might_be_function=" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bool
mb_fun)
ppr (IfLFCon IfExtName
con) =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFCon" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
con)
ppr IfaceLFInfo
IfLFUnlifted =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFUnlifted"
ppr (IfLFUnknown Bool
fun_flag) =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFUnknown" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bool
fun_flag
instance Binary IfaceLFInfo where
put_ :: WriteBinHandle -> IfaceLFInfo -> IO ()
put_ WriteBinHandle
bh (IfLFReEntrant Int
arity) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Int
arity
put_ WriteBinHandle
bh (IfLFThunk Bool
updatable Bool
mb_fun) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
updatable
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
mb_fun
put_ WriteBinHandle
bh (IfLFCon IfExtName
con_name) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
con_name
put_ WriteBinHandle
bh (IfLFUnknown Bool
fun_flag) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
fun_flag
put_ WriteBinHandle
bh IfaceLFInfo
IfLFUnlifted =
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
4
get :: ReadBinHandle -> IO IfaceLFInfo
get ReadBinHandle
bh = do
tag <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case tag of
Word8
0 -> Int -> IfaceLFInfo
IfLFReEntrant (Int -> IfaceLFInfo) -> IO Int -> IO IfaceLFInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
1 -> Bool -> Bool -> IfaceLFInfo
IfLFThunk (Bool -> Bool -> IfaceLFInfo)
-> IO Bool -> IO (Bool -> IfaceLFInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO Bool
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (Bool -> IfaceLFInfo) -> IO Bool -> IO IfaceLFInfo
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO Bool
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
2 -> IfExtName -> IfaceLFInfo
IfLFCon (IfExtName -> IfaceLFInfo) -> IO IfExtName -> IO IfaceLFInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
3 -> Bool -> IfaceLFInfo
IfLFUnknown (Bool -> IfaceLFInfo) -> IO Bool -> IO IfaceLFInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO Bool
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
4 -> IfaceLFInfo -> IO IfaceLFInfo
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceLFInfo
IfLFUnlifted
Word8
_ -> String -> IO IfaceLFInfo
forall a. HasCallStack => String -> a
panic String
"Invalid byte"
visibleIfConDecls :: IfaceConDecls -> [IfaceConDecl]
visibleIfConDecls :: IfaceConDecls -> [IfaceConDecl]
visibleIfConDecls (IfAbstractTyCon {}) = []
visibleIfConDecls (IfDataTyCon Bool
_ [IfaceConDecl]
cs) = [IfaceConDecl]
cs
visibleIfConDecls (IfNewTyCon IfaceConDecl
c) = [IfaceConDecl
c]
ifaceDeclImplicitBndrs :: IfaceDecl -> [OccName]
ifaceDeclImplicitBndrs :: IfaceDecl -> [OccName]
ifaceDeclImplicitBndrs (IfaceData {ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
tc_name, ifCons :: IfaceDecl -> IfaceConDecls
ifCons = IfaceConDecls
cons })
= case IfaceConDecls
cons of
IfAbstractTyCon {} -> []
IfNewTyCon IfaceConDecl
cd -> OccName -> OccName
mkNewTyCoOcc (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
tc_name) OccName -> [OccName] -> [OccName]
forall a. a -> [a] -> [a]
: IfaceConDecl -> [OccName]
ifaceConDeclImplicitBndrs IfaceConDecl
cd
IfDataTyCon Bool
type_data [IfaceConDecl]
cds
| Bool
type_data ->
[IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
con_name | IfCon { ifConName :: IfaceConDecl -> IfExtName
ifConName = IfExtName
con_name } <- [IfaceConDecl]
cds]
| Bool
otherwise -> (IfaceConDecl -> [OccName]) -> [IfaceConDecl] -> [OccName]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap IfaceConDecl -> [OccName]
ifaceConDeclImplicitBndrs [IfaceConDecl]
cds
ifaceDeclImplicitBndrs (IfaceClass { ifBody :: IfaceDecl -> IfaceClassBody
ifBody = IfaceClassBody
IfAbstractClass })
= []
ifaceDeclImplicitBndrs (IfaceClass { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
cls_tc_name
, ifBody :: IfaceDecl -> IfaceClassBody
ifBody = IfConcreteClass {
ifClassCtxt :: IfaceClassBody -> IfaceContext
ifClassCtxt = IfaceContext
sc_ctxt,
ifSigs :: IfaceClassBody -> [IfaceClassOp]
ifSigs = [IfaceClassOp]
sigs,
ifATs :: IfaceClassBody -> [IfaceAT]
ifATs = [IfaceAT]
ats
}})
=
[OccName]
co_occs [OccName] -> [OccName] -> [OccName]
forall a. [a] -> [a] -> [a]
++
[OccName
dc_occ, OccName
dcww_occ] [OccName] -> [OccName] -> [OccName]
forall a. [a] -> [a] -> [a]
++
[IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName (IfaceDecl -> IfExtName
ifName IfaceDecl
at) | IfaceAT IfaceDecl
at Maybe IfaceType
_ <- [IfaceAT]
ats ] [OccName] -> [OccName] -> [OccName]
forall a. [a] -> [a] -> [a]
++
[Int -> OccName -> OccName
mkSuperDictSelOcc Int
n OccName
cls_tc_occ | Int
n <- [Int
1..Int
n_ctxt]] [OccName] -> [OccName] -> [OccName]
forall a. [a] -> [a] -> [a]
++
[IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
op | IfaceClassOp IfExtName
op IfaceType
_ Maybe (DefMethSpec IfaceType)
_ <- [IfaceClassOp]
sigs]
where
cls_tc_occ :: OccName
cls_tc_occ = IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
cls_tc_name
n_ctxt :: Int
n_ctxt = IfaceContext -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length IfaceContext
sc_ctxt
n_sigs :: Int
n_sigs = [IfaceClassOp] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [IfaceClassOp]
sigs
co_occs :: [OccName]
co_occs | Bool
is_newtype = [OccName -> OccName
mkNewTyCoOcc OccName
cls_tc_occ]
| Bool
otherwise = []
dcww_occ :: OccName
dcww_occ = OccName -> OccName
mkDataConWorkerOcc OccName
dc_occ
dc_occ :: OccName
dc_occ = OccName -> OccName
mkClassDataConOcc OccName
cls_tc_occ
is_newtype :: Bool
is_newtype = Int
n_sigs Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n_ctxt Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
ifaceDeclImplicitBndrs IfaceDecl
_ = []
ifaceConDeclImplicitBndrs :: IfaceConDecl -> [OccName]
ifaceConDeclImplicitBndrs :: IfaceConDecl -> [OccName]
ifaceConDeclImplicitBndrs (IfCon {
ifConWrapper :: IfaceConDecl -> Bool
ifConWrapper = Bool
has_wrapper, ifConName :: IfaceConDecl -> IfExtName
ifConName = IfExtName
con_name })
= [IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
con_name, OccName
work_occ] [OccName] -> [OccName] -> [OccName]
forall a. [a] -> [a] -> [a]
++ [OccName]
wrap_occs
where
con_occ :: OccName
con_occ = IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
con_name
work_occ :: OccName
work_occ = OccName -> OccName
mkDataConWorkerOcc OccName
con_occ
wrap_occs :: [OccName]
wrap_occs | Bool
has_wrapper = [OccName -> OccName
mkDataConWrapperOcc OccName
con_occ]
| Bool
otherwise = []
ifaceDeclFingerprints :: Fingerprint -> IfaceDecl -> [(OccName,Fingerprint)]
ifaceDeclFingerprints :: Fingerprint -> IfaceDecl -> [(OccName, Fingerprint)]
ifaceDeclFingerprints Fingerprint
hash IfaceDecl
decl
= (IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
decl, Fingerprint
hash) (OccName, Fingerprint)
-> [(OccName, Fingerprint)] -> [(OccName, Fingerprint)]
forall a. a -> [a] -> [a]
:
[ (OccName
occ, (Fingerprint, OccName) -> Fingerprint
computeFingerprint' (Fingerprint
hash,OccName
occ))
| OccName
occ <- IfaceDecl -> [OccName]
ifaceDeclImplicitBndrs IfaceDecl
decl ]
where
computeFingerprint' :: (Fingerprint, OccName) -> Fingerprint
computeFingerprint' =
IO Fingerprint -> Fingerprint
forall a. IO a -> a
unsafeDupablePerformIO
(IO Fingerprint -> Fingerprint)
-> ((Fingerprint, OccName) -> IO Fingerprint)
-> (Fingerprint, OccName)
-> Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WriteBinHandle -> IfExtName -> IO ())
-> (Fingerprint, OccName) -> IO Fingerprint
forall a.
Binary a =>
(WriteBinHandle -> IfExtName -> IO ()) -> a -> IO Fingerprint
computeFingerprint (String -> WriteBinHandle -> IfExtName -> IO ()
forall a. HasCallStack => String -> a
panic String
"ifaceDeclFingerprints")
fromIfaceWarnings :: IfaceWarnings -> Warnings GhcRn
fromIfaceWarnings :: IfaceWarnings -> Warnings GhcRn
fromIfaceWarnings = \case
IfWarnAll IfaceWarningTxt
txt -> WarningTxt GhcRn -> Warnings GhcRn
forall pass. WarningTxt pass -> Warnings pass
WarnAll (IfaceWarningTxt -> WarningTxt GhcRn
fromIfaceWarningTxt IfaceWarningTxt
txt)
IfWarnSome [(OccName, IfaceWarningTxt)]
vs [(IfExtName, IfaceWarningTxt)]
ds -> DeclWarnOccNames GhcRn -> ExportWarnNames GhcRn -> Warnings GhcRn
forall pass.
DeclWarnOccNames pass -> ExportWarnNames pass -> Warnings pass
WarnSome [(OccName
occ, IfaceWarningTxt -> WarningTxt GhcRn
fromIfaceWarningTxt IfaceWarningTxt
txt) | (OccName
occ, IfaceWarningTxt
txt) <- [(OccName, IfaceWarningTxt)]
vs]
[(IfExtName
occ, IfaceWarningTxt -> WarningTxt GhcRn
fromIfaceWarningTxt IfaceWarningTxt
txt) | (IfExtName
occ, IfaceWarningTxt
txt) <- [(IfExtName, IfaceWarningTxt)]
ds]
fromIfaceWarningTxt :: IfaceWarningTxt -> WarningTxt GhcRn
fromIfaceWarningTxt :: IfaceWarningTxt -> WarningTxt GhcRn
fromIfaceWarningTxt = \case
IfWarningTxt Maybe WarningCategory
mb_cat SourceText
src [(IfaceStringLiteral, [IfExtName])]
strs -> Maybe (LocatedE InWarningCategory)
-> SourceText
-> [LocatedE (WithHsDocIdentifiers StringLiteral GhcRn)]
-> WarningTxt GhcRn
forall pass.
Maybe (LocatedE InWarningCategory)
-> SourceText
-> [LocatedE (WithHsDocIdentifiers StringLiteral pass)]
-> WarningTxt pass
WarningTxt (InWarningCategory -> LocatedE InWarningCategory
forall e a. HasAnnotation e => a -> GenLocated e a
noLocA (InWarningCategory -> LocatedE InWarningCategory)
-> (WarningCategory -> InWarningCategory)
-> WarningCategory
-> LocatedE InWarningCategory
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WarningCategory -> InWarningCategory
fromWarningCategory (WarningCategory -> LocatedE InWarningCategory)
-> Maybe WarningCategory -> Maybe (LocatedE InWarningCategory)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe WarningCategory
mb_cat) SourceText
src (WithHsDocIdentifiers StringLiteral GhcRn
-> LocatedE (WithHsDocIdentifiers StringLiteral GhcRn)
forall e a. HasAnnotation e => a -> GenLocated e a
noLocA (WithHsDocIdentifiers StringLiteral GhcRn
-> LocatedE (WithHsDocIdentifiers StringLiteral GhcRn))
-> [WithHsDocIdentifiers StringLiteral GhcRn]
-> [LocatedE (WithHsDocIdentifiers StringLiteral GhcRn)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((IfaceStringLiteral, [IfExtName])
-> WithHsDocIdentifiers StringLiteral GhcRn)
-> [(IfaceStringLiteral, [IfExtName])]
-> [WithHsDocIdentifiers StringLiteral GhcRn]
forall a b. (a -> b) -> [a] -> [b]
map (IfaceStringLiteral, [IfExtName])
-> WithHsDocIdentifiers StringLiteral GhcRn
fromIfaceStringLiteralWithNames [(IfaceStringLiteral, [IfExtName])]
strs)
IfDeprecatedTxt SourceText
src [(IfaceStringLiteral, [IfExtName])]
strs -> SourceText
-> [LocatedE (WithHsDocIdentifiers StringLiteral GhcRn)]
-> WarningTxt GhcRn
forall pass.
SourceText
-> [LocatedE (WithHsDocIdentifiers StringLiteral pass)]
-> WarningTxt pass
DeprecatedTxt SourceText
src (WithHsDocIdentifiers StringLiteral GhcRn
-> LocatedE (WithHsDocIdentifiers StringLiteral GhcRn)
forall e a. HasAnnotation e => a -> GenLocated e a
noLocA (WithHsDocIdentifiers StringLiteral GhcRn
-> LocatedE (WithHsDocIdentifiers StringLiteral GhcRn))
-> [WithHsDocIdentifiers StringLiteral GhcRn]
-> [LocatedE (WithHsDocIdentifiers StringLiteral GhcRn)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((IfaceStringLiteral, [IfExtName])
-> WithHsDocIdentifiers StringLiteral GhcRn)
-> [(IfaceStringLiteral, [IfExtName])]
-> [WithHsDocIdentifiers StringLiteral GhcRn]
forall a b. (a -> b) -> [a] -> [b]
map (IfaceStringLiteral, [IfExtName])
-> WithHsDocIdentifiers StringLiteral GhcRn
fromIfaceStringLiteralWithNames [(IfaceStringLiteral, [IfExtName])]
strs)
fromIfaceStringLiteralWithNames :: (IfaceStringLiteral, [IfExtName]) -> WithHsDocIdentifiers StringLiteral GhcRn
fromIfaceStringLiteralWithNames :: (IfaceStringLiteral, [IfExtName])
-> WithHsDocIdentifiers StringLiteral GhcRn
fromIfaceStringLiteralWithNames (IfaceStringLiteral
str, [IfExtName]
names) = StringLiteral
-> [Located (IdP GhcRn)]
-> WithHsDocIdentifiers StringLiteral GhcRn
forall a pass.
a -> [Located (IdP pass)] -> WithHsDocIdentifiers a pass
WithHsDocIdentifiers (IfaceStringLiteral -> StringLiteral
fromIfaceStringLiteral IfaceStringLiteral
str) ((IfExtName -> Located IfExtName)
-> [IfExtName] -> [Located IfExtName]
forall a b. (a -> b) -> [a] -> [b]
map IfExtName -> Located IfExtName
forall e. e -> Located e
noLoc [IfExtName]
names)
fromIfaceStringLiteral :: IfaceStringLiteral -> StringLiteral
fromIfaceStringLiteral :: IfaceStringLiteral -> StringLiteral
fromIfaceStringLiteral (IfStringLiteral SourceText
st FastString
fs) = SourceText
-> FastString -> Maybe NoCommentsLocation -> StringLiteral
StringLiteral SourceText
st FastString
fs Maybe NoCommentsLocation
forall a. Maybe a
Nothing
data IfaceExpr
= IfaceLcl IfLclName
| IfaceExt IfExtName
| IfaceType IfaceType
| IfaceCo IfaceCoercion
| IfaceTuple TupleSort [IfaceExpr]
| IfaceLam IfaceLamBndr IfaceExpr
| IfaceApp IfaceExpr IfaceExpr
| IfaceCase IfaceExpr IfLclName [IfaceAlt]
| IfaceECase IfaceExpr IfaceType
| IfaceLet (IfaceBinding IfaceLetBndr) IfaceExpr
| IfaceCast IfaceExpr IfaceCoercion
| IfaceLit Literal
| IfaceLitRubbish TypeOrConstraint IfaceType
| IfaceFCall ForeignCall IfaceType
| IfaceTick IfaceTickish IfaceExpr
data IfaceTickish
= IfaceHpcTick Module Int
| IfaceSCC CostCentre Bool Bool
| IfaceSource RealSrcSpan FastString
| IfaceBreakpoint Int [IfaceExpr] Module
data IfaceAlt = IfaceAlt IfaceConAlt [IfLclName] IfaceExpr
data IfaceConAlt = IfaceDefaultAlt
| IfaceDataAlt IfExtName
| IfaceLitAlt Literal
type IfaceBinding b = IfaceBindingX IfaceExpr b
data IfaceBindingX r b
= IfaceNonRec b r
| IfaceRec [(b, r)]
deriving ((forall a b. (a -> b) -> IfaceBindingX r a -> IfaceBindingX r b)
-> (forall a b. a -> IfaceBindingX r b -> IfaceBindingX r a)
-> Functor (IfaceBindingX r)
forall a b. a -> IfaceBindingX r b -> IfaceBindingX r a
forall a b. (a -> b) -> IfaceBindingX r a -> IfaceBindingX r b
forall r a b. a -> IfaceBindingX r b -> IfaceBindingX r a
forall r a b. (a -> b) -> IfaceBindingX r a -> IfaceBindingX r b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall r a b. (a -> b) -> IfaceBindingX r a -> IfaceBindingX r b
fmap :: forall a b. (a -> b) -> IfaceBindingX r a -> IfaceBindingX r b
$c<$ :: forall r a b. a -> IfaceBindingX r b -> IfaceBindingX r a
<$ :: forall a b. a -> IfaceBindingX r b -> IfaceBindingX r a
Functor, (forall m. Monoid m => IfaceBindingX r m -> m)
-> (forall m a. Monoid m => (a -> m) -> IfaceBindingX r a -> m)
-> (forall m a. Monoid m => (a -> m) -> IfaceBindingX r a -> m)
-> (forall a b. (a -> b -> b) -> b -> IfaceBindingX r a -> b)
-> (forall a b. (a -> b -> b) -> b -> IfaceBindingX r a -> b)
-> (forall b a. (b -> a -> b) -> b -> IfaceBindingX r a -> b)
-> (forall b a. (b -> a -> b) -> b -> IfaceBindingX r a -> b)
-> (forall a. (a -> a -> a) -> IfaceBindingX r a -> a)
-> (forall a. (a -> a -> a) -> IfaceBindingX r a -> a)
-> (forall a. IfaceBindingX r a -> [a])
-> (forall a. IfaceBindingX r a -> Bool)
-> (forall a. IfaceBindingX r a -> Int)
-> (forall a. Eq a => a -> IfaceBindingX r a -> Bool)
-> (forall a. Ord a => IfaceBindingX r a -> a)
-> (forall a. Ord a => IfaceBindingX r a -> a)
-> (forall a. Num a => IfaceBindingX r a -> a)
-> (forall a. Num a => IfaceBindingX r a -> a)
-> Foldable (IfaceBindingX r)
forall a. Eq a => a -> IfaceBindingX r a -> Bool
forall a. Num a => IfaceBindingX r a -> a
forall a. Ord a => IfaceBindingX r a -> a
forall m. Monoid m => IfaceBindingX r m -> m
forall a. IfaceBindingX r a -> Bool
forall a. IfaceBindingX r a -> Int
forall a. IfaceBindingX r a -> [a]
forall a. (a -> a -> a) -> IfaceBindingX r a -> a
forall r a. Eq a => a -> IfaceBindingX r a -> Bool
forall r a. Num a => IfaceBindingX r a -> a
forall r a. Ord a => IfaceBindingX r a -> a
forall r m. Monoid m => IfaceBindingX r m -> m
forall m a. Monoid m => (a -> m) -> IfaceBindingX r a -> m
forall r a. IfaceBindingX r a -> Bool
forall r a. IfaceBindingX r a -> Int
forall r a. IfaceBindingX r a -> [a]
forall b a. (b -> a -> b) -> b -> IfaceBindingX r a -> b
forall a b. (a -> b -> b) -> b -> IfaceBindingX r a -> b
forall r a. (a -> a -> a) -> IfaceBindingX r a -> a
forall r m a. Monoid m => (a -> m) -> IfaceBindingX r a -> m
forall r b a. (b -> a -> b) -> b -> IfaceBindingX r a -> b
forall r a b. (a -> b -> b) -> b -> IfaceBindingX r a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall r m. Monoid m => IfaceBindingX r m -> m
fold :: forall m. Monoid m => IfaceBindingX r m -> m
$cfoldMap :: forall r m a. Monoid m => (a -> m) -> IfaceBindingX r a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> IfaceBindingX r a -> m
$cfoldMap' :: forall r m a. Monoid m => (a -> m) -> IfaceBindingX r a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> IfaceBindingX r a -> m
$cfoldr :: forall r a b. (a -> b -> b) -> b -> IfaceBindingX r a -> b
foldr :: forall a b. (a -> b -> b) -> b -> IfaceBindingX r a -> b
$cfoldr' :: forall r a b. (a -> b -> b) -> b -> IfaceBindingX r a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> IfaceBindingX r a -> b
$cfoldl :: forall r b a. (b -> a -> b) -> b -> IfaceBindingX r a -> b
foldl :: forall b a. (b -> a -> b) -> b -> IfaceBindingX r a -> b
$cfoldl' :: forall r b a. (b -> a -> b) -> b -> IfaceBindingX r a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> IfaceBindingX r a -> b
$cfoldr1 :: forall r a. (a -> a -> a) -> IfaceBindingX r a -> a
foldr1 :: forall a. (a -> a -> a) -> IfaceBindingX r a -> a
$cfoldl1 :: forall r a. (a -> a -> a) -> IfaceBindingX r a -> a
foldl1 :: forall a. (a -> a -> a) -> IfaceBindingX r a -> a
$ctoList :: forall r a. IfaceBindingX r a -> [a]
toList :: forall a. IfaceBindingX r a -> [a]
$cnull :: forall r a. IfaceBindingX r a -> Bool
null :: forall a. IfaceBindingX r a -> Bool
$clength :: forall r a. IfaceBindingX r a -> Int
length :: forall a. IfaceBindingX r a -> Int
$celem :: forall r a. Eq a => a -> IfaceBindingX r a -> Bool
elem :: forall a. Eq a => a -> IfaceBindingX r a -> Bool
$cmaximum :: forall r a. Ord a => IfaceBindingX r a -> a
maximum :: forall a. Ord a => IfaceBindingX r a -> a
$cminimum :: forall r a. Ord a => IfaceBindingX r a -> a
minimum :: forall a. Ord a => IfaceBindingX r a -> a
$csum :: forall r a. Num a => IfaceBindingX r a -> a
sum :: forall a. Num a => IfaceBindingX r a -> a
$cproduct :: forall r a. Num a => IfaceBindingX r a -> a
product :: forall a. Num a => IfaceBindingX r a -> a
Foldable, Functor (IfaceBindingX r)
Foldable (IfaceBindingX r)
(Functor (IfaceBindingX r), Foldable (IfaceBindingX r)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IfaceBindingX r a -> f (IfaceBindingX r b))
-> (forall (f :: * -> *) a.
Applicative f =>
IfaceBindingX r (f a) -> f (IfaceBindingX r a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IfaceBindingX r a -> m (IfaceBindingX r b))
-> (forall (m :: * -> *) a.
Monad m =>
IfaceBindingX r (m a) -> m (IfaceBindingX r a))
-> Traversable (IfaceBindingX r)
forall r. Functor (IfaceBindingX r)
forall r. Foldable (IfaceBindingX r)
forall r (m :: * -> *) a.
Monad m =>
IfaceBindingX r (m a) -> m (IfaceBindingX r a)
forall r (f :: * -> *) a.
Applicative f =>
IfaceBindingX r (f a) -> f (IfaceBindingX r a)
forall r (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IfaceBindingX r a -> m (IfaceBindingX r b)
forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IfaceBindingX r a -> f (IfaceBindingX r b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
IfaceBindingX r (m a) -> m (IfaceBindingX r a)
forall (f :: * -> *) a.
Applicative f =>
IfaceBindingX r (f a) -> f (IfaceBindingX r a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IfaceBindingX r a -> m (IfaceBindingX r b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IfaceBindingX r a -> f (IfaceBindingX r b)
$ctraverse :: forall r (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IfaceBindingX r a -> f (IfaceBindingX r b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IfaceBindingX r a -> f (IfaceBindingX r b)
$csequenceA :: forall r (f :: * -> *) a.
Applicative f =>
IfaceBindingX r (f a) -> f (IfaceBindingX r a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
IfaceBindingX r (f a) -> f (IfaceBindingX r a)
$cmapM :: forall r (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IfaceBindingX r a -> m (IfaceBindingX r b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IfaceBindingX r a -> m (IfaceBindingX r b)
$csequence :: forall r (m :: * -> *) a.
Monad m =>
IfaceBindingX r (m a) -> m (IfaceBindingX r a)
sequence :: forall (m :: * -> *) a.
Monad m =>
IfaceBindingX r (m a) -> m (IfaceBindingX r a)
Traversable, Eq (IfaceBindingX r b)
Eq (IfaceBindingX r b) =>
(IfaceBindingX r b -> IfaceBindingX r b -> Ordering)
-> (IfaceBindingX r b -> IfaceBindingX r b -> Bool)
-> (IfaceBindingX r b -> IfaceBindingX r b -> Bool)
-> (IfaceBindingX r b -> IfaceBindingX r b -> Bool)
-> (IfaceBindingX r b -> IfaceBindingX r b -> Bool)
-> (IfaceBindingX r b -> IfaceBindingX r b -> IfaceBindingX r b)
-> (IfaceBindingX r b -> IfaceBindingX r b -> IfaceBindingX r b)
-> Ord (IfaceBindingX r b)
IfaceBindingX r b -> IfaceBindingX r b -> Bool
IfaceBindingX r b -> IfaceBindingX r b -> Ordering
IfaceBindingX r b -> IfaceBindingX r b -> IfaceBindingX r b
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
forall r b. (Ord b, Ord r) => Eq (IfaceBindingX r b)
forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Bool
forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Ordering
forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> IfaceBindingX r b
$ccompare :: forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Ordering
compare :: IfaceBindingX r b -> IfaceBindingX r b -> Ordering
$c< :: forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Bool
< :: IfaceBindingX r b -> IfaceBindingX r b -> Bool
$c<= :: forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Bool
<= :: IfaceBindingX r b -> IfaceBindingX r b -> Bool
$c> :: forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Bool
> :: IfaceBindingX r b -> IfaceBindingX r b -> Bool
$c>= :: forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Bool
>= :: IfaceBindingX r b -> IfaceBindingX r b -> Bool
$cmax :: forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> IfaceBindingX r b
max :: IfaceBindingX r b -> IfaceBindingX r b -> IfaceBindingX r b
$cmin :: forall r b.
(Ord b, Ord r) =>
IfaceBindingX r b -> IfaceBindingX r b -> IfaceBindingX r b
min :: IfaceBindingX r b -> IfaceBindingX r b -> IfaceBindingX r b
Ord, IfaceBindingX r b -> IfaceBindingX r b -> Bool
(IfaceBindingX r b -> IfaceBindingX r b -> Bool)
-> (IfaceBindingX r b -> IfaceBindingX r b -> Bool)
-> Eq (IfaceBindingX r b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall r b.
(Eq b, Eq r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Bool
$c== :: forall r b.
(Eq b, Eq r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Bool
== :: IfaceBindingX r b -> IfaceBindingX r b -> Bool
$c/= :: forall r b.
(Eq b, Eq r) =>
IfaceBindingX r b -> IfaceBindingX r b -> Bool
/= :: IfaceBindingX r b -> IfaceBindingX r b -> Bool
Eq)
data IfaceLetBndr = IfLetBndr IfLclName IfaceType IfaceIdInfo JoinPointHood
data IfaceTopBndrInfo = IfLclTopBndr IfLclName IfaceType IfaceIdInfo IfaceIdDetails
| IfGblTopBndr IfaceTopBndr
data IfaceMaybeRhs = IfUseUnfoldingRhs | IfRhs IfaceExpr
pprAxBranch :: SDoc -> BranchIndex -> IfaceAxBranch -> SDoc
pprAxBranch :: SDoc -> Int -> IfaceAxBranch -> SDoc
pprAxBranch SDoc
pp_tc Int
idx (IfaceAxBranch { ifaxbTyVars :: IfaceAxBranch -> [IfaceTvBndr]
ifaxbTyVars = [IfaceTvBndr]
tvs
, ifaxbCoVars :: IfaceAxBranch -> [IfaceIdBndr]
ifaxbCoVars = [IfaceIdBndr]
_cvs
, ifaxbLHS :: IfaceAxBranch -> IfaceAppArgs
ifaxbLHS = IfaceAppArgs
pat_tys
, ifaxbRHS :: IfaceAxBranch -> IfaceType
ifaxbRHS = IfaceType
rhs
, ifaxbIncomps :: IfaceAxBranch -> [Int]
ifaxbIncomps = [Int]
incomps })
= Bool -> SDoc -> SDoc -> SDoc
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr ([IfaceIdBndr] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceIdBndr]
_cvs) (SDoc
pp_tc SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ [IfaceIdBndr] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfaceIdBndr]
_cvs) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
SDoc -> Int -> SDoc -> SDoc
hang SDoc
ppr_binders Int
2 (SDoc -> Int -> SDoc -> SDoc
hang SDoc
pp_lhs Int
2 (SDoc
forall doc. IsLine doc => doc
equals SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
rhs))
SDoc -> SDoc -> SDoc
$+$
Int -> SDoc -> SDoc
nest Int
4 SDoc
maybe_incomps
where
ppr_binders :: SDoc
ppr_binders = SDoc
maybe_index SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
[IfaceForAllBndr] -> SDoc
pprUserIfaceForAll ((IfaceTvBndr -> IfaceForAllBndr)
-> [IfaceTvBndr] -> [IfaceForAllBndr]
forall a b. (a -> b) -> [a] -> [b]
map (ForAllTyFlag -> IfaceTvBndr -> IfaceForAllBndr
mkIfaceForAllTvBndr ForAllTyFlag
Specified) [IfaceTvBndr]
tvs)
pp_lhs :: SDoc
pp_lhs = SDoc -> Int -> SDoc -> SDoc
hang SDoc
pp_tc Int
2 (IfaceAppArgs -> SDoc
pprParendIfaceAppArgs IfaceAppArgs
pat_tys)
maybe_index :: SDoc
maybe_index
= (SDocContext -> Bool) -> SDoc -> SDoc
ppWhenOption SDocContext -> Bool
sdocPrintAxiomIncomps (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"{-" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"#" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
idx) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"-}"
maybe_incomps :: SDoc
maybe_incomps
= (SDocContext -> Bool) -> SDoc -> SDoc
ppWhenOption SDocContext -> Bool
sdocPrintAxiomIncomps (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen ([Int] -> Bool
forall (f :: * -> *) a. Foldable f => f a -> Bool
notNull [Int]
incomps) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"--" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"incompatible with:"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Int -> SDoc) -> [Int] -> SDoc
forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas (\Int
incomp -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"#" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
incomp) [Int]
incomps
instance Outputable IfaceWarnings where
ppr :: IfaceWarnings -> SDoc
ppr = \case
IfWarnAll IfaceWarningTxt
txt -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Warn all" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceWarningTxt -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceWarningTxt
txt
IfWarnSome [(OccName, IfaceWarningTxt)]
vs [(IfExtName, IfaceWarningTxt)]
ds ->
SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Warnings:") Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Deprecated names:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
name SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceWarningTxt -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceWarningTxt
txt | (OccName
name, IfaceWarningTxt
txt) <- [(OccName, IfaceWarningTxt)]
vs] SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Deprecated exports:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
name SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceWarningTxt -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceWarningTxt
txt | (IfExtName
name, IfaceWarningTxt
txt) <- [(IfExtName, IfaceWarningTxt)]
ds]
instance Outputable IfaceWarningTxt where
ppr :: IfaceWarningTxt -> SDoc
ppr = \case
IfWarningTxt Maybe WarningCategory
_ SourceText
_ [(IfaceStringLiteral, [IfExtName])]
ws -> [(IfaceStringLiteral, [IfExtName])] -> SDoc
pp_ws [(IfaceStringLiteral, [IfExtName])]
ws
IfDeprecatedTxt SourceText
_ [(IfaceStringLiteral, [IfExtName])]
ds -> [(IfaceStringLiteral, [IfExtName])] -> SDoc
pp_ws [(IfaceStringLiteral, [IfExtName])]
ds
where
pp_ws :: [(IfaceStringLiteral, [IfExtName])] -> SDoc
pp_ws [(IfaceStringLiteral, [IfExtName])
msg] = (IfaceStringLiteral, [IfExtName]) -> SDoc
forall {b}. (IfaceStringLiteral, b) -> SDoc
pp_with_name (IfaceStringLiteral, [IfExtName])
msg
pp_ws [(IfaceStringLiteral, [IfExtName])]
msgs = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ([SDoc] -> SDoc)
-> ([(IfaceStringLiteral, [IfExtName])] -> [SDoc])
-> [(IfaceStringLiteral, [IfExtName])]
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDoc -> [SDoc] -> [SDoc]
forall doc. IsLine doc => doc -> [doc] -> [doc]
punctuate SDoc
forall doc. IsLine doc => doc
comma ([SDoc] -> [SDoc])
-> ([(IfaceStringLiteral, [IfExtName])] -> [SDoc])
-> [(IfaceStringLiteral, [IfExtName])]
-> [SDoc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((IfaceStringLiteral, [IfExtName]) -> SDoc)
-> [(IfaceStringLiteral, [IfExtName])] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (IfaceStringLiteral, [IfExtName]) -> SDoc
forall {b}. (IfaceStringLiteral, b) -> SDoc
pp_with_name ([(IfaceStringLiteral, [IfExtName])] -> SDoc)
-> [(IfaceStringLiteral, [IfExtName])] -> SDoc
forall a b. (a -> b) -> a -> b
$ [(IfaceStringLiteral, [IfExtName])]
msgs
pp_with_name :: (IfaceStringLiteral, b) -> SDoc
pp_with_name = IfaceStringLiteral -> SDoc
forall a. Outputable a => a -> SDoc
ppr (IfaceStringLiteral -> SDoc)
-> ((IfaceStringLiteral, b) -> IfaceStringLiteral)
-> (IfaceStringLiteral, b)
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IfaceStringLiteral, b) -> IfaceStringLiteral
forall a b. (a, b) -> a
fst
instance Outputable IfaceStringLiteral where
ppr :: IfaceStringLiteral -> SDoc
ppr (IfStringLiteral SourceText
st FastString
fs) = SourceText -> SDoc -> SDoc
pprWithSourceText SourceText
st (FastString -> SDoc
forall doc. IsLine doc => FastString -> doc
ftext FastString
fs)
instance Outputable IfaceAnnotation where
ppr :: IfaceAnnotation -> SDoc
ppr (IfaceAnnotation IfaceAnnTarget
target AnnPayload
value) = IfaceAnnTarget -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceAnnTarget
target SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
forall doc. IsLine doc => doc
colon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> AnnPayload -> SDoc
forall a. Outputable a => a -> SDoc
ppr AnnPayload
value
instance NamedThing IfaceClassOp where
getName :: IfaceClassOp -> IfExtName
getName (IfaceClassOp IfExtName
n IfaceType
_ Maybe (DefMethSpec IfaceType)
_) = IfExtName
n
instance HasOccName IfaceClassOp where
occName :: IfaceClassOp -> OccName
occName = IfaceClassOp -> OccName
forall a. NamedThing a => a -> OccName
getOccName
instance NamedThing IfaceConDecl where
getName :: IfaceConDecl -> IfExtName
getName = IfaceConDecl -> IfExtName
ifConName
instance HasOccName IfaceConDecl where
occName :: IfaceConDecl -> OccName
occName = IfaceConDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName
instance NamedThing IfaceDecl where
getName :: IfaceDecl -> IfExtName
getName = IfaceDecl -> IfExtName
ifName
instance HasOccName IfaceDecl where
occName :: IfaceDecl -> OccName
occName = IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName
instance Outputable IfaceDecl where
ppr :: IfaceDecl -> SDoc
ppr = ShowSub -> IfaceDecl -> SDoc
pprIfaceDecl ShowSub
showToIface
instance (Outputable r, Outputable b) => Outputable (IfaceBindingX r b) where
ppr :: IfaceBindingX r b -> SDoc
ppr IfaceBindingX r b
b = case IfaceBindingX r b
b of
(IfaceNonRec b
b r
r) -> (b, r) -> SDoc
forall {a} {a}. (Outputable a, Outputable a) => (a, a) -> SDoc
ppr_bind (b
b, r
r)
(IfaceRec [(b, r)]
pairs) -> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"rec {", Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep (((b, r) -> SDoc) -> [(b, r)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (b, r) -> SDoc
forall {a} {a}. (Outputable a, Outputable a) => (a, a) -> SDoc
ppr_bind [(b, r)]
pairs)),String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"}"]
where
ppr_bind :: (a, a) -> SDoc
ppr_bind (a
b, a
r) = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
b SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
forall doc. IsLine doc => doc
equals SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
r
instance Outputable IfaceTopBndrInfo where
ppr :: IfaceTopBndrInfo -> SDoc
ppr (IfLclTopBndr IfLclName
lcl_name IfaceType
_ IfaceIdInfo
_ IfaceIdDetails
_) = IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfLclName
lcl_name
ppr (IfGblTopBndr IfExtName
gbl) = IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
gbl
instance Outputable IfaceMaybeRhs where
ppr :: IfaceMaybeRhs -> SDoc
ppr IfaceMaybeRhs
IfUseUnfoldingRhs = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"<unfolding>"
ppr (IfRhs IfaceExpr
ie) = IfaceExpr -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceExpr
ie
showToHeader :: ShowSub
= ShowSub { ss_how_much :: ShowHowMuch
ss_how_much = AltPpr -> ShowHowMuch
ShowHeader (AltPpr -> ShowHowMuch) -> AltPpr -> ShowHowMuch
forall a b. (a -> b) -> a -> b
$ Maybe (OccName -> SDoc) -> AltPpr
AltPpr Maybe (OccName -> SDoc)
forall a. Maybe a
Nothing
, ss_forall :: ShowForAllFlag
ss_forall = ShowForAllFlag
ShowForAllWhen }
showToIface :: ShowSub
showToIface :: ShowSub
showToIface = ShowSub { ss_how_much :: ShowHowMuch
ss_how_much = ShowHowMuch
ShowIface
, ss_forall :: ShowForAllFlag
ss_forall = ShowForAllFlag
ShowForAllWhen }
ppShowIface :: ShowSub -> SDoc -> SDoc
ppShowIface :: ShowSub -> SDoc -> SDoc
ppShowIface (ShowSub { ss_how_much :: ShowSub -> ShowHowMuch
ss_how_much = ShowHowMuch
ShowIface }) SDoc
doc = SDoc
doc
ppShowIface ShowSub
_ SDoc
_ = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
ppShowAllSubs :: ShowSub -> SDoc -> SDoc
ppShowAllSubs :: ShowSub -> SDoc -> SDoc
ppShowAllSubs (ShowSub { ss_how_much :: ShowSub -> ShowHowMuch
ss_how_much = ShowSome Maybe (OccName -> Bool)
Nothing AltPpr
_ }) SDoc
doc
= SDoc
doc
ppShowAllSubs (ShowSub { ss_how_much :: ShowSub -> ShowHowMuch
ss_how_much = ShowHowMuch
ShowIface }) SDoc
doc = SDoc
doc
ppShowAllSubs ShowSub
_ SDoc
_ = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
ppShowRhs :: ShowSub -> SDoc -> SDoc
ppShowRhs :: ShowSub -> SDoc -> SDoc
ppShowRhs (ShowSub { ss_how_much :: ShowSub -> ShowHowMuch
ss_how_much = ShowHeader AltPpr
_ }) SDoc
_ = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
ppShowRhs ShowSub
_ SDoc
doc = SDoc
doc
showSub :: HasOccName n => ShowSub -> n -> Bool
showSub :: forall n. HasOccName n => ShowSub -> n -> Bool
showSub (ShowSub { ss_how_much :: ShowSub -> ShowHowMuch
ss_how_much = ShowHeader AltPpr
_ }) n
_ = Bool
False
showSub (ShowSub { ss_how_much :: ShowSub -> ShowHowMuch
ss_how_much = ShowSome (Just OccName -> Bool
f) AltPpr
_ }) n
thing
= OccName -> Bool
f (n -> OccName
forall name. HasOccName name => name -> OccName
occName n
thing)
showSub (ShowSub { ss_how_much :: ShowSub -> ShowHowMuch
ss_how_much = ShowHowMuch
_ }) n
_ = Bool
True
ppr_trim :: [Maybe SDoc] -> [SDoc]
ppr_trim :: [Maybe SDoc] -> [SDoc]
ppr_trim [Maybe SDoc]
xs
= (Bool, [SDoc]) -> [SDoc]
forall a b. (a, b) -> b
snd ((Maybe SDoc -> (Bool, [SDoc]) -> (Bool, [SDoc]))
-> (Bool, [SDoc]) -> [Maybe SDoc] -> (Bool, [SDoc])
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Maybe SDoc -> (Bool, [SDoc]) -> (Bool, [SDoc])
forall {a}. IsLine a => Maybe a -> (Bool, [a]) -> (Bool, [a])
go (Bool
False, []) [Maybe SDoc]
xs)
where
go :: Maybe a -> (Bool, [a]) -> (Bool, [a])
go (Just a
doc) (Bool
_, [a]
so_far) = (Bool
False, a
doc a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
so_far)
go Maybe a
Nothing (Bool
True, [a]
so_far) = (Bool
True, [a]
so_far)
go Maybe a
Nothing (Bool
False, [a]
so_far) = (Bool
True, String -> a
forall doc. IsLine doc => String -> doc
text String
"..." a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
so_far)
isIfaceDataInstance :: IfaceTyConParent -> Bool
isIfaceDataInstance :: IfaceTyConParent -> Bool
isIfaceDataInstance IfaceTyConParent
IfNoParent = Bool
False
isIfaceDataInstance IfaceTyConParent
_ = Bool
True
pprClassRoles :: ShowSub -> IfaceTopBndr -> [IfaceTyConBinder] -> [Role] -> SDoc
pprClassRoles :: ShowSub -> IfExtName -> [IfaceTyConBinder] -> [Role] -> SDoc
pprClassRoles ShowSub
ss IfExtName
clas [IfaceTyConBinder]
binders [Role]
roles =
(Role -> Bool) -> SDoc -> [IfaceTyConBinder] -> [Role] -> SDoc
pprRoles (Role -> Role -> Bool
forall a. Eq a => a -> a -> Bool
== Role
Nominal)
(ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss) (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
clas))
[IfaceTyConBinder]
binders
[Role]
roles
pprClassStandaloneKindSig :: ShowSub -> IfaceTopBndr -> IfaceKind -> SDoc
pprClassStandaloneKindSig :: ShowSub -> IfExtName -> IfaceType -> SDoc
pprClassStandaloneKindSig ShowSub
ss IfExtName
clas =
SDoc -> IfaceType -> SDoc
pprStandaloneKindSig (ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss) (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
clas))
constraintIfaceKind :: IfaceKind
constraintIfaceKind :: IfaceType
constraintIfaceKind =
IfaceTyCon -> IfaceAppArgs -> IfaceType
IfaceTyConApp (IfExtName -> IfaceTyConInfo -> IfaceTyCon
IfaceTyCon IfExtName
constraintKindTyConName (PromotionFlag -> IfaceTyConSort -> IfaceTyConInfo
mkIfaceTyConInfo PromotionFlag
NotPromoted IfaceTyConSort
IfaceNormalTyCon)) IfaceAppArgs
IA_Nil
pprIfaceDecl :: ShowSub -> IfaceDecl -> SDoc
pprIfaceDecl :: ShowSub -> IfaceDecl -> SDoc
pprIfaceDecl ShowSub
ss (IfaceData { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
tycon, ifCType :: IfaceDecl -> Maybe CType
ifCType = Maybe CType
ctype,
ifCtxt :: IfaceDecl -> IfaceContext
ifCtxt = IfaceContext
context, ifResKind :: IfaceDecl -> IfaceType
ifResKind = IfaceType
kind,
ifRoles :: IfaceDecl -> [Role]
ifRoles = [Role]
roles, ifCons :: IfaceDecl -> IfaceConDecls
ifCons = IfaceConDecls
condecls,
ifParent :: IfaceDecl -> IfaceTyConParent
ifParent = IfaceTyConParent
parent,
ifGadtSyntax :: IfaceDecl -> Bool
ifGadtSyntax = Bool
gadt,
ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders })
| Bool
gadt = [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ SDoc
pp_roles
, SDoc
pp_ki_sig
, SDoc
pp_nd SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_lhs SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_kind SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_where
, Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [SDoc]
pp_cons)
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss SDoc
pp_extra ]
| Bool
otherwise = [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ SDoc
pp_roles
, SDoc
pp_ki_sig
, SDoc -> Int -> SDoc -> SDoc
hang (SDoc
pp_nd SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_lhs) Int
2 ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
add_bars [SDoc]
pp_cons)
, Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss SDoc
pp_extra ]
where
is_data_instance :: Bool
is_data_instance = IfaceTyConParent -> Bool
isIfaceDataInstance IfaceTyConParent
parent
pp_data_inst_forall :: SDoc
pp_data_inst_forall :: SDoc
pp_data_inst_forall = [IfaceForAllBndr] -> SDoc
pprUserIfaceForAll [IfaceForAllBndr]
forall_bndrs
forall_bndrs :: [IfaceForAllBndr]
forall_bndrs :: [IfaceForAllBndr]
forall_bndrs = [IfaceBndr -> ForAllTyFlag -> IfaceForAllBndr
forall var argf. var -> argf -> VarBndr var argf
Bndr (IfaceTyConBinder -> IfaceBndr
forall tv argf. VarBndr tv argf -> tv
binderVar IfaceTyConBinder
tc_bndr) ForAllTyFlag
Specified | IfaceTyConBinder
tc_bndr <- [IfaceTyConBinder]
binders]
cons :: [IfaceConDecl]
cons = IfaceConDecls -> [IfaceConDecl]
visibleIfConDecls IfaceConDecls
condecls
pp_where :: SDoc
pp_where = Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen (Bool
gadt Bool -> Bool -> Bool
&& Bool -> Bool
not ([IfaceConDecl] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceConDecl]
cons)) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"where"
pp_cons :: [SDoc]
pp_cons = [Maybe SDoc] -> [SDoc]
ppr_trim ((IfaceConDecl -> Maybe SDoc) -> [IfaceConDecl] -> [Maybe SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceConDecl -> Maybe SDoc
show_con [IfaceConDecl]
cons) :: [SDoc]
pp_kind :: SDoc
pp_kind = Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless (Bool
ki_sig_printable Bool -> Bool -> Bool
|| IfaceType -> Bool
isIfaceLiftedTypeKind IfaceType
kind)
(SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
kind)
pp_lhs :: SDoc
pp_lhs = case IfaceTyConParent
parent of
IfaceTyConParent
IfNoParent -> SuppressBndrSig
-> IfaceContext
-> ShowSub
-> IfExtName
-> [IfaceTyConBinder]
-> SDoc
pprIfaceDeclHead SuppressBndrSig
suppress_bndr_sig IfaceContext
context ShowSub
ss IfExtName
tycon [IfaceTyConBinder]
binders
IfDataInstance{}
-> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"instance" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_data_inst_forall
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceTyConParent -> SDoc
pprIfaceTyConParent IfaceTyConParent
parent
pp_roles :: SDoc
pp_roles
| Bool
is_data_instance = SDoc
forall doc. IsOutput doc => doc
empty
| Bool
otherwise = (Role -> Bool) -> SDoc -> [IfaceTyConBinder] -> [Role] -> SDoc
pprRoles (Role -> Role -> Bool
forall a. Eq a => a -> a -> Bool
== Role
Representational) SDoc
name_doc [IfaceTyConBinder]
binders [Role]
roles
ki_sig_printable :: Bool
ki_sig_printable =
Bool -> Bool
not Bool
is_data_instance
pp_ki_sig :: SDoc
pp_ki_sig = Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen Bool
ki_sig_printable (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
SDoc -> IfaceType -> SDoc
pprStandaloneKindSig SDoc
name_doc ([IfaceTyConBinder] -> IfaceType -> IfaceType
mkIfaceTyConKind [IfaceTyConBinder]
binders IfaceType
kind)
suppress_bndr_sig :: SuppressBndrSig
suppress_bndr_sig = Bool -> SuppressBndrSig
SuppressBndrSig Bool
ki_sig_printable
name_doc :: SDoc
name_doc = ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss) (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
tycon)
add_bars :: [doc] -> doc
add_bars [] = doc
forall doc. IsOutput doc => doc
Outputable.empty
add_bars (doc
c:[doc]
cs) = [doc] -> doc
forall doc. IsLine doc => [doc] -> doc
sep ((doc
forall doc. IsLine doc => doc
equals doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<+> doc
c) doc -> [doc] -> [doc]
forall a. a -> [a] -> [a]
: (doc -> doc) -> [doc] -> [doc]
forall a b. (a -> b) -> [a] -> [b]
map (doc
forall doc. IsLine doc => doc
vbar doc -> doc -> doc
forall doc. IsLine doc => doc -> doc -> doc
<+>) [doc]
cs)
ok_con :: IfaceConDecl -> Bool
ok_con IfaceConDecl
dc = ShowSub -> IfaceConDecl -> Bool
forall n. HasOccName n => ShowSub -> n -> Bool
showSub ShowSub
ss IfaceConDecl
dc Bool -> Bool -> Bool
|| (FieldLabel -> Bool) -> [FieldLabel] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (ShowSub -> IfExtName -> Bool
forall n. HasOccName n => ShowSub -> n -> Bool
showSub ShowSub
ss (IfExtName -> Bool)
-> (FieldLabel -> IfExtName) -> FieldLabel -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLabel -> IfExtName
flSelector) (IfaceConDecl -> [FieldLabel]
ifConFields IfaceConDecl
dc)
show_con :: IfaceConDecl -> Maybe SDoc
show_con IfaceConDecl
dc
| IfaceConDecl -> Bool
ok_con IfaceConDecl
dc = SDoc -> Maybe SDoc
forall a. a -> Maybe a
Just (SDoc -> Maybe SDoc) -> SDoc -> Maybe SDoc
forall a b. (a -> b) -> a -> b
$ ShowSub
-> Bool
-> IfExtName
-> [IfaceTyConBinder]
-> IfaceTyConParent
-> IfaceConDecl
-> SDoc
pprIfaceConDecl ShowSub
ss Bool
gadt IfExtName
tycon [IfaceTyConBinder]
binders IfaceTyConParent
parent IfaceConDecl
dc
| Bool
otherwise = Maybe SDoc
forall a. Maybe a
Nothing
pp_nd :: SDoc
pp_nd = case IfaceConDecls
condecls of
IfAbstractTyCon{} -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"data"
IfDataTyCon Bool
True [IfaceConDecl]
_ -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"type data"
IfDataTyCon{} -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"data"
IfNewTyCon{} -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"newtype"
pp_extra :: SDoc
pp_extra = [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [Maybe CType -> SDoc
pprCType Maybe CType
ctype]
pprIfaceDecl ShowSub
ss (IfaceClass { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
clas
, ifRoles :: IfaceDecl -> [Role]
ifRoles = [Role]
roles
, ifFDs :: IfaceDecl -> [FunDep IfLclName]
ifFDs = [FunDep IfLclName]
fds
, ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
, ifBody :: IfaceDecl -> IfaceClassBody
ifBody = IfaceClassBody
IfAbstractClass })
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ ShowSub -> IfExtName -> [IfaceTyConBinder] -> [Role] -> SDoc
pprClassRoles ShowSub
ss IfExtName
clas [IfaceTyConBinder]
binders [Role]
roles
, ShowSub -> IfExtName -> IfaceType -> SDoc
pprClassStandaloneKindSig ShowSub
ss IfExtName
clas ([IfaceTyConBinder] -> IfaceType -> IfaceType
mkIfaceTyConKind [IfaceTyConBinder]
binders IfaceType
constraintIfaceKind)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"class" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SuppressBndrSig
-> IfaceContext
-> ShowSub
-> IfExtName
-> [IfaceTyConBinder]
-> SDoc
pprIfaceDeclHead SuppressBndrSig
suppress_bndr_sig [] ShowSub
ss IfExtName
clas [IfaceTyConBinder]
binders SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [FunDep IfLclName] -> SDoc
forall a. Outputable a => [FunDep a] -> SDoc
pprFundeps [FunDep IfLclName]
fds ]
where
suppress_bndr_sig :: SuppressBndrSig
suppress_bndr_sig = Bool -> SuppressBndrSig
SuppressBndrSig Bool
True
pprIfaceDecl ShowSub
ss (IfaceClass { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
clas
, ifRoles :: IfaceDecl -> [Role]
ifRoles = [Role]
roles
, ifFDs :: IfaceDecl -> [FunDep IfLclName]
ifFDs = [FunDep IfLclName]
fds
, ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
, ifBody :: IfaceDecl -> IfaceClassBody
ifBody = IfConcreteClass {
ifATs :: IfaceClassBody -> [IfaceAT]
ifATs = [IfaceAT]
ats,
ifSigs :: IfaceClassBody -> [IfaceClassOp]
ifSigs = [IfaceClassOp]
sigs,
ifClassCtxt :: IfaceClassBody -> IfaceContext
ifClassCtxt = IfaceContext
context,
ifMinDef :: IfaceClassBody -> IfaceBooleanFormula
ifMinDef = IfaceBooleanFormula
minDef
}})
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ ShowSub -> IfExtName -> [IfaceTyConBinder] -> [Role] -> SDoc
pprClassRoles ShowSub
ss IfExtName
clas [IfaceTyConBinder]
binders [Role]
roles
, ShowSub -> IfExtName -> IfaceType -> SDoc
pprClassStandaloneKindSig ShowSub
ss IfExtName
clas ([IfaceTyConBinder] -> IfaceType -> IfaceType
mkIfaceTyConKind [IfaceTyConBinder]
binders IfaceType
constraintIfaceKind)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"class" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SuppressBndrSig
-> IfaceContext
-> ShowSub
-> IfExtName
-> [IfaceTyConBinder]
-> SDoc
pprIfaceDeclHead SuppressBndrSig
suppress_bndr_sig IfaceContext
context ShowSub
ss IfExtName
clas [IfaceTyConBinder]
binders SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [FunDep IfLclName] -> SDoc
forall a. Outputable a => [FunDep a] -> SDoc
pprFundeps [FunDep IfLclName]
fds SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_where
, Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [SDoc]
asocs, [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [SDoc]
dsigs
, ShowSub -> SDoc -> SDoc
ppShowAllSubs ShowSub
ss (BooleanFormula IfLclName -> SDoc
pprMinDef (BooleanFormula IfLclName -> SDoc)
-> BooleanFormula IfLclName -> SDoc
forall a b. (a -> b) -> a -> b
$ IfaceBooleanFormula -> BooleanFormula IfLclName
fromIfaceBooleanFormula IfaceBooleanFormula
minDef)])]
where
pp_where :: SDoc
pp_where = ShowSub -> SDoc -> SDoc
ppShowRhs ShowSub
ss (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless ([IfaceClassOp] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceClassOp]
sigs Bool -> Bool -> Bool
&& [IfaceAT] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceAT]
ats) (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"where")
asocs :: [SDoc]
asocs = [Maybe SDoc] -> [SDoc]
ppr_trim ([Maybe SDoc] -> [SDoc]) -> [Maybe SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ (IfaceAT -> Maybe SDoc) -> [IfaceAT] -> [Maybe SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceAT -> Maybe SDoc
maybeShowAssoc [IfaceAT]
ats
dsigs :: [SDoc]
dsigs = [Maybe SDoc] -> [SDoc]
ppr_trim ([Maybe SDoc] -> [SDoc]) -> [Maybe SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ (IfaceClassOp -> Maybe SDoc) -> [IfaceClassOp] -> [Maybe SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceClassOp -> Maybe SDoc
maybeShowSig [IfaceClassOp]
sigs
maybeShowAssoc :: IfaceAT -> Maybe SDoc
maybeShowAssoc :: IfaceAT -> Maybe SDoc
maybeShowAssoc asc :: IfaceAT
asc@(IfaceAT IfaceDecl
d Maybe IfaceType
_)
| ShowSub -> IfaceDecl -> Bool
forall n. HasOccName n => ShowSub -> n -> Bool
showSub ShowSub
ss IfaceDecl
d = SDoc -> Maybe SDoc
forall a. a -> Maybe a
Just (SDoc -> Maybe SDoc) -> SDoc -> Maybe SDoc
forall a b. (a -> b) -> a -> b
$ ShowSub -> IfaceAT -> SDoc
pprIfaceAT ShowSub
ss IfaceAT
asc
| Bool
otherwise = Maybe SDoc
forall a. Maybe a
Nothing
maybeShowSig :: IfaceClassOp -> Maybe SDoc
maybeShowSig :: IfaceClassOp -> Maybe SDoc
maybeShowSig IfaceClassOp
sg
| ShowSub -> IfaceClassOp -> Bool
forall n. HasOccName n => ShowSub -> n -> Bool
showSub ShowSub
ss IfaceClassOp
sg = SDoc -> Maybe SDoc
forall a. a -> Maybe a
Just (SDoc -> Maybe SDoc) -> SDoc -> Maybe SDoc
forall a b. (a -> b) -> a -> b
$ ShowSub -> IfaceClassOp -> SDoc
pprIfaceClassOp ShowSub
ss IfaceClassOp
sg
| Bool
otherwise = Maybe SDoc
forall a. Maybe a
Nothing
pprMinDef :: BooleanFormula IfLclName -> SDoc
pprMinDef :: BooleanFormula IfLclName -> SDoc
pprMinDef BooleanFormula IfLclName
minDef = Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless (BooleanFormula IfLclName -> Bool
forall a. BooleanFormula a -> Bool
isTrue BooleanFormula IfLclName
minDef) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"{-# MINIMAL" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
(Rational -> FastString -> SDoc)
-> Rational -> BooleanFormula FastString -> SDoc
forall a.
(Rational -> a -> SDoc) -> Rational -> BooleanFormula a -> SDoc
pprBooleanFormula
(\Rational
_ FastString
def -> Bool -> SDoc -> SDoc
cparen (FastString -> Bool
isLexSym FastString
def) (FastString -> SDoc
forall a. Outputable a => a -> SDoc
ppr FastString
def)) Rational
0 ((IfLclName -> FastString)
-> BooleanFormula IfLclName -> BooleanFormula FastString
forall a b. (a -> b) -> BooleanFormula a -> BooleanFormula b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfLclName -> FastString
ifLclNameFS BooleanFormula IfLclName
minDef) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"#-}"
suppress_bndr_sig :: SuppressBndrSig
suppress_bndr_sig = Bool -> SuppressBndrSig
SuppressBndrSig Bool
True
pprIfaceDecl ShowSub
ss (IfaceSynonym { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
tc
, ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
, ifSynRhs :: IfaceDecl -> IfaceType
ifSynRhs = IfaceType
mono_ty
, ifResKind :: IfaceDecl -> IfaceType
ifResKind = IfaceType
res_kind})
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ SDoc -> IfaceType -> SDoc
pprStandaloneKindSig SDoc
name_doc ([IfaceTyConBinder] -> IfaceType -> IfaceType
mkIfaceTyConKind [IfaceTyConBinder]
binders IfaceType
res_kind)
, SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"type" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SuppressBndrSig
-> IfaceContext
-> ShowSub
-> IfExtName
-> [IfaceTyConBinder]
-> SDoc
pprIfaceDeclHead SuppressBndrSig
suppress_bndr_sig [] ShowSub
ss IfExtName
tc [IfaceTyConBinder]
binders SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
forall doc. IsLine doc => doc
equals)
Int
2 ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ [IfaceForAllBndr] -> SDoc
pprIfaceForAll [IfaceForAllBndr]
tvs, IfaceContext -> SDoc
pprIfaceContextArr IfaceContext
theta, SDoc
ppr_tau
, Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless (IfaceType -> Bool
isIfaceLiftedTypeKind IfaceType
res_kind) (SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
res_kind) ])
]
where
([IfaceForAllBndr]
tvs, IfaceContext
theta, IfaceType
tau) = IfaceType -> ([IfaceForAllBndr], IfaceContext, IfaceType)
splitIfaceSigmaTy IfaceType
mono_ty
name_doc :: SDoc
name_doc = ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss) (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
tc)
ppr_tau :: SDoc
ppr_tau | IfExtName
tc IfExtName -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
liftedTypeKindTyConKey Bool -> Bool -> Bool
||
IfExtName
tc IfExtName -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
unrestrictedFunTyConKey Bool -> Bool -> Bool
||
IfExtName
tc IfExtName -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
constraintKindTyConKey
= (SDocContext -> SDocContext) -> SDoc -> SDoc
updSDocContext (\SDocContext
ctx -> SDocContext
ctx { sdocPrintTypeAbbreviations = False }) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
tau
| Bool
otherwise = IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
tau
suppress_bndr_sig :: SuppressBndrSig
suppress_bndr_sig = Bool -> SuppressBndrSig
SuppressBndrSig Bool
True
pprIfaceDecl ShowSub
ss (IfaceFamily { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
tycon
, ifFamFlav :: IfaceDecl -> IfaceFamTyConFlav
ifFamFlav = IfaceFamTyConFlav
rhs, ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
binders
, ifResKind :: IfaceDecl -> IfaceType
ifResKind = IfaceType
res_kind
, ifResVar :: IfaceDecl -> Maybe IfLclName
ifResVar = Maybe IfLclName
res_var, ifFamInj :: IfaceDecl -> Injectivity
ifFamInj = Injectivity
inj })
| IfaceFamTyConFlav
IfaceDataFamilyTyCon <- IfaceFamTyConFlav
rhs
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ SDoc -> IfaceType -> SDoc
pprStandaloneKindSig SDoc
name_doc ([IfaceTyConBinder] -> IfaceType -> IfaceType
mkIfaceTyConKind [IfaceTyConBinder]
binders IfaceType
res_kind)
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"data family" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SuppressBndrSig
-> IfaceContext
-> ShowSub
-> IfExtName
-> [IfaceTyConBinder]
-> SDoc
pprIfaceDeclHead SuppressBndrSig
suppress_bndr_sig [] ShowSub
ss IfExtName
tycon [IfaceTyConBinder]
binders
]
| Bool
otherwise
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ SDoc -> IfaceType -> SDoc
pprStandaloneKindSig SDoc
name_doc ([IfaceTyConBinder] -> IfaceType -> IfaceType
mkIfaceTyConKind [IfaceTyConBinder]
binders IfaceType
res_kind)
, SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"type family"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SuppressBndrSig
-> IfaceContext
-> ShowSub
-> IfExtName
-> [IfaceTyConBinder]
-> SDoc
pprIfaceDeclHead SuppressBndrSig
suppress_bndr_sig [] ShowSub
ss IfExtName
tycon [IfaceTyConBinder]
binders
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Maybe IfLclName -> Injectivity -> SDoc
pp_inj Maybe IfLclName
res_var Injectivity
inj
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ShowSub -> SDoc -> SDoc
ppShowRhs ShowSub
ss (IfaceFamTyConFlav -> SDoc
forall {doc}. IsLine doc => IfaceFamTyConFlav -> doc
pp_where IfaceFamTyConFlav
rhs))
Int
2 (ShowSub -> SDoc -> SDoc
ppShowRhs ShowSub
ss (IfaceFamTyConFlav -> SDoc
pp_rhs IfaceFamTyConFlav
rhs))
SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$
Int -> SDoc -> SDoc
nest Int
2 (ShowSub -> SDoc -> SDoc
ppShowRhs ShowSub
ss (IfaceFamTyConFlav -> SDoc
pp_branches IfaceFamTyConFlav
rhs))
]
where
name_doc :: SDoc
name_doc = ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss) (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
tycon)
pp_where :: IfaceFamTyConFlav -> doc
pp_where (IfaceClosedSynFamilyTyCon {}) = String -> doc
forall doc. IsLine doc => String -> doc
text String
"where"
pp_where IfaceFamTyConFlav
_ = doc
forall doc. IsOutput doc => doc
empty
pp_inj :: Maybe IfLclName -> Injectivity -> SDoc
pp_inj Maybe IfLclName
Nothing Injectivity
_ = SDoc
forall doc. IsOutput doc => doc
empty
pp_inj (Just IfLclName
res) Injectivity
inj
| Injective [Bool]
injectivity <- Injectivity
inj = [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep [ SDoc
forall doc. IsLine doc => doc
equals, IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfLclName
res
, IfLclName -> [Bool] -> SDoc
pp_inj_cond IfLclName
res [Bool]
injectivity]
| Bool
otherwise = [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep [ SDoc
forall doc. IsLine doc => doc
equals, IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfLclName
res ]
pp_inj_cond :: IfLclName -> [Bool] -> SDoc
pp_inj_cond IfLclName
res [Bool]
inj = case [Bool] -> [IfaceTyConBinder] -> [IfaceTyConBinder]
forall a. [Bool] -> [a] -> [a]
filterByList [Bool]
inj [IfaceTyConBinder]
binders of
[] -> SDoc
forall doc. IsOutput doc => doc
empty
[IfaceTyConBinder]
tvs -> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep [SDoc
forall doc. IsLine doc => doc
vbar, IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfLclName
res, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"->", [IfLclName] -> SDoc
forall a. Outputable a => [a] -> SDoc
interppSP ((IfaceTyConBinder -> IfLclName)
-> [IfaceTyConBinder] -> [IfLclName]
forall a b. (a -> b) -> [a] -> [b]
map IfaceTyConBinder -> IfLclName
ifTyConBinderName [IfaceTyConBinder]
tvs)]
pp_rhs :: IfaceFamTyConFlav -> SDoc
pp_rhs IfaceFamTyConFlav
IfaceDataFamilyTyCon
= ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"data")
pp_rhs IfaceFamTyConFlav
IfaceOpenSynFamilyTyCon
= ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"open")
pp_rhs IfaceFamTyConFlav
IfaceAbstractClosedSynFamilyTyCon
= ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"closed, abstract")
pp_rhs (IfaceClosedSynFamilyTyCon {})
= SDoc
forall doc. IsOutput doc => doc
empty
pp_rhs IfaceFamTyConFlav
IfaceBuiltInSynFamTyCon
= ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"built-in")
pp_branches :: IfaceFamTyConFlav -> SDoc
pp_branches (IfaceClosedSynFamilyTyCon (Just (IfExtName
ax, [IfaceAxBranch]
brs)))
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ((Int -> IfaceAxBranch -> SDoc) -> [(Int, IfaceAxBranch)] -> [SDoc]
forall a b c. (a -> b -> c) -> [(a, b)] -> [c]
unzipWith (SDoc -> Int -> IfaceAxBranch -> SDoc
pprAxBranch
(ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr
(ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss)
(IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
tycon))
) ([(Int, IfaceAxBranch)] -> [SDoc])
-> [(Int, IfaceAxBranch)] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ [Int] -> [IfaceAxBranch] -> [(Int, IfaceAxBranch)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] [IfaceAxBranch]
brs)
SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"axiom" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
ax)
pp_branches IfaceFamTyConFlav
_ = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
suppress_bndr_sig :: SuppressBndrSig
suppress_bndr_sig = Bool -> SuppressBndrSig
SuppressBndrSig Bool
True
pprIfaceDecl ShowSub
_ (IfacePatSyn { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
name,
ifPatUnivBndrs :: IfaceDecl -> [IfaceForAllSpecBndr]
ifPatUnivBndrs = [IfaceForAllSpecBndr]
univ_bndrs, ifPatExBndrs :: IfaceDecl -> [IfaceForAllSpecBndr]
ifPatExBndrs = [IfaceForAllSpecBndr]
ex_bndrs,
ifPatProvCtxt :: IfaceDecl -> IfaceContext
ifPatProvCtxt = IfaceContext
prov_ctxt, ifPatReqCtxt :: IfaceDecl -> IfaceContext
ifPatReqCtxt = IfaceContext
req_ctxt,
ifPatArgs :: IfaceDecl -> IfaceContext
ifPatArgs = IfaceContext
arg_tys, ifFieldLabels :: IfaceDecl -> [FieldLabel]
ifFieldLabels = [FieldLabel]
pat_fldlbls,
ifPatTy :: IfaceDecl -> IfaceType
ifPatTy = IfaceType
pat_ty} )
= (SDocContext -> SDoc) -> SDoc
sdocWithContext SDocContext -> SDoc
mk_msg
where
pat_keywrd :: SDoc
pat_keywrd = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"pattern"
mk_msg :: SDocContext -> SDoc
mk_msg SDocContext
sdocCtx
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ SDoc
ppr_pat_ty
, if [FieldLabel] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FieldLabel]
pat_fldlbls then SDoc
forall doc. IsOutput doc => doc
Outputable.empty
else SDoc
pat_keywrd SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprPrefixOcc IfExtName
name SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pat_body]
where
ppr_pat_ty :: SDoc
ppr_pat_ty =
SDoc -> Int -> SDoc -> SDoc
hang (SDoc
pat_keywrd SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. OutputableBndr a => a -> SDoc
pprPrefixOcc IfExtName
name)
Int
2 (SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [SDoc
univ_msg
, IfaceContext -> SDoc
pprIfaceContextArr IfaceContext
req_ctxt
, Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen Bool
insert_empty_ctxt (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens SDoc
forall doc. IsOutput doc => doc
empty SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
darrow
, SDoc
ex_msg
, IfaceContext -> SDoc
pprIfaceContextArr IfaceContext
prov_ctxt
, IfaceType -> SDoc
pprIfaceType (IfaceType -> SDoc) -> IfaceType -> SDoc
forall a b. (a -> b) -> a -> b
$ (IfaceType -> IfaceType -> IfaceType)
-> IfaceType -> IfaceContext -> IfaceType
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (FunTyFlag -> IfaceType -> IfaceType -> IfaceType -> IfaceType
IfaceFunTy FunTyFlag
visArgTypeLike IfaceType
many_ty)
IfaceType
pat_ty IfaceContext
arg_tys ])
pat_body :: SDoc
pat_body = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
forall doc. IsLine doc => doc -> [doc] -> [doc]
punctuate SDoc
forall doc. IsLine doc => doc
comma ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ (FieldLabel -> SDoc) -> [FieldLabel] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map FieldLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr [FieldLabel]
pat_fldlbls
univ_msg :: SDoc
univ_msg = [IfaceForAllBndr] -> SDoc
pprUserIfaceForAll ([IfaceForAllBndr] -> SDoc) -> [IfaceForAllBndr] -> SDoc
forall a b. (a -> b) -> a -> b
$ [IfaceForAllSpecBndr] -> [IfaceForAllBndr]
forall a. [VarBndr a Specificity] -> [VarBndr a ForAllTyFlag]
tyVarSpecToBinders [IfaceForAllSpecBndr]
univ_bndrs
ex_msg :: SDoc
ex_msg = [IfaceForAllBndr] -> SDoc
pprUserIfaceForAll ([IfaceForAllBndr] -> SDoc) -> [IfaceForAllBndr] -> SDoc
forall a b. (a -> b) -> a -> b
$ [IfaceForAllSpecBndr] -> [IfaceForAllBndr]
forall a. [VarBndr a Specificity] -> [VarBndr a ForAllTyFlag]
tyVarSpecToBinders [IfaceForAllSpecBndr]
ex_bndrs
insert_empty_ctxt :: Bool
insert_empty_ctxt = IfaceContext -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null IfaceContext
req_ctxt
Bool -> Bool -> Bool
&& Bool -> Bool
not (IfaceContext -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null IfaceContext
prov_ctxt Bool -> Bool -> Bool
&& SDocContext -> SDoc -> Bool
isEmpty SDocContext
sdocCtx SDoc
ex_msg)
pprIfaceDecl ShowSub
ss (IfaceId { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
var, ifType :: IfaceDecl -> IfaceType
ifType = IfaceType
ty,
ifIdDetails :: IfaceDecl -> IfaceIdDetails
ifIdDetails = IfaceIdDetails
details, ifIdInfo :: IfaceDecl -> IfaceIdInfo
ifIdInfo = IfaceIdInfo
info })
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ SDoc -> Int -> SDoc -> SDoc
hang (ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss) (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
var) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
dcolon)
Int
2 (ShowForAllFlag -> IfaceType -> SDoc
pprIfaceSigmaType (ShowSub -> ShowForAllFlag
ss_forall ShowSub
ss) IfaceType
ty)
, ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss (IfaceIdDetails -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceIdDetails
details)
, ShowSub -> SDoc -> SDoc
ppShowIface ShowSub
ss (IfaceIdInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceIdInfo
info) ]
pprIfaceDecl ShowSub
_ (IfaceAxiom { ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
name, ifTyCon :: IfaceDecl -> IfaceTyCon
ifTyCon = IfaceTyCon
tycon
, ifAxBranches :: IfaceDecl -> [IfaceAxBranch]
ifAxBranches = [IfaceAxBranch]
branches })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"axiom" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
name SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
dcolon)
Int
2 ([SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ (Int -> IfaceAxBranch -> SDoc) -> [(Int, IfaceAxBranch)] -> [SDoc]
forall a b c. (a -> b -> c) -> [(a, b)] -> [c]
unzipWith (SDoc -> Int -> IfaceAxBranch -> SDoc
pprAxBranch (IfaceTyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceTyCon
tycon)) ([(Int, IfaceAxBranch)] -> [SDoc])
-> [(Int, IfaceAxBranch)] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ [Int] -> [IfaceAxBranch] -> [(Int, IfaceAxBranch)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] [IfaceAxBranch]
branches)
pprCType :: Maybe CType -> SDoc
pprCType :: Maybe CType -> SDoc
pprCType Maybe CType
Nothing = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
pprCType (Just CType
cType) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"C type:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> CType -> SDoc
forall a. Outputable a => a -> SDoc
ppr CType
cType
pprRoles :: (Role -> Bool) -> SDoc -> [IfaceTyConBinder]
-> [Role] -> SDoc
pprRoles :: (Role -> Bool) -> SDoc -> [IfaceTyConBinder] -> [Role] -> SDoc
pprRoles Role -> Bool
suppress_if SDoc
tyCon [IfaceTyConBinder]
bndrs [Role]
roles
= (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocPrintExplicitKinds ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Bool
print_kinds ->
let froles :: [Role]
froles = PrintExplicitKinds -> [IfaceTyConBinder] -> [Role] -> [Role]
forall a. PrintExplicitKinds -> [IfaceTyConBinder] -> [a] -> [a]
suppressIfaceInvisibles (Bool -> PrintExplicitKinds
PrintExplicitKinds Bool
print_kinds) [IfaceTyConBinder]
bndrs [Role]
roles
in Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless ((Role -> Bool) -> [Role] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Role -> Bool
suppress_if [Role]
froles Bool -> Bool -> Bool
|| [Role] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Role]
froles) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"type role" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
tyCon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep ((Role -> SDoc) -> [Role] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map Role -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Role]
froles)
pprStandaloneKindSig :: SDoc -> IfaceType -> SDoc
pprStandaloneKindSig :: SDoc -> IfaceType -> SDoc
pprStandaloneKindSig SDoc
tyCon IfaceType
ty = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"type" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
tyCon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"::" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
ty
pprInfixIfDeclBndr :: ShowHowMuch -> OccName -> SDoc
pprInfixIfDeclBndr :: ShowHowMuch -> OccName -> SDoc
pprInfixIfDeclBndr (ShowSome Maybe (OccName -> Bool)
_ (AltPpr (Just OccName -> SDoc
ppr_bndr))) OccName
name
= Bool -> SDoc -> SDoc
pprInfixVar (OccName -> Bool
isSymOcc OccName
name) (OccName -> SDoc
ppr_bndr OccName
name)
pprInfixIfDeclBndr ShowHowMuch
_ OccName
name
= Bool -> SDoc -> SDoc
pprInfixVar (OccName -> Bool
isSymOcc OccName
name) (OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
name)
pprPrefixIfDeclBndr :: ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr :: ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowHeader (AltPpr (Just OccName -> SDoc
ppr_bndr))) OccName
name
= OccName -> SDoc -> SDoc
parenSymOcc OccName
name (OccName -> SDoc
ppr_bndr OccName
name)
pprPrefixIfDeclBndr (ShowSome Maybe (OccName -> Bool)
_ (AltPpr (Just OccName -> SDoc
ppr_bndr))) OccName
name
= OccName -> SDoc -> SDoc
parenSymOcc OccName
name (OccName -> SDoc
ppr_bndr OccName
name)
pprPrefixIfDeclBndr ShowHowMuch
_ OccName
name
= OccName -> SDoc -> SDoc
parenSymOcc OccName
name (OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
name)
instance Outputable IfaceClassOp where
ppr :: IfaceClassOp -> SDoc
ppr = ShowSub -> IfaceClassOp -> SDoc
pprIfaceClassOp ShowSub
showToIface
pprIfaceClassOp :: ShowSub -> IfaceClassOp -> SDoc
pprIfaceClassOp :: ShowSub -> IfaceClassOp -> SDoc
pprIfaceClassOp ShowSub
ss (IfaceClassOp IfExtName
n IfaceType
ty Maybe (DefMethSpec IfaceType)
dm)
= IfExtName -> IfaceType -> SDoc
pp_sig IfExtName
n IfaceType
ty SDoc -> SDoc -> SDoc
forall doc. IsDoc doc => doc -> doc -> doc
$$ SDoc
generic_dm
where
generic_dm :: SDoc
generic_dm | Just (GenericDM IfaceType
dm_ty) <- Maybe (DefMethSpec IfaceType)
dm
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"default" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> IfaceType -> SDoc
pp_sig IfExtName
n IfaceType
dm_ty
| Bool
otherwise
= SDoc
forall doc. IsOutput doc => doc
empty
pp_sig :: IfExtName -> IfaceType -> SDoc
pp_sig IfExtName
n IfaceType
ty
= ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss) (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
n)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
dcolon
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ShowForAllFlag -> IfaceType -> SDoc
pprIfaceSigmaType ShowForAllFlag
ShowForAllWhen IfaceType
ty
instance Outputable IfaceAT where
ppr :: IfaceAT -> SDoc
ppr = ShowSub -> IfaceAT -> SDoc
pprIfaceAT ShowSub
showToIface
pprIfaceAT :: ShowSub -> IfaceAT -> SDoc
pprIfaceAT :: ShowSub -> IfaceAT -> SDoc
pprIfaceAT ShowSub
ss (IfaceAT IfaceDecl
d Maybe IfaceType
mb_def)
= [SDoc] -> SDoc
forall doc. IsDoc doc => [doc] -> doc
vcat [ ShowSub -> IfaceDecl -> SDoc
pprIfaceDecl ShowSub
ss IfaceDecl
d
, case Maybe IfaceType
mb_def of
Maybe IfaceType
Nothing -> SDoc
forall doc. IsOutput doc => doc
Outputable.empty
Just IfaceType
rhs -> Int -> SDoc -> SDoc
nest Int
2 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Default:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
rhs ]
instance Outputable IfaceTyConParent where
ppr :: IfaceTyConParent -> SDoc
ppr IfaceTyConParent
p = IfaceTyConParent -> SDoc
pprIfaceTyConParent IfaceTyConParent
p
pprIfaceTyConParent :: IfaceTyConParent -> SDoc
pprIfaceTyConParent :: IfaceTyConParent -> SDoc
pprIfaceTyConParent IfaceTyConParent
IfNoParent
= SDoc
forall doc. IsOutput doc => doc
Outputable.empty
pprIfaceTyConParent (IfDataInstance IfExtName
_ IfaceTyCon
tc IfaceAppArgs
tys)
= PprPrec -> IfaceTyCon -> IfaceAppArgs -> SDoc
pprIfaceTypeApp PprPrec
topPrec IfaceTyCon
tc IfaceAppArgs
tys
pprIfaceDeclHead :: SuppressBndrSig
-> IfaceContext -> ShowSub -> Name
-> [IfaceTyConBinder]
-> SDoc
pprIfaceDeclHead :: SuppressBndrSig
-> IfaceContext
-> ShowSub
-> IfExtName
-> [IfaceTyConBinder]
-> SDoc
pprIfaceDeclHead SuppressBndrSig
suppress_sig IfaceContext
context ShowSub
ss IfExtName
tc_occ [IfaceTyConBinder]
bndrs
= (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocPrintExplicitKinds ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Bool
print_kinds ->
[SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ IfaceContext -> SDoc
pprIfaceContextArr IfaceContext
context
, ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr (ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss) (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
tc_occ)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SuppressBndrSig -> [IfaceTyConBinder] -> SDoc
pprIfaceTyConBinders SuppressBndrSig
suppress_sig
(PrintExplicitKinds
-> [IfaceTyConBinder] -> [IfaceTyConBinder] -> [IfaceTyConBinder]
forall a. PrintExplicitKinds -> [IfaceTyConBinder] -> [a] -> [a]
suppressIfaceInvisibles (Bool -> PrintExplicitKinds
PrintExplicitKinds Bool
print_kinds) [IfaceTyConBinder]
bndrs [IfaceTyConBinder]
bndrs) ]
pprIfaceConDecl :: ShowSub -> Bool
-> IfaceTopBndr
-> [IfaceTyConBinder]
-> IfaceTyConParent
-> IfaceConDecl -> SDoc
pprIfaceConDecl :: ShowSub
-> Bool
-> IfExtName
-> [IfaceTyConBinder]
-> IfaceTyConParent
-> IfaceConDecl
-> SDoc
pprIfaceConDecl ShowSub
ss Bool
gadt_style IfExtName
tycon [IfaceTyConBinder]
tc_binders IfaceTyConParent
parent
(IfCon { ifConName :: IfaceConDecl -> IfExtName
ifConName = IfExtName
name, ifConInfix :: IfaceConDecl -> Bool
ifConInfix = Bool
is_infix,
ifConUserTvBinders :: IfaceConDecl -> [IfaceForAllSpecBndr]
ifConUserTvBinders = [IfaceForAllSpecBndr]
user_tvbs,
ifConEqSpec :: IfaceConDecl -> [IfaceTvBndr]
ifConEqSpec = [IfaceTvBndr]
eq_spec, ifConCtxt :: IfaceConDecl -> IfaceContext
ifConCtxt = IfaceContext
ctxt, ifConArgTys :: IfaceConDecl -> [(IfaceType, IfaceType)]
ifConArgTys = [(IfaceType, IfaceType)]
arg_tys,
ifConStricts :: IfaceConDecl -> [IfaceBang]
ifConStricts = [IfaceBang]
stricts, ifConFields :: IfaceConDecl -> [FieldLabel]
ifConFields = [FieldLabel]
fields })
| Bool
gadt_style = SDoc
pp_prefix_con SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
ppr_gadt_ty
| Bool
otherwise = SDoc -> SDoc
ppr_ex_quant SDoc
pp_h98_con
where
pp_h98_con :: SDoc
pp_h98_con
| Bool -> Bool
not ([FieldLabel] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FieldLabel]
fields) = SDoc
pp_prefix_con SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_field_args
| Bool
is_infix
, [SDoc
ty1, SDoc
ty2] <- [SDoc]
pp_args
= [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ SDoc
ty1
, ShowHowMuch -> OccName -> SDoc
pprInfixIfDeclBndr ShowHowMuch
how_much (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
name)
, SDoc
ty2]
| Bool
otherwise = SDoc
pp_prefix_con SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [SDoc]
pp_args
how_much :: ShowHowMuch
how_much = ShowSub -> ShowHowMuch
ss_how_much ShowSub
ss
tys_w_strs :: [(IfaceBang, IfaceType)]
tys_w_strs :: [(IfaceBang, IfaceType)]
tys_w_strs = [IfaceBang] -> IfaceContext -> [(IfaceBang, IfaceType)]
forall a b. [a] -> [b] -> [(a, b)]
zip [IfaceBang]
stricts (((IfaceType, IfaceType) -> IfaceType)
-> [(IfaceType, IfaceType)] -> IfaceContext
forall a b. (a -> b) -> [a] -> [b]
map (IfaceType, IfaceType) -> IfaceType
forall a b. (a, b) -> b
snd [(IfaceType, IfaceType)]
arg_tys)
pp_prefix_con :: SDoc
pp_prefix_con = ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr ShowHowMuch
how_much (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
name)
ex_tvbs :: [IfaceForAllSpecBndr]
ex_tvbs = [IfaceTyConBinder]
-> [IfaceForAllSpecBndr] -> [IfaceForAllSpecBndr]
forall b a. [b] -> [a] -> [a]
dropList [IfaceTyConBinder]
tc_binders [IfaceForAllSpecBndr]
user_tvbs
ppr_ex_quant :: SDoc -> SDoc
ppr_ex_quant = [IfaceForAllBndr] -> IfaceContext -> SDoc -> SDoc
pprIfaceForAllPartMust ([IfaceForAllSpecBndr] -> [IfaceForAllBndr]
ifaceForAllSpecToBndrs [IfaceForAllSpecBndr]
ex_tvbs) IfaceContext
ctxt
pp_gadt_res_ty :: SDoc
pp_gadt_res_ty = [IfaceTvBndr] -> SDoc
mk_user_con_res_ty [IfaceTvBndr]
eq_spec
ppr_gadt_ty :: SDoc
ppr_gadt_ty = [IfaceForAllBndr] -> IfaceContext -> SDoc -> SDoc
pprIfaceForAllPart ([IfaceForAllSpecBndr] -> [IfaceForAllBndr]
ifaceForAllSpecToBndrs [IfaceForAllSpecBndr]
user_tvbs) IfaceContext
ctxt SDoc
pp_tau
pp_tau :: SDoc
pp_tau | [FieldLabel] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FieldLabel]
fields
= case [SDoc]
pp_args [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ [SDoc
pp_gadt_res_ty] of
(SDoc
t:[SDoc]
ts) -> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
fsep (SDoc
t SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
: String
-> ((IfaceType, IfaceType) -> SDoc -> SDoc)
-> [(IfaceType, IfaceType)]
-> [SDoc]
-> [SDoc]
forall a b c.
HasDebugCallStack =>
String -> (a -> b -> c) -> [a] -> [b] -> [c]
zipWithEqual String
"pprIfaceConDecl" (\(IfaceType
w,IfaceType
_) SDoc
d -> IfaceType -> SDoc
ppr_arr IfaceType
w SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
d)
[(IfaceType, IfaceType)]
arg_tys [SDoc]
ts)
[] -> String -> SDoc
forall a. HasCallStack => String -> a
panic String
"pp_con_taus"
| Bool
otherwise
= [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [SDoc
pp_field_args, SDoc
arrow SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_gadt_res_ty]
ppr_arr :: IfaceType -> SDoc
ppr_arr IfaceType
w = (SDocContext -> Bool) -> (Bool -> SDoc) -> SDoc
forall a. (SDocContext -> a) -> (a -> SDoc) -> SDoc
sdocOption SDocContext -> Bool
sdocLinearTypes ((Bool -> SDoc) -> SDoc) -> (Bool -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \Bool
linearTypes ->
if Bool
linearTypes
then FunTyFlag -> IfaceType -> SDoc
pprTypeArrow FunTyFlag
visArgTypeLike IfaceType
w
else SDoc
arrow
ppr_bang :: IfaceBang -> SDoc
ppr_bang IfaceBang
IfNoBang = SDoc -> SDoc
forall doc. IsOutput doc => doc -> doc
whenPprDebug (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'_'
ppr_bang IfaceBang
IfStrict = Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'!'
ppr_bang IfaceBang
IfUnpack = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"{-# UNPACK #-}"
ppr_bang (IfUnpackCo IfaceCoercion
co) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"! {-# UNPACK #-}" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<>
IfaceCoercion -> SDoc
pprParendIfaceCoercion IfaceCoercion
co
pprFieldArgTy, pprArgTy :: (IfaceBang, IfaceType) -> SDoc
pprFieldArgTy :: (IfaceBang, IfaceType) -> SDoc
pprFieldArgTy (IfaceBang
bang, IfaceType
ty) = PprPrec -> IfaceBang -> IfaceType -> SDoc
ppr_arg_ty (IfaceBang -> PprPrec
bang_prec IfaceBang
bang) IfaceBang
bang IfaceType
ty
pprArgTy :: (IfaceBang, IfaceType) -> SDoc
pprArgTy (IfaceBang
bang, IfaceType
ty) = PprPrec -> IfaceBang -> IfaceType -> SDoc
ppr_arg_ty (PprPrec -> PprPrec -> PprPrec
forall a. Ord a => a -> a -> a
max PprPrec
gadt_prec (IfaceBang -> PprPrec
bang_prec IfaceBang
bang)) IfaceBang
bang IfaceType
ty
ppr_arg_ty :: PprPrec -> IfaceBang -> IfaceType -> SDoc
ppr_arg_ty :: PprPrec -> IfaceBang -> IfaceType -> SDoc
ppr_arg_ty PprPrec
prec IfaceBang
bang IfaceType
ty = IfaceBang -> SDoc
ppr_bang IfaceBang
bang SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> PprPrec -> IfaceType -> SDoc
pprPrecIfaceType PprPrec
prec IfaceType
ty
gadt_prec :: PprPrec
gadt_prec :: PprPrec
gadt_prec
| Bool
gadt_style = PprPrec
funPrec
| Bool
otherwise = PprPrec
appPrec
bang_prec :: IfaceBang -> PprPrec
bang_prec :: IfaceBang -> PprPrec
bang_prec IfaceBang
IfNoBang = PprPrec
topPrec
bang_prec IfaceBang
IfStrict = PprPrec
appPrec
bang_prec IfaceBang
IfUnpack = PprPrec
appPrec
bang_prec IfUnpackCo{} = PprPrec
appPrec
pp_args :: [SDoc]
pp_args :: [SDoc]
pp_args = ((IfaceBang, IfaceType) -> SDoc)
-> [(IfaceBang, IfaceType)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (IfaceBang, IfaceType) -> SDoc
pprArgTy [(IfaceBang, IfaceType)]
tys_w_strs
pp_field_args :: SDoc
pp_field_args :: SDoc
pp_field_args = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
forall doc. IsLine doc => doc -> [doc] -> [doc]
punctuate SDoc
forall doc. IsLine doc => doc
comma ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ [Maybe SDoc] -> [SDoc]
ppr_trim ([Maybe SDoc] -> [SDoc]) -> [Maybe SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$
(FieldLabel -> (IfaceBang, IfaceType) -> Maybe SDoc)
-> [FieldLabel] -> [(IfaceBang, IfaceType)] -> [Maybe SDoc]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith FieldLabel -> (IfaceBang, IfaceType) -> Maybe SDoc
maybe_show_label [FieldLabel]
fields [(IfaceBang, IfaceType)]
tys_w_strs
maybe_show_label :: FieldLabel -> (IfaceBang, IfaceType) -> Maybe SDoc
maybe_show_label :: FieldLabel -> (IfaceBang, IfaceType) -> Maybe SDoc
maybe_show_label FieldLabel
lbl (IfaceBang, IfaceType)
bty
| ShowSub -> IfExtName -> Bool
forall n. HasOccName n => ShowSub -> n -> Bool
showSub ShowSub
ss IfExtName
sel = SDoc -> Maybe SDoc
forall a. a -> Maybe a
Just (ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr ShowHowMuch
how_much OccName
occ
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (IfaceBang, IfaceType) -> SDoc
pprFieldArgTy (IfaceBang, IfaceType)
bty)
| Bool
otherwise = Maybe SDoc
forall a. Maybe a
Nothing
where
sel :: IfExtName
sel = FieldLabel -> IfExtName
flSelector FieldLabel
lbl
occ :: OccName
occ = IfExtName -> OccName
nameOccName IfExtName
sel
mk_user_con_res_ty :: IfaceEqSpec -> SDoc
mk_user_con_res_ty :: [IfaceTvBndr] -> SDoc
mk_user_con_res_ty [IfaceTvBndr]
eq_spec
| IfDataInstance IfExtName
_ IfaceTyCon
tc IfaceAppArgs
tys <- IfaceTyConParent
parent
= IfaceType -> SDoc
pprIfaceType (IfaceTyCon -> IfaceAppArgs -> IfaceType
IfaceTyConApp IfaceTyCon
tc (IfaceTySubst -> IfaceAppArgs -> IfaceAppArgs
substIfaceAppArgs IfaceTySubst
gadt_subst IfaceAppArgs
tys))
| Bool
otherwise
= IfaceTySubst -> SDoc
ppr_tc_app IfaceTySubst
gadt_subst
where
gadt_subst :: IfaceTySubst
gadt_subst = [IfaceTvBndr] -> IfaceTySubst
mkIfaceTySubst [IfaceTvBndr]
eq_spec
ppr_tc_app :: IfaceTySubst -> SDoc
ppr_tc_app IfaceTySubst
gadt_subst =
ShowHowMuch -> OccName -> SDoc
pprPrefixIfDeclBndr ShowHowMuch
how_much (IfExtName -> OccName
forall name. HasOccName name => name -> OccName
occName IfExtName
tycon)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceAppArgs -> SDoc
pprParendIfaceAppArgs
(IfaceTySubst -> IfaceAppArgs -> IfaceAppArgs
substIfaceAppArgs IfaceTySubst
gadt_subst ([IfaceTyConBinder] -> IfaceAppArgs
mk_tc_app_args [IfaceTyConBinder]
tc_binders))
mk_tc_app_args :: [IfaceTyConBinder] -> IfaceAppArgs
mk_tc_app_args :: [IfaceTyConBinder] -> IfaceAppArgs
mk_tc_app_args [] = IfaceAppArgs
IA_Nil
mk_tc_app_args (Bndr IfaceBndr
bndr TyConBndrVis
vis:[IfaceTyConBinder]
tc_bndrs) =
IfaceType -> ForAllTyFlag -> IfaceAppArgs -> IfaceAppArgs
IA_Arg (IfLclName -> IfaceType
IfaceTyVar (IfaceBndr -> IfLclName
ifaceBndrName IfaceBndr
bndr)) (TyConBndrVis -> ForAllTyFlag
tyConBndrVisForAllTyFlag TyConBndrVis
vis)
([IfaceTyConBinder] -> IfaceAppArgs
mk_tc_app_args [IfaceTyConBinder]
tc_bndrs)
instance Outputable IfaceRule where
ppr :: IfaceRule -> SDoc
ppr (IfaceRule { ifRuleName :: IfaceRule -> FastString
ifRuleName = FastString
name, ifActivation :: IfaceRule -> Activation
ifActivation = Activation
act, ifRuleBndrs :: IfaceRule -> [IfaceBndr]
ifRuleBndrs = [IfaceBndr]
bndrs,
ifRuleHead :: IfaceRule -> IfExtName
ifRuleHead = IfExtName
fn, ifRuleArgs :: IfaceRule -> [IfaceExpr]
ifRuleArgs = [IfaceExpr]
args, ifRuleRhs :: IfaceRule -> IfaceExpr
ifRuleRhs = IfaceExpr
rhs,
ifRuleOrph :: IfaceRule -> IsOrphan
ifRuleOrph = IsOrphan
orph })
= [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep [ FastString -> SDoc
pprRuleName FastString
name
, if IsOrphan -> Bool
isOrphan IsOrphan
orph then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[orphan]" else SDoc
forall doc. IsOutput doc => doc
Outputable.empty
, Activation -> SDoc
forall a. Outputable a => a -> SDoc
ppr Activation
act
, SDoc
pp_foralls ]
, Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
fn SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep ((IfaceExpr -> SDoc) -> [IfaceExpr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceExpr -> SDoc
pprParendIfaceExpr [IfaceExpr]
args),
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"=" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceExpr -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceExpr
rhs]) ]
where
pp_foralls :: SDoc
pp_foralls = Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppUnless ([IfaceBndr] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceBndr]
bndrs) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc
forAllLit SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [IfaceBndr] -> SDoc
pprIfaceBndrs [IfaceBndr]
bndrs SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
dot
instance Outputable IfaceDefault where
ppr :: IfaceDefault -> SDoc
ppr (IfaceDefault { ifDefaultCls :: IfaceDefault -> IfaceTyCon
ifDefaultCls = IfaceTyCon
cls, ifDefaultTys :: IfaceDefault -> IfaceContext
ifDefaultTys = IfaceContext
tcs })
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"default" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceTyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceTyCon
cls SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens ((IfaceType -> SDoc) -> IfaceContext -> SDoc
forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceContext
tcs)
instance Outputable IfaceClsInst where
ppr :: IfaceClsInst -> SDoc
ppr (IfaceClsInst { ifDFun :: IfaceClsInst -> IfExtName
ifDFun = IfExtName
dfun_id, ifOFlag :: IfaceClsInst -> OverlapFlag
ifOFlag = OverlapFlag
flag
, ifInstCls :: IfaceClsInst -> IfExtName
ifInstCls = IfExtName
cls, ifInstTys :: IfaceClsInst -> [Maybe IfaceTyCon]
ifInstTys = [Maybe IfaceTyCon]
mb_tcs
, ifInstOrph :: IfaceClsInst -> IsOrphan
ifInstOrph = IsOrphan
orph })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"instance" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> OverlapFlag -> SDoc
forall a. Outputable a => a -> SDoc
ppr OverlapFlag
flag
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (if IsOrphan -> Bool
isOrphan IsOrphan
orph then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[orphan]" else SDoc
forall doc. IsOutput doc => doc
Outputable.empty)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
cls SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets ((Maybe IfaceTyCon -> SDoc) -> [Maybe IfaceTyCon] -> SDoc
forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas Maybe IfaceTyCon -> SDoc
ppr_rough [Maybe IfaceTyCon]
mb_tcs))
Int
2 (SDoc
forall doc. IsLine doc => doc
equals SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
dfun_id)
instance Outputable IfaceFamInst where
ppr :: IfaceFamInst -> SDoc
ppr (IfaceFamInst { ifFamInstFam :: IfaceFamInst -> IfExtName
ifFamInstFam = IfExtName
fam, ifFamInstTys :: IfaceFamInst -> [Maybe IfaceTyCon]
ifFamInstTys = [Maybe IfaceTyCon]
mb_tcs
, ifFamInstAxiom :: IfaceFamInst -> IfExtName
ifFamInstAxiom = IfExtName
tycon_ax, ifFamInstOrph :: IfaceFamInst -> IsOrphan
ifFamInstOrph = IsOrphan
orph })
= SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"family instance"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (if IsOrphan -> Bool
isOrphan IsOrphan
orph then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[orphan]" else SDoc
forall doc. IsOutput doc => doc
Outputable.empty)
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
fam SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (Maybe IfaceTyCon -> SDoc) -> [Maybe IfaceTyCon] -> SDoc
forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas (SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (SDoc -> SDoc)
-> (Maybe IfaceTyCon -> SDoc) -> Maybe IfaceTyCon -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe IfaceTyCon -> SDoc
ppr_rough) [Maybe IfaceTyCon]
mb_tcs)
Int
2 (SDoc
forall doc. IsLine doc => doc
equals SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
tycon_ax)
ppr_rough :: Maybe IfaceTyCon -> SDoc
ppr_rough :: Maybe IfaceTyCon -> SDoc
ppr_rough Maybe IfaceTyCon
Nothing = SDoc
forall doc. IsLine doc => doc
dot
ppr_rough (Just IfaceTyCon
tc) = IfaceTyCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceTyCon
tc
instance Outputable IfaceExpr where
ppr :: IfaceExpr -> SDoc
ppr IfaceExpr
e = (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
e
noParens :: SDoc -> SDoc
noParens :: SDoc -> SDoc
noParens SDoc
pp = SDoc
pp
pprParendIfaceExpr :: IfaceExpr -> SDoc
pprParendIfaceExpr :: IfaceExpr -> SDoc
pprParendIfaceExpr = (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens
pprIfaceExpr :: (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr :: (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
_ (IfaceLcl IfLclName
v) = IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfLclName
v
pprIfaceExpr SDoc -> SDoc
_ (IfaceExt IfExtName
v) = IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
v
pprIfaceExpr SDoc -> SDoc
_ (IfaceLit Literal
l) = Literal -> SDoc
forall a. Outputable a => a -> SDoc
ppr Literal
l
pprIfaceExpr SDoc -> SDoc
_ (IfaceFCall ForeignCall
cc IfaceType
ty) = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (ForeignCall -> SDoc
forall a. Outputable a => a -> SDoc
ppr ForeignCall
cc SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
ty)
pprIfaceExpr SDoc -> SDoc
_ (IfaceType IfaceType
ty) = Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'@' SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> IfaceType -> SDoc
pprParendIfaceType IfaceType
ty
pprIfaceExpr SDoc -> SDoc
_ (IfaceCo IfaceCoercion
co) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"@~" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> IfaceCoercion -> SDoc
pprParendIfaceCoercion IfaceCoercion
co
pprIfaceExpr SDoc -> SDoc
_ (IfaceTuple TupleSort
c [IfaceExpr]
as) = TupleSort -> SDoc -> SDoc
tupleParens TupleSort
c ((IfaceExpr -> SDoc) -> [IfaceExpr] -> SDoc
forall a. (a -> SDoc) -> [a] -> SDoc
pprWithCommas IfaceExpr -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfaceExpr]
as)
pprIfaceExpr SDoc -> SDoc
_ (IfaceLitRubbish TypeOrConstraint
tc IfaceType
r)
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"RUBBISH"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> (case TypeOrConstraint
tc of { TypeOrConstraint
TypeLike -> SDoc
forall doc. IsOutput doc => doc
empty; TypeOrConstraint
ConstraintLike -> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[c]" })
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
r)
pprIfaceExpr SDoc -> SDoc
add_par app :: IfaceExpr
app@(IfaceApp IfaceExpr
_ IfaceExpr
_) = SDoc -> SDoc
add_par (IfaceExpr -> [SDoc] -> SDoc
pprIfaceApp IfaceExpr
app [])
pprIfaceExpr SDoc -> SDoc
add_par i :: IfaceExpr
i@(IfaceLam IfaceLamBndr
_ IfaceExpr
_)
= SDoc -> SDoc
add_par ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'\\' SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep ((IfaceLamBndr -> SDoc) -> [IfaceLamBndr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceLamBndr -> SDoc
pprIfaceLamBndr [IfaceLamBndr]
bndrs) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
arrow,
(SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
body])
where
([IfaceLamBndr]
bndrs,IfaceExpr
body) = [IfaceLamBndr] -> IfaceExpr -> ([IfaceLamBndr], IfaceExpr)
collect [] IfaceExpr
i
collect :: [IfaceLamBndr] -> IfaceExpr -> ([IfaceLamBndr], IfaceExpr)
collect [IfaceLamBndr]
bs (IfaceLam IfaceLamBndr
b IfaceExpr
e) = [IfaceLamBndr] -> IfaceExpr -> ([IfaceLamBndr], IfaceExpr)
collect (IfaceLamBndr
bIfaceLamBndr -> [IfaceLamBndr] -> [IfaceLamBndr]
forall a. a -> [a] -> [a]
:[IfaceLamBndr]
bs) IfaceExpr
e
collect [IfaceLamBndr]
bs IfaceExpr
e = ([IfaceLamBndr] -> [IfaceLamBndr]
forall a. [a] -> [a]
reverse [IfaceLamBndr]
bs, IfaceExpr
e)
pprIfaceExpr SDoc -> SDoc
add_par (IfaceECase IfaceExpr
scrut IfaceType
ty)
= SDoc -> SDoc
add_par ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"case" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
scrut
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ret_ty" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceType -> SDoc
pprParendIfaceType IfaceType
ty
, String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"of {}" ])
pprIfaceExpr SDoc -> SDoc
add_par (IfaceCase IfaceExpr
scrut IfLclName
bndr [IfaceAlt IfaceConAlt
con [IfLclName]
bs IfaceExpr
rhs])
= SDoc -> SDoc
add_par ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"case"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
scrut SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"of"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfLclName
bndr SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'{' SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceConAlt -> [IfLclName] -> SDoc
ppr_con_bs IfaceConAlt
con [IfLclName]
bs SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
arrow,
(SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
rhs SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'}'])
pprIfaceExpr SDoc -> SDoc
add_par (IfaceCase IfaceExpr
scrut IfLclName
bndr [IfaceAlt]
alts)
= SDoc -> SDoc
add_par ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"case"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
scrut SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"of"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfLclName
bndr SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'{',
Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep ((IfaceAlt -> SDoc) -> [IfaceAlt] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceAlt -> SDoc
pprIfaceAlt [IfaceAlt]
alts)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'}'])
pprIfaceExpr SDoc -> SDoc
_ (IfaceCast IfaceExpr
expr IfaceCoercion
co)
= [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [IfaceExpr -> SDoc
pprParendIfaceExpr IfaceExpr
expr,
Int -> SDoc -> SDoc
nest Int
2 (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"`cast`"),
IfaceCoercion -> SDoc
pprParendIfaceCoercion IfaceCoercion
co]
pprIfaceExpr SDoc -> SDoc
add_par (IfaceLet (IfaceNonRec IfaceLetBndr
b IfaceExpr
rhs) IfaceExpr
body)
= SDoc -> SDoc
add_par ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"let {",
Int -> SDoc -> SDoc
nest Int
2 ((IfaceLetBndr, IfaceExpr) -> SDoc
ppr_bind (IfaceLetBndr
b, IfaceExpr
rhs)),
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"} in",
(SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
body])
pprIfaceExpr SDoc -> SDoc
add_par (IfaceLet (IfaceRec [(IfaceLetBndr, IfaceExpr)]
pairs) IfaceExpr
body)
= SDoc -> SDoc
add_par ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"letrec {",
Int -> SDoc -> SDoc
nest Int
2 ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep (((IfaceLetBndr, IfaceExpr) -> SDoc)
-> [(IfaceLetBndr, IfaceExpr)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (IfaceLetBndr, IfaceExpr) -> SDoc
ppr_bind [(IfaceLetBndr, IfaceExpr)]
pairs)),
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"} in",
(SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
body])
pprIfaceExpr SDoc -> SDoc
add_par (IfaceTick IfaceTickish
tickish IfaceExpr
e)
= SDoc -> SDoc
add_par (IfaceTickish -> SDoc
pprIfaceTickish IfaceTickish
tickish SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
e)
pprIfaceAlt :: IfaceAlt -> SDoc
pprIfaceAlt :: IfaceAlt -> SDoc
pprIfaceAlt (IfaceAlt IfaceConAlt
con [IfLclName]
bs IfaceExpr
rhs)
= [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [IfaceConAlt -> [IfLclName] -> SDoc
ppr_con_bs IfaceConAlt
con [IfLclName]
bs, SDoc
arrow SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
rhs]
ppr_con_bs :: IfaceConAlt -> [IfLclName] -> SDoc
ppr_con_bs :: IfaceConAlt -> [IfLclName] -> SDoc
ppr_con_bs IfaceConAlt
con [IfLclName]
bs = IfaceConAlt -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceConAlt
con SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
hsep ((IfLclName -> SDoc) -> [IfLclName] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfLclName]
bs)
ppr_bind :: (IfaceLetBndr, IfaceExpr) -> SDoc
ppr_bind :: (IfaceLetBndr, IfaceExpr) -> SDoc
ppr_bind (IfLetBndr IfLclName
b IfaceType
ty IfaceIdInfo
info JoinPointHood
ji, IfaceExpr
rhs)
= [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [SDoc -> Int -> SDoc -> SDoc
hang (IfLclName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfLclName
b SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceType -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceType
ty) Int
2 (JoinPointHood -> SDoc
forall a. Outputable a => a -> SDoc
ppr JoinPointHood
ji SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceIdInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceIdInfo
info),
SDoc
forall doc. IsLine doc => doc
equals SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> (SDoc -> SDoc) -> IfaceExpr -> SDoc
pprIfaceExpr SDoc -> SDoc
noParens IfaceExpr
rhs]
pprIfaceTickish :: IfaceTickish -> SDoc
pprIfaceTickish :: IfaceTickish -> SDoc
pprIfaceTickish (IfaceHpcTick Module
m Int
ix)
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"tick" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
m SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
ix)
pprIfaceTickish (IfaceSCC CostCentre
cc Bool
tick Bool
scope)
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (CostCentre -> SDoc
pprCostCentreCore CostCentre
cc SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bool
tick SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bool
scope)
pprIfaceTickish (IfaceSource RealSrcSpan
src FastString
_names)
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (Bool -> RealSrcSpan -> SDoc
pprUserRealSpan Bool
True RealSrcSpan
src)
pprIfaceTickish (IfaceBreakpoint Int
m [IfaceExpr]
ix Module
fvs)
= SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"break" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
m SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [IfaceExpr] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfaceExpr]
ix SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
fvs)
pprIfaceApp :: IfaceExpr -> [SDoc] -> SDoc
pprIfaceApp :: IfaceExpr -> [SDoc] -> SDoc
pprIfaceApp (IfaceApp IfaceExpr
fun IfaceExpr
arg) [SDoc]
args = IfaceExpr -> [SDoc] -> SDoc
pprIfaceApp IfaceExpr
fun ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$
Int -> SDoc -> SDoc
nest Int
2 (IfaceExpr -> SDoc
pprParendIfaceExpr IfaceExpr
arg) SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
: [SDoc]
args
pprIfaceApp IfaceExpr
fun [SDoc]
args = [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep (IfaceExpr -> SDoc
pprParendIfaceExpr IfaceExpr
fun SDoc -> [SDoc] -> [SDoc]
forall a. a -> [a] -> [a]
: [SDoc]
args)
instance Outputable IfaceConAlt where
ppr :: IfaceConAlt -> SDoc
ppr IfaceConAlt
IfaceDefaultAlt = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"DEFAULT"
ppr (IfaceLitAlt Literal
l) = Literal -> SDoc
forall a. Outputable a => a -> SDoc
ppr Literal
l
ppr (IfaceDataAlt IfExtName
d) = IfExtName -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfExtName
d
instance Outputable IfaceIdDetails where
ppr :: IfaceIdDetails -> SDoc
ppr IfaceIdDetails
IfVanillaId = SDoc
forall doc. IsOutput doc => doc
Outputable.empty
ppr (IfWorkerLikeId [CbvMark]
dmd) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"StrWork" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens ([CbvMark] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [CbvMark]
dmd)
ppr (IfRecSelId Either IfaceTyCon IfaceDecl
tc IfExtName
_c Bool
b FieldLabel
_fl) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"RecSel" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Either IfaceTyCon IfaceDecl -> SDoc
forall a. Outputable a => a -> SDoc
ppr Either IfaceTyCon IfaceDecl
tc
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> if Bool
b
then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"<naughty>"
else SDoc
forall doc. IsOutput doc => doc
Outputable.empty
ppr IfaceIdDetails
IfDFunId = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"DFunId"
instance Outputable IfaceInfoItem where
ppr :: IfaceInfoItem -> SDoc
ppr (HsUnfold Bool
lb IfaceUnfolding
unf) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Unfolding"
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Bool -> SDoc -> SDoc
forall doc. IsOutput doc => Bool -> doc -> doc
ppWhen Bool
lb (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(loop-breaker)")
SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
colon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceUnfolding -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceUnfolding
unf
ppr (HsInline InlinePragma
prag) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Inline:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> InlinePragma -> SDoc
forall a. Outputable a => a -> SDoc
ppr InlinePragma
prag
ppr (HsArity Int
arity) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Arity:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
arity
ppr (HsDmdSig DmdSig
str) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Strictness:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> DmdSig -> SDoc
forall a. Outputable a => a -> SDoc
ppr DmdSig
str
ppr (HsCprSig CprSig
cpr) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"CPR:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> CprSig -> SDoc
forall a. Outputable a => a -> SDoc
ppr CprSig
cpr
ppr IfaceInfoItem
HsNoCafRefs = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"HasNoCafRefs"
ppr (HsLFInfo IfaceLFInfo
lf_info) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LambdaFormInfo:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfaceLFInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceLFInfo
lf_info
ppr (HsTagSig TagSig
tag_sig) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"TagSig:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> TagSig -> SDoc
forall a. Outputable a => a -> SDoc
ppr TagSig
tag_sig
instance Outputable IfaceUnfolding where
ppr :: IfaceUnfolding -> SDoc
ppr (IfCoreUnfold UnfoldingSource
src IfUnfoldingCache
_ IfGuidance
guide IfaceExpr
e)
= [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Core:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> UnfoldingSource -> SDoc
forall a. Outputable a => a -> SDoc
ppr UnfoldingSource
src SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> IfGuidance -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfGuidance
guide, IfaceExpr -> SDoc
forall a. Outputable a => a -> SDoc
ppr IfaceExpr
e ]
ppr (IfDFunUnfold [IfaceBndr]
bs [IfaceExpr]
es) = SDoc -> Int -> SDoc -> SDoc
hang (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"DFun:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep ((IfaceBndr -> SDoc) -> [IfaceBndr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceBndr -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfaceBndr]
bs) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
dot)
Int
2 ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep ((IfaceExpr -> SDoc) -> [IfaceExpr] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceExpr -> SDoc
pprParendIfaceExpr [IfaceExpr]
es))
instance Outputable IfGuidance where
ppr :: IfGuidance -> SDoc
ppr IfGuidance
IfNoGuidance = SDoc
forall doc. IsOutput doc => doc
empty
ppr (IfWhen Int
a Bool
u Bool
b) = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
angleBrackets (Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
a SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
comma SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Bool -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bool
u SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Bool -> SDoc
forall a. Outputable a => a -> SDoc
ppr Bool
b)
freeNamesIfDecl :: IfaceDecl -> NameSet
freeNamesIfDecl :: IfaceDecl -> NameSet
freeNamesIfDecl (IfaceId { ifType :: IfaceDecl -> IfaceType
ifType = IfaceType
t, ifIdDetails :: IfaceDecl -> IfaceIdDetails
ifIdDetails = IfaceIdDetails
d, ifIdInfo :: IfaceDecl -> IfaceIdInfo
ifIdInfo = IfaceIdInfo
i})
= IfaceType -> NameSet
freeNamesIfType IfaceType
t NameSet -> NameSet -> NameSet
&&&
IfaceIdInfo -> NameSet
freeNamesIfIdInfo IfaceIdInfo
i NameSet -> NameSet -> NameSet
&&&
IfaceIdDetails -> NameSet
freeNamesIfIdDetails IfaceIdDetails
d
freeNamesIfDecl (IfaceData { ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
bndrs, ifResKind :: IfaceDecl -> IfaceType
ifResKind = IfaceType
res_k
, ifParent :: IfaceDecl -> IfaceTyConParent
ifParent = IfaceTyConParent
p, ifCtxt :: IfaceDecl -> IfaceContext
ifCtxt = IfaceContext
ctxt, ifCons :: IfaceDecl -> IfaceConDecls
ifCons = IfaceConDecls
cons })
= [IfaceTyConBinder] -> NameSet
forall vis. [VarBndr IfaceBndr vis] -> NameSet
freeNamesIfVarBndrs [IfaceTyConBinder]
bndrs NameSet -> NameSet -> NameSet
&&&
IfaceType -> NameSet
freeNamesIfType IfaceType
res_k NameSet -> NameSet -> NameSet
&&&
IfaceTyConParent -> NameSet
freeNamesIfaceTyConParent IfaceTyConParent
p NameSet -> NameSet -> NameSet
&&&
IfaceContext -> NameSet
freeNamesIfContext IfaceContext
ctxt NameSet -> NameSet -> NameSet
&&&
IfaceConDecls -> NameSet
freeNamesIfConDecls IfaceConDecls
cons
freeNamesIfDecl (IfaceSynonym { ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
bndrs, ifResKind :: IfaceDecl -> IfaceType
ifResKind = IfaceType
res_k
, ifSynRhs :: IfaceDecl -> IfaceType
ifSynRhs = IfaceType
rhs })
= [IfaceTyConBinder] -> NameSet
forall vis. [VarBndr IfaceBndr vis] -> NameSet
freeNamesIfVarBndrs [IfaceTyConBinder]
bndrs NameSet -> NameSet -> NameSet
&&&
IfaceType -> NameSet
freeNamesIfKind IfaceType
res_k NameSet -> NameSet -> NameSet
&&&
IfaceType -> NameSet
freeNamesIfType IfaceType
rhs
freeNamesIfDecl (IfaceFamily { ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
bndrs, ifResKind :: IfaceDecl -> IfaceType
ifResKind = IfaceType
res_k
, ifFamFlav :: IfaceDecl -> IfaceFamTyConFlav
ifFamFlav = IfaceFamTyConFlav
flav })
= [IfaceTyConBinder] -> NameSet
forall vis. [VarBndr IfaceBndr vis] -> NameSet
freeNamesIfVarBndrs [IfaceTyConBinder]
bndrs NameSet -> NameSet -> NameSet
&&&
IfaceType -> NameSet
freeNamesIfKind IfaceType
res_k NameSet -> NameSet -> NameSet
&&&
IfaceFamTyConFlav -> NameSet
freeNamesIfFamFlav IfaceFamTyConFlav
flav
freeNamesIfDecl (IfaceClass{ ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
bndrs, ifBody :: IfaceDecl -> IfaceClassBody
ifBody = IfaceClassBody
cls_body })
= [IfaceTyConBinder] -> NameSet
forall vis. [VarBndr IfaceBndr vis] -> NameSet
freeNamesIfVarBndrs [IfaceTyConBinder]
bndrs NameSet -> NameSet -> NameSet
&&&
IfaceClassBody -> NameSet
freeNamesIfClassBody IfaceClassBody
cls_body
freeNamesIfDecl (IfaceAxiom { ifTyCon :: IfaceDecl -> IfaceTyCon
ifTyCon = IfaceTyCon
tc, ifAxBranches :: IfaceDecl -> [IfaceAxBranch]
ifAxBranches = [IfaceAxBranch]
branches })
= IfaceTyCon -> NameSet
freeNamesIfTc IfaceTyCon
tc NameSet -> NameSet -> NameSet
&&&
(IfaceAxBranch -> NameSet) -> [IfaceAxBranch] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceAxBranch -> NameSet
freeNamesIfAxBranch [IfaceAxBranch]
branches
freeNamesIfDecl (IfacePatSyn { ifPatMatcher :: IfaceDecl -> (IfExtName, Bool)
ifPatMatcher = (IfExtName
matcher, Bool
_)
, ifPatBuilder :: IfaceDecl -> Maybe (IfExtName, Bool)
ifPatBuilder = Maybe (IfExtName, Bool)
mb_builder
, ifPatUnivBndrs :: IfaceDecl -> [IfaceForAllSpecBndr]
ifPatUnivBndrs = [IfaceForAllSpecBndr]
univ_bndrs
, ifPatExBndrs :: IfaceDecl -> [IfaceForAllSpecBndr]
ifPatExBndrs = [IfaceForAllSpecBndr]
ex_bndrs
, ifPatProvCtxt :: IfaceDecl -> IfaceContext
ifPatProvCtxt = IfaceContext
prov_ctxt
, ifPatReqCtxt :: IfaceDecl -> IfaceContext
ifPatReqCtxt = IfaceContext
req_ctxt
, ifPatArgs :: IfaceDecl -> IfaceContext
ifPatArgs = IfaceContext
args
, ifPatTy :: IfaceDecl -> IfaceType
ifPatTy = IfaceType
pat_ty
, ifFieldLabels :: IfaceDecl -> [FieldLabel]
ifFieldLabels = [FieldLabel]
lbls })
= IfExtName -> NameSet
unitNameSet IfExtName
matcher NameSet -> NameSet -> NameSet
&&&
NameSet
-> ((IfExtName, Bool) -> NameSet)
-> Maybe (IfExtName, Bool)
-> NameSet
forall b a. b -> (a -> b) -> Maybe a -> b
maybe NameSet
emptyNameSet (IfExtName -> NameSet
unitNameSet (IfExtName -> NameSet)
-> ((IfExtName, Bool) -> IfExtName) -> (IfExtName, Bool) -> NameSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IfExtName, Bool) -> IfExtName
forall a b. (a, b) -> a
fst) Maybe (IfExtName, Bool)
mb_builder NameSet -> NameSet -> NameSet
&&&
[IfaceForAllSpecBndr] -> NameSet
forall vis. [VarBndr IfaceBndr vis] -> NameSet
freeNamesIfVarBndrs [IfaceForAllSpecBndr]
univ_bndrs NameSet -> NameSet -> NameSet
&&&
[IfaceForAllSpecBndr] -> NameSet
forall vis. [VarBndr IfaceBndr vis] -> NameSet
freeNamesIfVarBndrs [IfaceForAllSpecBndr]
ex_bndrs NameSet -> NameSet -> NameSet
&&&
IfaceContext -> NameSet
freeNamesIfContext IfaceContext
prov_ctxt NameSet -> NameSet -> NameSet
&&&
IfaceContext -> NameSet
freeNamesIfContext IfaceContext
req_ctxt NameSet -> NameSet -> NameSet
&&&
(IfaceType -> NameSet) -> IfaceContext -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceType -> NameSet
freeNamesIfType IfaceContext
args NameSet -> NameSet -> NameSet
&&&
IfaceType -> NameSet
freeNamesIfType IfaceType
pat_ty NameSet -> NameSet -> NameSet
&&&
[IfExtName] -> NameSet
mkNameSet ((FieldLabel -> IfExtName) -> [FieldLabel] -> [IfExtName]
forall a b. (a -> b) -> [a] -> [b]
map FieldLabel -> IfExtName
flSelector [FieldLabel]
lbls)
freeNamesIfClassBody :: IfaceClassBody -> NameSet
freeNamesIfClassBody :: IfaceClassBody -> NameSet
freeNamesIfClassBody IfaceClassBody
IfAbstractClass
= NameSet
emptyNameSet
freeNamesIfClassBody (IfConcreteClass{ ifClassCtxt :: IfaceClassBody -> IfaceContext
ifClassCtxt = IfaceContext
ctxt, ifATs :: IfaceClassBody -> [IfaceAT]
ifATs = [IfaceAT]
ats, ifSigs :: IfaceClassBody -> [IfaceClassOp]
ifSigs = [IfaceClassOp]
sigs })
= IfaceContext -> NameSet
freeNamesIfContext IfaceContext
ctxt NameSet -> NameSet -> NameSet
&&&
(IfaceAT -> NameSet) -> [IfaceAT] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceAT -> NameSet
freeNamesIfAT [IfaceAT]
ats NameSet -> NameSet -> NameSet
&&&
(IfaceClassOp -> NameSet) -> [IfaceClassOp] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceClassOp -> NameSet
freeNamesIfClsSig [IfaceClassOp]
sigs
freeNamesIfAxBranch :: IfaceAxBranch -> NameSet
freeNamesIfAxBranch :: IfaceAxBranch -> NameSet
freeNamesIfAxBranch (IfaceAxBranch { ifaxbTyVars :: IfaceAxBranch -> [IfaceTvBndr]
ifaxbTyVars = [IfaceTvBndr]
tyvars
, ifaxbCoVars :: IfaceAxBranch -> [IfaceIdBndr]
ifaxbCoVars = [IfaceIdBndr]
covars
, ifaxbLHS :: IfaceAxBranch -> IfaceAppArgs
ifaxbLHS = IfaceAppArgs
lhs
, ifaxbRHS :: IfaceAxBranch -> IfaceType
ifaxbRHS = IfaceType
rhs })
= (IfaceTvBndr -> NameSet) -> [IfaceTvBndr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceTvBndr -> NameSet
freeNamesIfTvBndr [IfaceTvBndr]
tyvars NameSet -> NameSet -> NameSet
&&&
(IfaceIdBndr -> NameSet) -> [IfaceIdBndr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceIdBndr -> NameSet
freeNamesIfIdBndr [IfaceIdBndr]
covars NameSet -> NameSet -> NameSet
&&&
IfaceAppArgs -> NameSet
freeNamesIfAppArgs IfaceAppArgs
lhs NameSet -> NameSet -> NameSet
&&&
IfaceType -> NameSet
freeNamesIfType IfaceType
rhs
freeNamesIfIdDetails :: IfaceIdDetails -> NameSet
freeNamesIfIdDetails :: IfaceIdDetails -> NameSet
freeNamesIfIdDetails (IfRecSelId Either IfaceTyCon IfaceDecl
tc IfExtName
first_con Bool
_ FieldLabel
fl) =
(IfaceTyCon -> NameSet)
-> (IfaceDecl -> NameSet) -> Either IfaceTyCon IfaceDecl -> NameSet
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either IfaceTyCon -> NameSet
freeNamesIfTc IfaceDecl -> NameSet
freeNamesIfDecl Either IfaceTyCon IfaceDecl
tc NameSet -> NameSet -> NameSet
&&&
IfExtName -> NameSet
unitFV IfExtName
first_con NameSet -> NameSet -> NameSet
&&&
IfExtName -> NameSet
unitFV (FieldLabel -> IfExtName
flSelector FieldLabel
fl)
freeNamesIfIdDetails IfaceIdDetails
IfVanillaId = NameSet
emptyNameSet
freeNamesIfIdDetails (IfWorkerLikeId {}) = NameSet
emptyNameSet
freeNamesIfIdDetails IfaceIdDetails
IfDFunId = NameSet
emptyNameSet
freeNamesIfFamFlav :: IfaceFamTyConFlav -> NameSet
freeNamesIfFamFlav :: IfaceFamTyConFlav -> NameSet
freeNamesIfFamFlav IfaceFamTyConFlav
IfaceOpenSynFamilyTyCon = NameSet
emptyNameSet
freeNamesIfFamFlav IfaceFamTyConFlav
IfaceDataFamilyTyCon = NameSet
emptyNameSet
freeNamesIfFamFlav (IfaceClosedSynFamilyTyCon (Just (IfExtName
ax, [IfaceAxBranch]
br)))
= IfExtName -> NameSet
unitNameSet IfExtName
ax NameSet -> NameSet -> NameSet
&&& (IfaceAxBranch -> NameSet) -> [IfaceAxBranch] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceAxBranch -> NameSet
freeNamesIfAxBranch [IfaceAxBranch]
br
freeNamesIfFamFlav (IfaceClosedSynFamilyTyCon Maybe (IfExtName, [IfaceAxBranch])
Nothing) = NameSet
emptyNameSet
freeNamesIfFamFlav IfaceFamTyConFlav
IfaceAbstractClosedSynFamilyTyCon = NameSet
emptyNameSet
freeNamesIfFamFlav IfaceFamTyConFlav
IfaceBuiltInSynFamTyCon = NameSet
emptyNameSet
freeNamesIfContext :: IfaceContext -> NameSet
freeNamesIfContext :: IfaceContext -> NameSet
freeNamesIfContext = (IfaceType -> NameSet) -> IfaceContext -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceType -> NameSet
freeNamesIfType
freeNamesIfAT :: IfaceAT -> NameSet
freeNamesIfAT :: IfaceAT -> NameSet
freeNamesIfAT (IfaceAT IfaceDecl
decl Maybe IfaceType
mb_def)
= IfaceDecl -> NameSet
freeNamesIfDecl IfaceDecl
decl NameSet -> NameSet -> NameSet
&&&
case Maybe IfaceType
mb_def of
Maybe IfaceType
Nothing -> NameSet
emptyNameSet
Just IfaceType
rhs -> IfaceType -> NameSet
freeNamesIfType IfaceType
rhs
freeNamesIfClsSig :: IfaceClassOp -> NameSet
freeNamesIfClsSig :: IfaceClassOp -> NameSet
freeNamesIfClsSig (IfaceClassOp IfExtName
_n IfaceType
ty Maybe (DefMethSpec IfaceType)
dm) = IfaceType -> NameSet
freeNamesIfType IfaceType
ty NameSet -> NameSet -> NameSet
&&& Maybe (DefMethSpec IfaceType) -> NameSet
freeNamesDM Maybe (DefMethSpec IfaceType)
dm
freeNamesDM :: Maybe (DefMethSpec IfaceType) -> NameSet
freeNamesDM :: Maybe (DefMethSpec IfaceType) -> NameSet
freeNamesDM (Just (GenericDM IfaceType
ty)) = IfaceType -> NameSet
freeNamesIfType IfaceType
ty
freeNamesDM Maybe (DefMethSpec IfaceType)
_ = NameSet
emptyNameSet
freeNamesIfConDecls :: IfaceConDecls -> NameSet
freeNamesIfConDecls :: IfaceConDecls -> NameSet
freeNamesIfConDecls (IfDataTyCon Bool
_ [IfaceConDecl]
cs) = (IfaceConDecl -> NameSet) -> [IfaceConDecl] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceConDecl -> NameSet
freeNamesIfConDecl [IfaceConDecl]
cs
freeNamesIfConDecls (IfNewTyCon IfaceConDecl
c) = IfaceConDecl -> NameSet
freeNamesIfConDecl IfaceConDecl
c
freeNamesIfConDecls IfaceConDecls
_ = NameSet
emptyNameSet
freeNamesIfConDecl :: IfaceConDecl -> NameSet
freeNamesIfConDecl :: IfaceConDecl -> NameSet
freeNamesIfConDecl (IfCon { ifConExTCvs :: IfaceConDecl -> [IfaceBndr]
ifConExTCvs = [IfaceBndr]
ex_tvs, ifConCtxt :: IfaceConDecl -> IfaceContext
ifConCtxt = IfaceContext
ctxt
, ifConArgTys :: IfaceConDecl -> [(IfaceType, IfaceType)]
ifConArgTys = [(IfaceType, IfaceType)]
arg_tys
, ifConFields :: IfaceConDecl -> [FieldLabel]
ifConFields = [FieldLabel]
flds
, ifConEqSpec :: IfaceConDecl -> [IfaceTvBndr]
ifConEqSpec = [IfaceTvBndr]
eq_spec
, ifConStricts :: IfaceConDecl -> [IfaceBang]
ifConStricts = [IfaceBang]
bangs })
= (IfaceBndr -> NameSet) -> [IfaceBndr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceBndr -> NameSet
freeNamesIfBndr [IfaceBndr]
ex_tvs NameSet -> NameSet -> NameSet
&&&
IfaceContext -> NameSet
freeNamesIfContext IfaceContext
ctxt NameSet -> NameSet -> NameSet
&&&
(IfaceType -> NameSet) -> IfaceContext -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceType -> NameSet
freeNamesIfType (((IfaceType, IfaceType) -> IfaceType)
-> [(IfaceType, IfaceType)] -> IfaceContext
forall a b. (a -> b) -> [a] -> [b]
map (IfaceType, IfaceType) -> IfaceType
forall a b. (a, b) -> a
fst [(IfaceType, IfaceType)]
arg_tys) NameSet -> NameSet -> NameSet
&&&
(IfaceType -> NameSet) -> IfaceContext -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceType -> NameSet
freeNamesIfType (((IfaceType, IfaceType) -> IfaceType)
-> [(IfaceType, IfaceType)] -> IfaceContext
forall a b. (a -> b) -> [a] -> [b]
map (IfaceType, IfaceType) -> IfaceType
forall a b. (a, b) -> b
snd [(IfaceType, IfaceType)]
arg_tys) NameSet -> NameSet -> NameSet
&&&
[IfExtName] -> NameSet
mkNameSet ((FieldLabel -> IfExtName) -> [FieldLabel] -> [IfExtName]
forall a b. (a -> b) -> [a] -> [b]
map FieldLabel -> IfExtName
flSelector [FieldLabel]
flds) NameSet -> NameSet -> NameSet
&&&
(IfaceType -> NameSet) -> IfaceContext -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceType -> NameSet
freeNamesIfType ((IfaceTvBndr -> IfaceType) -> [IfaceTvBndr] -> IfaceContext
forall a b. (a -> b) -> [a] -> [b]
map IfaceTvBndr -> IfaceType
forall a b. (a, b) -> b
snd [IfaceTvBndr]
eq_spec) NameSet -> NameSet -> NameSet
&&&
(IfaceBang -> NameSet) -> [IfaceBang] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceBang -> NameSet
freeNamesIfBang [IfaceBang]
bangs
freeNamesIfBang :: IfaceBang -> NameSet
freeNamesIfBang :: IfaceBang -> NameSet
freeNamesIfBang (IfUnpackCo IfaceCoercion
co) = IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co
freeNamesIfBang IfaceBang
_ = NameSet
emptyNameSet
freeNamesIfKind :: IfaceType -> NameSet
freeNamesIfKind :: IfaceType -> NameSet
freeNamesIfKind = IfaceType -> NameSet
freeNamesIfType
freeNamesIfAppArgs :: IfaceAppArgs -> NameSet
freeNamesIfAppArgs :: IfaceAppArgs -> NameSet
freeNamesIfAppArgs (IA_Arg IfaceType
t ForAllTyFlag
_ IfaceAppArgs
ts) = IfaceType -> NameSet
freeNamesIfType IfaceType
t NameSet -> NameSet -> NameSet
&&& IfaceAppArgs -> NameSet
freeNamesIfAppArgs IfaceAppArgs
ts
freeNamesIfAppArgs IfaceAppArgs
IA_Nil = NameSet
emptyNameSet
freeNamesIfType :: IfaceType -> NameSet
freeNamesIfType :: IfaceType -> NameSet
freeNamesIfType (IfaceFreeTyVar TyVar
_) = NameSet
emptyNameSet
freeNamesIfType (IfaceTyVar IfLclName
_) = NameSet
emptyNameSet
freeNamesIfType (IfaceAppTy IfaceType
s IfaceAppArgs
t) = IfaceType -> NameSet
freeNamesIfType IfaceType
s NameSet -> NameSet -> NameSet
&&& IfaceAppArgs -> NameSet
freeNamesIfAppArgs IfaceAppArgs
t
freeNamesIfType (IfaceTyConApp IfaceTyCon
tc IfaceAppArgs
ts) = IfaceTyCon -> NameSet
freeNamesIfTc IfaceTyCon
tc NameSet -> NameSet -> NameSet
&&& IfaceAppArgs -> NameSet
freeNamesIfAppArgs IfaceAppArgs
ts
freeNamesIfType (IfaceTupleTy TupleSort
_ PromotionFlag
_ IfaceAppArgs
ts) = IfaceAppArgs -> NameSet
freeNamesIfAppArgs IfaceAppArgs
ts
freeNamesIfType (IfaceLitTy IfaceTyLit
_) = NameSet
emptyNameSet
freeNamesIfType (IfaceForAllTy IfaceForAllBndr
tv IfaceType
t) = IfaceForAllBndr -> NameSet
forall vis. VarBndr IfaceBndr vis -> NameSet
freeNamesIfVarBndr IfaceForAllBndr
tv NameSet -> NameSet -> NameSet
&&& IfaceType -> NameSet
freeNamesIfType IfaceType
t
freeNamesIfType (IfaceFunTy FunTyFlag
_ IfaceType
w IfaceType
s IfaceType
t) = IfaceType -> NameSet
freeNamesIfType IfaceType
s NameSet -> NameSet -> NameSet
&&& IfaceType -> NameSet
freeNamesIfType IfaceType
t NameSet -> NameSet -> NameSet
&&& IfaceType -> NameSet
freeNamesIfType IfaceType
w
freeNamesIfType (IfaceCastTy IfaceType
t IfaceCoercion
c) = IfaceType -> NameSet
freeNamesIfType IfaceType
t NameSet -> NameSet -> NameSet
&&& IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c
freeNamesIfType (IfaceCoercionTy IfaceCoercion
c) = IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c
freeNamesIfMCoercion :: IfaceMCoercion -> NameSet
freeNamesIfMCoercion :: IfaceMCoercion -> NameSet
freeNamesIfMCoercion IfaceMCoercion
IfaceMRefl = NameSet
emptyNameSet
freeNamesIfMCoercion (IfaceMCo IfaceCoercion
co) = IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co
freeNamesIfCoercion :: IfaceCoercion -> NameSet
freeNamesIfCoercion :: IfaceCoercion -> NameSet
freeNamesIfCoercion (IfaceReflCo IfaceType
t) = IfaceType -> NameSet
freeNamesIfType IfaceType
t
freeNamesIfCoercion (IfaceGReflCo Role
_ IfaceType
t IfaceMCoercion
mco)
= IfaceType -> NameSet
freeNamesIfType IfaceType
t NameSet -> NameSet -> NameSet
&&& IfaceMCoercion -> NameSet
freeNamesIfMCoercion IfaceMCoercion
mco
freeNamesIfCoercion (IfaceFunCo Role
_ IfaceCoercion
c_mult IfaceCoercion
c1 IfaceCoercion
c2)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c_mult NameSet -> NameSet -> NameSet
&&& IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c1 NameSet -> NameSet -> NameSet
&&& IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c2
freeNamesIfCoercion (IfaceTyConAppCo Role
_ IfaceTyCon
tc [IfaceCoercion]
cos)
= IfaceTyCon -> NameSet
freeNamesIfTc IfaceTyCon
tc NameSet -> NameSet -> NameSet
&&& (IfaceCoercion -> NameSet) -> [IfaceCoercion] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceCoercion -> NameSet
freeNamesIfCoercion [IfaceCoercion]
cos
freeNamesIfCoercion (IfaceAppCo IfaceCoercion
c1 IfaceCoercion
c2)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c1 NameSet -> NameSet -> NameSet
&&& IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c2
freeNamesIfCoercion (IfaceForAllCo IfaceBndr
_tcv ForAllTyFlag
_visL ForAllTyFlag
_visR IfaceCoercion
kind_co IfaceCoercion
co)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
kind_co NameSet -> NameSet -> NameSet
&&& IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co
freeNamesIfCoercion (IfaceFreeCoVar TyVar
_) = NameSet
emptyNameSet
freeNamesIfCoercion (IfaceCoVarCo IfLclName
_) = NameSet
emptyNameSet
freeNamesIfCoercion (IfaceHoleCo TyVar
_) = NameSet
emptyNameSet
freeNamesIfCoercion (IfaceUnivCo UnivCoProvenance
_ Role
_ IfaceType
t1 IfaceType
t2 [IfaceCoercion]
cos)
= IfaceType -> NameSet
freeNamesIfType IfaceType
t1 NameSet -> NameSet -> NameSet
&&& IfaceType -> NameSet
freeNamesIfType IfaceType
t2 NameSet -> NameSet -> NameSet
&&& (IfaceCoercion -> NameSet) -> [IfaceCoercion] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceCoercion -> NameSet
freeNamesIfCoercion [IfaceCoercion]
cos
freeNamesIfCoercion (IfaceSymCo IfaceCoercion
c)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c
freeNamesIfCoercion (IfaceTransCo IfaceCoercion
c1 IfaceCoercion
c2)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c1 NameSet -> NameSet -> NameSet
&&& IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c2
freeNamesIfCoercion (IfaceSelCo CoSel
_ IfaceCoercion
co)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co
freeNamesIfCoercion (IfaceLRCo LeftOrRight
_ IfaceCoercion
co)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co
freeNamesIfCoercion (IfaceInstCo IfaceCoercion
co IfaceCoercion
co2)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co NameSet -> NameSet -> NameSet
&&& IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co2
freeNamesIfCoercion (IfaceKindCo IfaceCoercion
c)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
c
freeNamesIfCoercion (IfaceSubCo IfaceCoercion
co)
= IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co
freeNamesIfCoercion (IfaceAxiomCo IfaceAxiomRule
ax [IfaceCoercion]
cos)
= IfaceAxiomRule -> NameSet
fnAxRule IfaceAxiomRule
ax NameSet -> NameSet -> NameSet
&&& (IfaceCoercion -> NameSet) -> [IfaceCoercion] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceCoercion -> NameSet
freeNamesIfCoercion [IfaceCoercion]
cos
fnAxRule :: IfaceAxiomRule -> NameSet
fnAxRule :: IfaceAxiomRule -> NameSet
fnAxRule (IfaceAR_X IfLclName
_) = NameSet
emptyNameSet
fnAxRule (IfaceAR_U IfExtName
n) = IfExtName -> NameSet
unitNameSet IfExtName
n
fnAxRule (IfaceAR_B IfExtName
n Int
_) = IfExtName -> NameSet
unitNameSet IfExtName
n
freeNamesIfVarBndr :: VarBndr IfaceBndr vis -> NameSet
freeNamesIfVarBndr :: forall vis. VarBndr IfaceBndr vis -> NameSet
freeNamesIfVarBndr (Bndr IfaceBndr
bndr vis
_) = IfaceBndr -> NameSet
freeNamesIfBndr IfaceBndr
bndr
freeNamesIfVarBndrs :: [VarBndr IfaceBndr vis] -> NameSet
freeNamesIfVarBndrs :: forall vis. [VarBndr IfaceBndr vis] -> NameSet
freeNamesIfVarBndrs = (VarBndr IfaceBndr vis -> NameSet)
-> [VarBndr IfaceBndr vis] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList VarBndr IfaceBndr vis -> NameSet
forall vis. VarBndr IfaceBndr vis -> NameSet
freeNamesIfVarBndr
freeNamesIfBndr :: IfaceBndr -> NameSet
freeNamesIfBndr :: IfaceBndr -> NameSet
freeNamesIfBndr (IfaceIdBndr IfaceIdBndr
b) = IfaceIdBndr -> NameSet
freeNamesIfIdBndr IfaceIdBndr
b
freeNamesIfBndr (IfaceTvBndr IfaceTvBndr
b) = IfaceTvBndr -> NameSet
freeNamesIfTvBndr IfaceTvBndr
b
freeNamesIfBndrs :: [IfaceBndr] -> NameSet
freeNamesIfBndrs :: [IfaceBndr] -> NameSet
freeNamesIfBndrs = (IfaceBndr -> NameSet) -> [IfaceBndr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceBndr -> NameSet
freeNamesIfBndr
freeNamesIfLetBndr :: IfaceLetBndr -> NameSet
freeNamesIfLetBndr :: IfaceLetBndr -> NameSet
freeNamesIfLetBndr (IfLetBndr IfLclName
_name IfaceType
ty IfaceIdInfo
info JoinPointHood
_ji) = IfaceType -> NameSet
freeNamesIfType IfaceType
ty
NameSet -> NameSet -> NameSet
&&& IfaceIdInfo -> NameSet
freeNamesIfIdInfo IfaceIdInfo
info
freeNamesIfTvBndr :: IfaceTvBndr -> NameSet
freeNamesIfTvBndr :: IfaceTvBndr -> NameSet
freeNamesIfTvBndr (IfLclName
_fs,IfaceType
k) = IfaceType -> NameSet
freeNamesIfKind IfaceType
k
freeNamesIfIdBndr :: IfaceIdBndr -> NameSet
freeNamesIfIdBndr :: IfaceIdBndr -> NameSet
freeNamesIfIdBndr (IfaceType
_, IfLclName
_fs,IfaceType
k) = IfaceType -> NameSet
freeNamesIfKind IfaceType
k
freeNamesIfIdInfo :: IfaceIdInfo -> NameSet
freeNamesIfIdInfo :: IfaceIdInfo -> NameSet
freeNamesIfIdInfo = (IfaceInfoItem -> NameSet) -> IfaceIdInfo -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceInfoItem -> NameSet
freeNamesItem
freeNamesItem :: IfaceInfoItem -> NameSet
freeNamesItem :: IfaceInfoItem -> NameSet
freeNamesItem (HsUnfold Bool
_ IfaceUnfolding
u) = IfaceUnfolding -> NameSet
freeNamesIfUnfold IfaceUnfolding
u
freeNamesItem (HsLFInfo (IfLFCon IfExtName
n)) = IfExtName -> NameSet
unitNameSet IfExtName
n
freeNamesItem IfaceInfoItem
_ = NameSet
emptyNameSet
freeNamesIfUnfold :: IfaceUnfolding -> NameSet
freeNamesIfUnfold :: IfaceUnfolding -> NameSet
freeNamesIfUnfold (IfCoreUnfold UnfoldingSource
_ IfUnfoldingCache
_ IfGuidance
_ IfaceExpr
e) = IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
e
freeNamesIfUnfold (IfDFunUnfold [IfaceBndr]
bs [IfaceExpr]
es) = [IfaceBndr] -> NameSet
freeNamesIfBndrs [IfaceBndr]
bs NameSet -> NameSet -> NameSet
&&& (IfaceExpr -> NameSet) -> [IfaceExpr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceExpr -> NameSet
freeNamesIfExpr [IfaceExpr]
es
freeNamesIfExpr :: IfaceExpr -> NameSet
freeNamesIfExpr :: IfaceExpr -> NameSet
freeNamesIfExpr (IfaceExt IfExtName
v) = IfExtName -> NameSet
unitNameSet IfExtName
v
freeNamesIfExpr (IfaceFCall ForeignCall
_ IfaceType
ty) = IfaceType -> NameSet
freeNamesIfType IfaceType
ty
freeNamesIfExpr (IfaceType IfaceType
ty) = IfaceType -> NameSet
freeNamesIfType IfaceType
ty
freeNamesIfExpr (IfaceCo IfaceCoercion
co) = IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co
freeNamesIfExpr (IfaceTuple TupleSort
_ [IfaceExpr]
as) = (IfaceExpr -> NameSet) -> [IfaceExpr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceExpr -> NameSet
freeNamesIfExpr [IfaceExpr]
as
freeNamesIfExpr (IfaceLam (IfaceBndr
b,IfaceOneShot
_) IfaceExpr
body) = IfaceBndr -> NameSet
freeNamesIfBndr IfaceBndr
b NameSet -> NameSet -> NameSet
&&& IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
body
freeNamesIfExpr (IfaceApp IfaceExpr
f IfaceExpr
a) = IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
f NameSet -> NameSet -> NameSet
&&& IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
a
freeNamesIfExpr (IfaceCast IfaceExpr
e IfaceCoercion
co) = IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
e NameSet -> NameSet -> NameSet
&&& IfaceCoercion -> NameSet
freeNamesIfCoercion IfaceCoercion
co
freeNamesIfExpr (IfaceTick IfaceTickish
t IfaceExpr
e) = IfaceTickish -> NameSet
freeNamesIfTickish IfaceTickish
t NameSet -> NameSet -> NameSet
&&& IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
e
freeNamesIfExpr (IfaceECase IfaceExpr
e IfaceType
ty) = IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
e NameSet -> NameSet -> NameSet
&&& IfaceType -> NameSet
freeNamesIfType IfaceType
ty
freeNamesIfExpr (IfaceCase IfaceExpr
s IfLclName
_ [IfaceAlt]
alts)
= IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
s NameSet -> NameSet -> NameSet
&&& (IfaceAlt -> NameSet) -> [IfaceAlt] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceAlt -> NameSet
fn_alt [IfaceAlt]
alts NameSet -> NameSet -> NameSet
&&& [IfaceAlt] -> NameSet
fn_cons [IfaceAlt]
alts
where
fn_alt :: IfaceAlt -> NameSet
fn_alt (IfaceAlt IfaceConAlt
_con [IfLclName]
_bs IfaceExpr
r) = IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
r
fn_cons :: [IfaceAlt] -> NameSet
fn_cons [] = NameSet
emptyNameSet
fn_cons (IfaceAlt IfaceConAlt
IfaceDefaultAlt [IfLclName]
_ IfaceExpr
_ : [IfaceAlt]
xs) = [IfaceAlt] -> NameSet
fn_cons [IfaceAlt]
xs
fn_cons (IfaceAlt (IfaceDataAlt IfExtName
con) [IfLclName]
_ IfaceExpr
_ : [IfaceAlt]
_ ) = IfExtName -> NameSet
unitNameSet IfExtName
con
fn_cons (IfaceAlt
_ : [IfaceAlt]
_ ) = NameSet
emptyNameSet
freeNamesIfExpr (IfaceLet (IfaceNonRec IfaceLetBndr
bndr IfaceExpr
rhs) IfaceExpr
body)
= IfaceLetBndr -> NameSet
freeNamesIfLetBndr IfaceLetBndr
bndr NameSet -> NameSet -> NameSet
&&& IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
rhs NameSet -> NameSet -> NameSet
&&& IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
body
freeNamesIfExpr (IfaceLet (IfaceRec [(IfaceLetBndr, IfaceExpr)]
as) IfaceExpr
x)
= ((IfaceLetBndr, IfaceExpr) -> NameSet)
-> [(IfaceLetBndr, IfaceExpr)] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList (IfaceLetBndr, IfaceExpr) -> NameSet
fn_pair [(IfaceLetBndr, IfaceExpr)]
as NameSet -> NameSet -> NameSet
&&& IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
x
where
fn_pair :: (IfaceLetBndr, IfaceExpr) -> NameSet
fn_pair (IfaceLetBndr
bndr, IfaceExpr
rhs) = IfaceLetBndr -> NameSet
freeNamesIfLetBndr IfaceLetBndr
bndr NameSet -> NameSet -> NameSet
&&& IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
rhs
freeNamesIfExpr IfaceExpr
_ = NameSet
emptyNameSet
freeNamesIfTc :: IfaceTyCon -> NameSet
freeNamesIfTc :: IfaceTyCon -> NameSet
freeNamesIfTc IfaceTyCon
tc = IfExtName -> NameSet
unitNameSet (IfaceTyCon -> IfExtName
ifaceTyConName IfaceTyCon
tc)
freeNamesIfRule :: IfaceRule -> NameSet
freeNamesIfRule :: IfaceRule -> NameSet
freeNamesIfRule (IfaceRule { ifRuleBndrs :: IfaceRule -> [IfaceBndr]
ifRuleBndrs = [IfaceBndr]
bs, ifRuleHead :: IfaceRule -> IfExtName
ifRuleHead = IfExtName
f
, ifRuleArgs :: IfaceRule -> [IfaceExpr]
ifRuleArgs = [IfaceExpr]
es, ifRuleRhs :: IfaceRule -> IfaceExpr
ifRuleRhs = IfaceExpr
rhs })
= IfExtName -> NameSet
unitNameSet IfExtName
f NameSet -> NameSet -> NameSet
&&&
(IfaceBndr -> NameSet) -> [IfaceBndr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceBndr -> NameSet
freeNamesIfBndr [IfaceBndr]
bs NameSet -> NameSet -> NameSet
&&&
(IfaceExpr -> NameSet) -> [IfaceExpr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceExpr -> NameSet
freeNamesIfExpr [IfaceExpr]
es NameSet -> NameSet -> NameSet
&&&
IfaceExpr -> NameSet
freeNamesIfExpr IfaceExpr
rhs
freeNamesIfFamInst :: IfaceFamInst -> NameSet
freeNamesIfFamInst :: IfaceFamInst -> NameSet
freeNamesIfFamInst (IfaceFamInst { ifFamInstFam :: IfaceFamInst -> IfExtName
ifFamInstFam = IfExtName
famName
, ifFamInstAxiom :: IfaceFamInst -> IfExtName
ifFamInstAxiom = IfExtName
axName })
= IfExtName -> NameSet
unitNameSet IfExtName
famName NameSet -> NameSet -> NameSet
&&&
IfExtName -> NameSet
unitNameSet IfExtName
axName
freeNamesIfaceTyConParent :: IfaceTyConParent -> NameSet
freeNamesIfaceTyConParent :: IfaceTyConParent -> NameSet
freeNamesIfaceTyConParent IfaceTyConParent
IfNoParent = NameSet
emptyNameSet
freeNamesIfaceTyConParent (IfDataInstance IfExtName
ax IfaceTyCon
tc IfaceAppArgs
tys)
= IfExtName -> NameSet
unitNameSet IfExtName
ax NameSet -> NameSet -> NameSet
&&& IfaceTyCon -> NameSet
freeNamesIfTc IfaceTyCon
tc NameSet -> NameSet -> NameSet
&&& IfaceAppArgs -> NameSet
freeNamesIfAppArgs IfaceAppArgs
tys
freeNamesIfTickish :: IfaceTickish -> NameSet
freeNamesIfTickish :: IfaceTickish -> NameSet
freeNamesIfTickish (IfaceBreakpoint Int
_ [IfaceExpr]
fvs Module
_) =
(IfaceExpr -> NameSet) -> [IfaceExpr] -> NameSet
forall a. (a -> NameSet) -> [a] -> NameSet
fnList IfaceExpr -> NameSet
freeNamesIfExpr [IfaceExpr]
fvs
freeNamesIfTickish IfaceTickish
_ = NameSet
emptyNameSet
(&&&) :: NameSet -> NameSet -> NameSet
&&& :: NameSet -> NameSet -> NameSet
(&&&) = NameSet -> NameSet -> NameSet
unionNameSet
fnList :: (a -> NameSet) -> [a] -> NameSet
fnList :: forall a. (a -> NameSet) -> [a] -> NameSet
fnList a -> NameSet
f = (NameSet -> NameSet -> NameSet) -> NameSet -> [NameSet] -> NameSet
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr NameSet -> NameSet -> NameSet
(&&&) NameSet
emptyNameSet ([NameSet] -> NameSet) -> ([a] -> [NameSet]) -> [a] -> NameSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> NameSet) -> [a] -> [NameSet]
forall a b. (a -> b) -> [a] -> [b]
map a -> NameSet
f
instance Binary IfaceDecl where
put_ :: WriteBinHandle -> IfaceDecl -> IO ()
put_ WriteBinHandle
bh (IfaceId IfExtName
name IfaceType
ty IfaceIdDetails
details IfaceIdInfo
idinfo) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
name
WriteBinHandle -> (IfaceType, IfaceIdDetails, IfaceIdInfo) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh (IfaceType
ty, IfaceIdDetails
details, IfaceIdInfo
idinfo)
put_ WriteBinHandle
bh (IfaceData IfExtName
a1 [IfaceTyConBinder]
a2 IfaceType
a3 Maybe CType
a4 [Role]
a5 IfaceContext
a6 IfaceConDecls
a7 Bool
a8 IfaceTyConParent
a9) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
a1
WriteBinHandle -> [IfaceTyConBinder] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceTyConBinder]
a2
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
a3
WriteBinHandle -> Maybe CType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe CType
a4
WriteBinHandle -> [Role] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [Role]
a5
WriteBinHandle -> IfaceContext -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceContext
a6
WriteBinHandle -> IfaceConDecls -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceConDecls
a7
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
a8
WriteBinHandle -> IfaceTyConParent -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceTyConParent
a9
put_ WriteBinHandle
bh (IfaceSynonym IfExtName
a1 [Role]
a2 [IfaceTyConBinder]
a3 IfaceType
a4 IfaceType
a5) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
a1
WriteBinHandle -> [Role] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [Role]
a2
WriteBinHandle -> [IfaceTyConBinder] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceTyConBinder]
a3
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
a4
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
a5
put_ WriteBinHandle
bh (IfaceFamily IfExtName
a1 Maybe IfLclName
a2 [IfaceTyConBinder]
a3 IfaceType
a4 IfaceFamTyConFlav
a5 Injectivity
a6) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
4
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
a1
WriteBinHandle -> Maybe IfLclName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe IfLclName
a2
WriteBinHandle -> [IfaceTyConBinder] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceTyConBinder]
a3
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
a4
WriteBinHandle -> IfaceFamTyConFlav -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceFamTyConFlav
a5
WriteBinHandle -> Injectivity -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Injectivity
a6
put_ WriteBinHandle
bh (IfaceClass {
ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
a2,
ifRoles :: IfaceDecl -> [Role]
ifRoles = [Role]
a3,
ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
a4,
ifFDs :: IfaceDecl -> [FunDep IfLclName]
ifFDs = [FunDep IfLclName]
a5,
ifBody :: IfaceDecl -> IfaceClassBody
ifBody = IfConcreteClass {
ifClassCtxt :: IfaceClassBody -> IfaceContext
ifClassCtxt = IfaceContext
a1,
ifATs :: IfaceClassBody -> [IfaceAT]
ifATs = [IfaceAT]
a6,
ifSigs :: IfaceClassBody -> [IfaceClassOp]
ifSigs = [IfaceClassOp]
a7,
ifMinDef :: IfaceClassBody -> IfaceBooleanFormula
ifMinDef = IfaceBooleanFormula
a8
}}) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
5
WriteBinHandle -> IfaceContext -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceContext
a1
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
a2
WriteBinHandle -> [Role] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [Role]
a3
WriteBinHandle -> [IfaceTyConBinder] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceTyConBinder]
a4
WriteBinHandle -> [FunDep IfLclName] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [FunDep IfLclName]
a5
WriteBinHandle -> [IfaceAT] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceAT]
a6
WriteBinHandle -> [IfaceClassOp] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceClassOp]
a7
WriteBinHandle -> IfaceBooleanFormula -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceBooleanFormula
a8
put_ WriteBinHandle
bh (IfaceAxiom IfExtName
a1 IfaceTyCon
a2 Role
a3 [IfaceAxBranch]
a4) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
6
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
a1
WriteBinHandle -> IfaceTyCon -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceTyCon
a2
WriteBinHandle -> Role -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Role
a3
WriteBinHandle -> [IfaceAxBranch] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceAxBranch]
a4
put_ WriteBinHandle
bh (IfacePatSyn IfExtName
a1 Bool
a2 (IfExtName, Bool)
a3 Maybe (IfExtName, Bool)
a4 [IfaceForAllSpecBndr]
a5 [IfaceForAllSpecBndr]
a6 IfaceContext
a7 IfaceContext
a8 IfaceContext
a9 IfaceType
a10 [FieldLabel]
a11) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
7
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
a1
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
a2
WriteBinHandle -> (IfExtName, Bool) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (IfExtName, Bool)
a3
WriteBinHandle -> Maybe (IfExtName, Bool) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe (IfExtName, Bool)
a4
WriteBinHandle -> [IfaceForAllSpecBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceForAllSpecBndr]
a5
WriteBinHandle -> [IfaceForAllSpecBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceForAllSpecBndr]
a6
WriteBinHandle -> IfaceContext -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceContext
a7
WriteBinHandle -> IfaceContext -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceContext
a8
WriteBinHandle -> IfaceContext -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceContext
a9
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
a10
WriteBinHandle -> [FieldLabel] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [FieldLabel]
a11
put_ WriteBinHandle
bh (IfaceClass {
ifName :: IfaceDecl -> IfExtName
ifName = IfExtName
a1,
ifRoles :: IfaceDecl -> [Role]
ifRoles = [Role]
a2,
ifBinders :: IfaceDecl -> [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
a3,
ifFDs :: IfaceDecl -> [FunDep IfLclName]
ifFDs = [FunDep IfLclName]
a4,
ifBody :: IfaceDecl -> IfaceClassBody
ifBody = IfaceClassBody
IfAbstractClass }) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
8
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
a1
WriteBinHandle -> [Role] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [Role]
a2
WriteBinHandle -> [IfaceTyConBinder] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceTyConBinder]
a3
WriteBinHandle -> [FunDep IfLclName] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [FunDep IfLclName]
a4
get :: ReadBinHandle -> IO IfaceDecl
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> do name <- ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
~(ty, details, idinfo) <- lazyGet bh
return (IfaceId name ty details idinfo)
Word8
1 -> String -> IO IfaceDecl
forall a. HasCallStack => String -> a
error String
"Binary.get(TyClDecl): ForeignType"
Word8
2 -> do a1 <- ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
a5 <- get bh
a6 <- get bh
a7 <- get bh
a8 <- get bh
a9 <- get bh
return (IfaceData a1 a2 a3 a4 a5 a6 a7 a8 a9)
Word8
3 -> do a1 <- ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
a5 <- get bh
return (IfaceSynonym a1 a2 a3 a4 a5)
Word8
4 -> do a1 <- ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
a5 <- get bh
a6 <- get bh
return (IfaceFamily a1 a2 a3 a4 a5 a6)
Word8
5 -> do a1 <- ReadBinHandle -> IO IfaceContext
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
a2 <- getIfaceTopBndr bh
a3 <- get bh
a4 <- get bh
a5 <- get bh
a6 <- get bh
a7 <- get bh
a8 <- get bh
return (IfaceClass {
ifName = a2,
ifRoles = a3,
ifBinders = a4,
ifFDs = a5,
ifBody = IfConcreteClass {
ifClassCtxt = a1,
ifATs = a6,
ifSigs = a7,
ifMinDef = a8
}})
Word8
6 -> do a1 <- ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
return (IfaceAxiom a1 a2 a3 a4)
Word8
7 -> do a1 <- ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
a5 <- get bh
a6 <- get bh
a7 <- get bh
a8 <- get bh
a9 <- get bh
a10 <- get bh
a11 <- get bh
return (IfacePatSyn a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11)
Word8
8 -> do a1 <- ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
return (IfaceClass {
ifName = a1,
ifRoles = a2,
ifBinders = a3,
ifFDs = a4,
ifBody = IfAbstractClass })
Word8
_ -> String -> IO IfaceDecl
forall a. HasCallStack => String -> a
panic ([String] -> String
unwords [String
"Unknown IfaceDecl tag:", Word8 -> String
forall a. Show a => a -> String
show Word8
h])
instance Binary IfaceBooleanFormula where
put_ :: WriteBinHandle -> IfaceBooleanFormula -> IO ()
put_ WriteBinHandle
bh = \case
IfVar IfLclName
a1 -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> IfLclName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfLclName
a1
IfAnd [IfaceBooleanFormula]
a1 -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> [IfaceBooleanFormula] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceBooleanFormula]
a1
IfOr [IfaceBooleanFormula]
a1 -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> [IfaceBooleanFormula] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceBooleanFormula]
a1
IfParens IfaceBooleanFormula
a1 -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> IfaceBooleanFormula -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceBooleanFormula
a1
get :: ReadBinHandle -> IO IfaceBooleanFormula
get ReadBinHandle
bh = do
ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh IO Word8
-> (Word8 -> IO IfaceBooleanFormula) -> IO IfaceBooleanFormula
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Word8
0 -> IfLclName -> IfaceBooleanFormula
IfVar (IfLclName -> IfaceBooleanFormula)
-> IO IfLclName -> IO IfaceBooleanFormula
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO IfLclName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
1 -> [IfaceBooleanFormula] -> IfaceBooleanFormula
IfAnd ([IfaceBooleanFormula] -> IfaceBooleanFormula)
-> IO [IfaceBooleanFormula] -> IO IfaceBooleanFormula
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO [IfaceBooleanFormula]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
2 -> [IfaceBooleanFormula] -> IfaceBooleanFormula
IfOr ([IfaceBooleanFormula] -> IfaceBooleanFormula)
-> IO [IfaceBooleanFormula] -> IO IfaceBooleanFormula
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO [IfaceBooleanFormula]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> IfaceBooleanFormula -> IfaceBooleanFormula
IfParens (IfaceBooleanFormula -> IfaceBooleanFormula)
-> IO IfaceBooleanFormula -> IO IfaceBooleanFormula
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO IfaceBooleanFormula
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Binary IfaceFamTyConFlav where
put_ :: WriteBinHandle -> IfaceFamTyConFlav -> IO ()
put_ WriteBinHandle
bh IfaceFamTyConFlav
IfaceDataFamilyTyCon = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
put_ WriteBinHandle
bh IfaceFamTyConFlav
IfaceOpenSynFamilyTyCon = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
put_ WriteBinHandle
bh (IfaceClosedSynFamilyTyCon Maybe (IfExtName, [IfaceAxBranch])
mb) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> Maybe (IfExtName, [IfaceAxBranch]) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe (IfExtName, [IfaceAxBranch])
mb
put_ WriteBinHandle
bh IfaceFamTyConFlav
IfaceAbstractClosedSynFamilyTyCon = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3
put_ WriteBinHandle
_ IfaceFamTyConFlav
IfaceBuiltInSynFamTyCon
= String -> SDoc -> IO ()
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Cannot serialize IfaceBuiltInSynFamTyCon, used for pretty-printing only" SDoc
forall doc. IsOutput doc => doc
Outputable.empty
get :: ReadBinHandle -> IO IfaceFamTyConFlav
get ReadBinHandle
bh = do { h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
; case h of
Word8
0 -> IfaceFamTyConFlav -> IO IfaceFamTyConFlav
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceFamTyConFlav
IfaceDataFamilyTyCon
Word8
1 -> IfaceFamTyConFlav -> IO IfaceFamTyConFlav
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceFamTyConFlav
IfaceOpenSynFamilyTyCon
Word8
2 -> do { mb <- ReadBinHandle -> IO (Maybe (IfExtName, [IfaceAxBranch]))
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
; return (IfaceClosedSynFamilyTyCon mb) }
Word8
3 -> IfaceFamTyConFlav -> IO IfaceFamTyConFlav
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceFamTyConFlav
IfaceAbstractClosedSynFamilyTyCon
Word8
_ -> String -> SDoc -> IO IfaceFamTyConFlav
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Binary.get(IfaceFamTyConFlav): Invalid tag"
(Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
h :: Int)) }
instance Binary IfaceClassOp where
put_ :: WriteBinHandle -> IfaceClassOp -> IO ()
put_ WriteBinHandle
bh (IfaceClassOp IfExtName
n IfaceType
ty Maybe (DefMethSpec IfaceType)
def) = do
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
n
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
ty
WriteBinHandle -> Maybe (DefMethSpec IfaceType) -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe (DefMethSpec IfaceType)
def
get :: ReadBinHandle -> IO IfaceClassOp
get ReadBinHandle
bh = do
n <- ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh
ty <- get bh
def <- get bh
return (IfaceClassOp n ty def)
instance Binary IfaceAT where
put_ :: WriteBinHandle -> IfaceAT -> IO ()
put_ WriteBinHandle
bh (IfaceAT IfaceDecl
dec Maybe IfaceType
defs) = do
WriteBinHandle -> IfaceDecl -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceDecl
dec
WriteBinHandle -> Maybe IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe IfaceType
defs
get :: ReadBinHandle -> IO IfaceAT
get ReadBinHandle
bh = do
dec <- ReadBinHandle -> IO IfaceDecl
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
defs <- get bh
return (IfaceAT dec defs)
instance Binary IfaceAxBranch where
put_ :: WriteBinHandle -> IfaceAxBranch -> IO ()
put_ WriteBinHandle
bh (IfaceAxBranch [IfaceTvBndr]
a1 [IfaceTvBndr]
a2 [IfaceIdBndr]
a3 IfaceAppArgs
a4 [Role]
a5 IfaceType
a6 [Int]
a7) = do
WriteBinHandle -> [IfaceTvBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceTvBndr]
a1
WriteBinHandle -> [IfaceTvBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceTvBndr]
a2
WriteBinHandle -> [IfaceIdBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceIdBndr]
a3
WriteBinHandle -> IfaceAppArgs -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceAppArgs
a4
WriteBinHandle -> [Role] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [Role]
a5
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
a6
WriteBinHandle -> [Int] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [Int]
a7
get :: ReadBinHandle -> IO IfaceAxBranch
get ReadBinHandle
bh = do
a1 <- ReadBinHandle -> IO [IfaceTvBndr]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
a5 <- get bh
a6 <- get bh
a7 <- get bh
return (IfaceAxBranch a1 a2 a3 a4 a5 a6 a7)
instance Binary IfaceConDecls where
put_ :: WriteBinHandle -> IfaceConDecls -> IO ()
put_ WriteBinHandle
bh IfaceConDecls
IfAbstractTyCon = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
put_ WriteBinHandle
bh (IfDataTyCon Bool
False [IfaceConDecl]
cs) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> [IfaceConDecl] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceConDecl]
cs
put_ WriteBinHandle
bh (IfDataTyCon Bool
True [IfaceConDecl]
cs) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> [IfaceConDecl] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceConDecl]
cs
put_ WriteBinHandle
bh (IfNewTyCon IfaceConDecl
c) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> IfaceConDecl -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceConDecl
c
get :: ReadBinHandle -> IO IfaceConDecls
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> IfaceConDecls -> IO IfaceConDecls
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceConDecls
IfAbstractTyCon
Word8
1 -> ([IfaceConDecl] -> IfaceConDecls)
-> IO [IfaceConDecl] -> IO IfaceConDecls
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Bool -> [IfaceConDecl] -> IfaceConDecls
IfDataTyCon Bool
False) (ReadBinHandle -> IO [IfaceConDecl]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh)
Word8
2 -> ([IfaceConDecl] -> IfaceConDecls)
-> IO [IfaceConDecl] -> IO IfaceConDecls
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Bool -> [IfaceConDecl] -> IfaceConDecls
IfDataTyCon Bool
True) (ReadBinHandle -> IO [IfaceConDecl]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh)
Word8
3 -> (IfaceConDecl -> IfaceConDecls)
-> IO IfaceConDecl -> IO IfaceConDecls
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM IfaceConDecl -> IfaceConDecls
IfNewTyCon (ReadBinHandle -> IO IfaceConDecl
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh)
Word8
_ -> String -> IO IfaceConDecls
forall a. HasCallStack => String -> a
error String
"Binary(IfaceConDecls).get: Invalid IfaceConDecls"
instance Binary IfaceConDecl where
put_ :: WriteBinHandle -> IfaceConDecl -> IO ()
put_ WriteBinHandle
bh (IfCon IfExtName
a1 Bool
a2 Bool
a3 [IfaceBndr]
a4 [IfaceForAllSpecBndr]
a5 [IfaceTvBndr]
a6 IfaceContext
a7 [(IfaceType, IfaceType)]
a8 [FieldLabel]
a9 [IfaceBang]
a10 [IfaceSrcBang]
a11) = do
WriteBinHandle -> IfExtName -> IO ()
putIfaceTopBndr WriteBinHandle
bh IfExtName
a1
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
a2
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
a3
WriteBinHandle -> [IfaceBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceBndr]
a4
WriteBinHandle -> [IfaceForAllSpecBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceForAllSpecBndr]
a5
WriteBinHandle -> [IfaceTvBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceTvBndr]
a6
WriteBinHandle -> IfaceContext -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceContext
a7
WriteBinHandle -> [(IfaceType, IfaceType)] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [(IfaceType, IfaceType)]
a8
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh ([FieldLabel] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [FieldLabel]
a9)
(FieldLabel -> IO ()) -> [FieldLabel] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (WriteBinHandle -> FieldLabel -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh) [FieldLabel]
a9
WriteBinHandle -> [IfaceBang] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceBang]
a10
WriteBinHandle -> [IfaceSrcBang] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceSrcBang]
a11
get :: ReadBinHandle -> IO IfaceConDecl
get ReadBinHandle
bh = do
a1 <- ReadBinHandle -> IO IfExtName
getIfaceTopBndr ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
a5 <- get bh
a6 <- get bh
a7 <- get bh
a8 <- get bh
n_fields <- get bh
a9 <- replicateM n_fields (get bh)
a10 <- get bh
a11 <- get bh
return (IfCon a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11)
instance Binary IfaceBang where
put_ :: WriteBinHandle -> IfaceBang -> IO ()
put_ WriteBinHandle
bh IfaceBang
IfNoBang = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
put_ WriteBinHandle
bh IfaceBang
IfStrict = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
put_ WriteBinHandle
bh IfaceBang
IfUnpack = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2
put_ WriteBinHandle
bh (IfUnpackCo IfaceCoercion
co) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> IfaceCoercion -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceCoercion
co
get :: ReadBinHandle -> IO IfaceBang
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> IfaceBang -> IO IfaceBang
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceBang
IfNoBang
Word8
1 -> IfaceBang -> IO IfaceBang
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceBang
IfStrict
Word8
2 -> IfaceBang -> IO IfaceBang
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceBang
IfUnpack
Word8
_ -> IfaceCoercion -> IfaceBang
IfUnpackCo (IfaceCoercion -> IfaceBang) -> IO IfaceCoercion -> IO IfaceBang
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO IfaceCoercion
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Binary IfaceSrcBang where
put_ :: WriteBinHandle -> IfaceSrcBang -> IO ()
put_ WriteBinHandle
bh (IfSrcBang SrcUnpackedness
a1 SrcStrictness
a2) =
do WriteBinHandle -> SrcUnpackedness -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh SrcUnpackedness
a1
WriteBinHandle -> SrcStrictness -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh SrcStrictness
a2
get :: ReadBinHandle -> IO IfaceSrcBang
get ReadBinHandle
bh =
do a1 <- ReadBinHandle -> IO SrcUnpackedness
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
a2 <- get bh
return (IfSrcBang a1 a2)
instance Binary IfaceDefault where
put_ :: WriteBinHandle -> IfaceDefault -> IO ()
put_ WriteBinHandle
bh (IfaceDefault IfaceTyCon
cls IfaceContext
tys Maybe IfaceWarningTxt
warn) = do
WriteBinHandle -> IfaceTyCon -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceTyCon
cls
WriteBinHandle -> IfaceContext -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceContext
tys
WriteBinHandle -> Maybe IfaceWarningTxt -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe IfaceWarningTxt
warn
get :: ReadBinHandle -> IO IfaceDefault
get ReadBinHandle
bh = do
cls <- ReadBinHandle -> IO IfaceTyCon
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
tys <- get bh
warn <- get bh
return (IfaceDefault cls tys warn)
instance Binary IfaceClsInst where
put_ :: WriteBinHandle -> IfaceClsInst -> IO ()
put_ WriteBinHandle
bh (IfaceClsInst IfExtName
cls [Maybe IfaceTyCon]
tys IfExtName
dfun OverlapFlag
flag IsOrphan
orph Maybe IfaceWarningTxt
warn) = do
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
cls
WriteBinHandle -> [Maybe IfaceTyCon] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [Maybe IfaceTyCon]
tys
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
dfun
WriteBinHandle -> OverlapFlag -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh OverlapFlag
flag
WriteBinHandle -> IsOrphan -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IsOrphan
orph
WriteBinHandle -> Maybe IfaceWarningTxt -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe IfaceWarningTxt
warn
get :: ReadBinHandle -> IO IfaceClsInst
get ReadBinHandle
bh = do
cls <- ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
tys <- get bh
dfun <- get bh
flag <- get bh
orph <- get bh
warn <- get bh
return (IfaceClsInst cls tys dfun flag orph warn)
instance Binary IfaceFamInst where
put_ :: WriteBinHandle -> IfaceFamInst -> IO ()
put_ WriteBinHandle
bh (IfaceFamInst IfExtName
fam [Maybe IfaceTyCon]
tys IfExtName
name IsOrphan
orph) = do
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
fam
WriteBinHandle -> [Maybe IfaceTyCon] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [Maybe IfaceTyCon]
tys
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
name
WriteBinHandle -> IsOrphan -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IsOrphan
orph
get :: ReadBinHandle -> IO IfaceFamInst
get ReadBinHandle
bh = do
fam <- ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
tys <- get bh
name <- get bh
orph <- get bh
return (IfaceFamInst fam tys name orph)
instance Binary IfaceRule where
put_ :: WriteBinHandle -> IfaceRule -> IO ()
put_ WriteBinHandle
bh (IfaceRule FastString
a1 Activation
a2 [IfaceBndr]
a3 IfExtName
a4 [IfaceExpr]
a5 IfaceExpr
a6 Bool
a7 IsOrphan
a8) = do
WriteBinHandle -> FastString -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh FastString
a1
WriteBinHandle -> Activation -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Activation
a2
WriteBinHandle -> [IfaceBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceBndr]
a3
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
a4
WriteBinHandle -> [IfaceExpr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceExpr]
a5
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
a6
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
a7
WriteBinHandle -> IsOrphan -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IsOrphan
a8
get :: ReadBinHandle -> IO IfaceRule
get ReadBinHandle
bh = do
a1 <- ReadBinHandle -> IO FastString
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
a2 <- get bh
a3 <- get bh
a4 <- get bh
a5 <- get bh
a6 <- get bh
a7 <- get bh
a8 <- get bh
return (IfaceRule a1 a2 a3 a4 a5 a6 a7 a8)
instance Binary IfaceWarnings where
put_ :: WriteBinHandle -> IfaceWarnings -> IO ()
put_ WriteBinHandle
bh = \case
IfWarnAll IfaceWarningTxt
txt -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> IfaceWarningTxt -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceWarningTxt
txt
IfWarnSome [(OccName, IfaceWarningTxt)]
vs [(IfExtName, IfaceWarningTxt)]
ds -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> [(OccName, IfaceWarningTxt)] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [(OccName, IfaceWarningTxt)]
vs IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> [(IfExtName, IfaceWarningTxt)] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [(IfExtName, IfaceWarningTxt)]
ds
get :: ReadBinHandle -> IO IfaceWarnings
get ReadBinHandle
bh = ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh IO Word8 -> (Word8 -> IO IfaceWarnings) -> IO IfaceWarnings
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Word8
0 -> (IfaceWarningTxt -> IfaceWarnings)
-> IO (IfaceWarningTxt -> IfaceWarnings)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure IfaceWarningTxt -> IfaceWarnings
IfWarnAll IO (IfaceWarningTxt -> IfaceWarnings)
-> IO IfaceWarningTxt -> IO IfaceWarnings
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceWarningTxt
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
1 -> ([(OccName, IfaceWarningTxt)]
-> [(IfExtName, IfaceWarningTxt)] -> IfaceWarnings)
-> IO
([(OccName, IfaceWarningTxt)]
-> [(IfExtName, IfaceWarningTxt)] -> IfaceWarnings)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [(OccName, IfaceWarningTxt)]
-> [(IfExtName, IfaceWarningTxt)] -> IfaceWarnings
IfWarnSome IO
([(OccName, IfaceWarningTxt)]
-> [(IfExtName, IfaceWarningTxt)] -> IfaceWarnings)
-> IO [(OccName, IfaceWarningTxt)]
-> IO ([(IfExtName, IfaceWarningTxt)] -> IfaceWarnings)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [(OccName, IfaceWarningTxt)]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO ([(IfExtName, IfaceWarningTxt)] -> IfaceWarnings)
-> IO [(IfExtName, IfaceWarningTxt)] -> IO IfaceWarnings
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [(IfExtName, IfaceWarningTxt)]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> String -> IO IfaceWarnings
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"invalid tag(IfaceWarnings)"
instance Binary IfaceWarningTxt where
put_ :: WriteBinHandle -> IfaceWarningTxt -> IO ()
put_ WriteBinHandle
bh = \case
IfWarningTxt Maybe WarningCategory
a1 SourceText
a2 [(IfaceStringLiteral, [IfExtName])]
a3 -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> Maybe WarningCategory -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe WarningCategory
a1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> SourceText -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh SourceText
a2 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> [(IfaceStringLiteral, [IfExtName])] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [(IfaceStringLiteral, [IfExtName])]
a3
IfDeprecatedTxt SourceText
a1 [(IfaceStringLiteral, [IfExtName])]
a2 -> WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> SourceText -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh SourceText
a1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> [(IfaceStringLiteral, [IfExtName])] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [(IfaceStringLiteral, [IfExtName])]
a2
get :: ReadBinHandle -> IO IfaceWarningTxt
get ReadBinHandle
bh = ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh IO Word8 -> (Word8 -> IO IfaceWarningTxt) -> IO IfaceWarningTxt
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Word8
0 -> (Maybe WarningCategory
-> SourceText
-> [(IfaceStringLiteral, [IfExtName])]
-> IfaceWarningTxt)
-> IO
(Maybe WarningCategory
-> SourceText
-> [(IfaceStringLiteral, [IfExtName])]
-> IfaceWarningTxt)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe WarningCategory
-> SourceText
-> [(IfaceStringLiteral, [IfExtName])]
-> IfaceWarningTxt
IfWarningTxt IO
(Maybe WarningCategory
-> SourceText
-> [(IfaceStringLiteral, [IfExtName])]
-> IfaceWarningTxt)
-> IO (Maybe WarningCategory)
-> IO
(SourceText
-> [(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO (Maybe WarningCategory)
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO
(SourceText
-> [(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
-> IO SourceText
-> IO ([(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO SourceText
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO ([(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
-> IO [(IfaceStringLiteral, [IfExtName])] -> IO IfaceWarningTxt
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [(IfaceStringLiteral, [IfExtName])]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> (SourceText
-> [(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
-> IO
(SourceText
-> [(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SourceText
-> [(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt
IfDeprecatedTxt IO
(SourceText
-> [(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
-> IO SourceText
-> IO ([(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO SourceText
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO ([(IfaceStringLiteral, [IfExtName])] -> IfaceWarningTxt)
-> IO [(IfaceStringLiteral, [IfExtName])] -> IO IfaceWarningTxt
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO [(IfaceStringLiteral, [IfExtName])]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Binary IfaceStringLiteral where
put_ :: WriteBinHandle -> IfaceStringLiteral -> IO ()
put_ WriteBinHandle
bh (IfStringLiteral SourceText
a1 FastString
a2) = WriteBinHandle -> SourceText -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh SourceText
a1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> WriteBinHandle -> FastString -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh FastString
a2
get :: ReadBinHandle -> IO IfaceStringLiteral
get ReadBinHandle
bh = SourceText -> FastString -> IfaceStringLiteral
IfStringLiteral (SourceText -> FastString -> IfaceStringLiteral)
-> IO SourceText -> IO (FastString -> IfaceStringLiteral)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO SourceText
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (FastString -> IfaceStringLiteral)
-> IO FastString -> IO IfaceStringLiteral
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO FastString
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Binary IfaceAnnotation where
put_ :: WriteBinHandle -> IfaceAnnotation -> IO ()
put_ WriteBinHandle
bh (IfaceAnnotation IfaceAnnTarget
a1 AnnPayload
a2) = do
WriteBinHandle -> IfaceAnnTarget -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceAnnTarget
a1
WriteBinHandle -> AnnPayload -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh AnnPayload
a2
get :: ReadBinHandle -> IO IfaceAnnotation
get ReadBinHandle
bh = do
a1 <- ReadBinHandle -> IO IfaceAnnTarget
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
a2 <- get bh
return (IfaceAnnotation a1 a2)
instance Binary IfaceIdDetails where
put_ :: WriteBinHandle -> IfaceIdDetails -> IO ()
put_ WriteBinHandle
bh IfaceIdDetails
IfVanillaId = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
put_ WriteBinHandle
bh (IfRecSelId Either IfaceTyCon IfaceDecl
a IfExtName
b Bool
c FieldLabel
d) = do { WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
; WriteBinHandle -> Either IfaceTyCon IfaceDecl -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Either IfaceTyCon IfaceDecl
a
; WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
b
; WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
c
; WriteBinHandle -> FieldLabel -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh FieldLabel
d }
put_ WriteBinHandle
bh (IfWorkerLikeId [CbvMark]
dmds) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> [CbvMark] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [CbvMark]
dmds
put_ WriteBinHandle
bh IfaceIdDetails
IfDFunId = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3
get :: ReadBinHandle -> IO IfaceIdDetails
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> IfaceIdDetails -> IO IfaceIdDetails
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceIdDetails
IfVanillaId
Word8
1 -> do { a <- ReadBinHandle -> IO (Either IfaceTyCon IfaceDecl)
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
; b <- get bh
; c <- get bh
; d <- get bh
; return (IfRecSelId a b c d) }
Word8
2 -> do { dmds <- ReadBinHandle -> IO [CbvMark]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
; return (IfWorkerLikeId dmds) }
Word8
_ -> IfaceIdDetails -> IO IfaceIdDetails
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceIdDetails
IfDFunId
instance Binary IfaceInfoItem where
put_ :: WriteBinHandle -> IfaceInfoItem -> IO ()
put_ WriteBinHandle
bh (HsArity Int
aa) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Int
aa
put_ WriteBinHandle
bh (HsDmdSig DmdSig
ab) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> DmdSig -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh DmdSig
ab
put_ WriteBinHandle
bh (HsUnfold Bool
lb IfaceUnfolding
ad) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
lb IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> IfaceUnfolding -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceUnfolding
ad
put_ WriteBinHandle
bh (HsInline InlinePragma
ad) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> InlinePragma -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh InlinePragma
ad
put_ WriteBinHandle
bh IfaceInfoItem
HsNoCafRefs = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
4
put_ WriteBinHandle
bh (HsCprSig CprSig
cpr) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
6 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> CprSig -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh CprSig
cpr
put_ WriteBinHandle
bh (HsLFInfo IfaceLFInfo
lf_info) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
7 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> IfaceLFInfo -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceLFInfo
lf_info
put_ WriteBinHandle
bh (HsTagSig TagSig
sig) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
8 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> TagSig -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh TagSig
sig
get :: ReadBinHandle -> IO IfaceInfoItem
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> (Int -> IfaceInfoItem) -> IO Int -> IO IfaceInfoItem
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Int -> IfaceInfoItem
HsArity (IO Int -> IO IfaceInfoItem) -> IO Int -> IO IfaceInfoItem
forall a b. (a -> b) -> a -> b
$ ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
1 -> (DmdSig -> IfaceInfoItem) -> IO DmdSig -> IO IfaceInfoItem
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM DmdSig -> IfaceInfoItem
HsDmdSig (IO DmdSig -> IO IfaceInfoItem) -> IO DmdSig -> IO IfaceInfoItem
forall a b. (a -> b) -> a -> b
$ ReadBinHandle -> IO DmdSig
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
2 -> do lb <- ReadBinHandle -> IO Bool
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
ad <- get bh
return (HsUnfold lb ad)
Word8
3 -> (InlinePragma -> IfaceInfoItem)
-> IO InlinePragma -> IO IfaceInfoItem
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM InlinePragma -> IfaceInfoItem
HsInline (IO InlinePragma -> IO IfaceInfoItem)
-> IO InlinePragma -> IO IfaceInfoItem
forall a b. (a -> b) -> a -> b
$ ReadBinHandle -> IO InlinePragma
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
4 -> IfaceInfoItem -> IO IfaceInfoItem
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceInfoItem
HsNoCafRefs
Word8
6 -> CprSig -> IfaceInfoItem
HsCprSig (CprSig -> IfaceInfoItem) -> IO CprSig -> IO IfaceInfoItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO CprSig
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
7 -> IfaceLFInfo -> IfaceInfoItem
HsLFInfo (IfaceLFInfo -> IfaceInfoItem)
-> IO IfaceLFInfo -> IO IfaceInfoItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO IfaceLFInfo
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> TagSig -> IfaceInfoItem
HsTagSig (TagSig -> IfaceInfoItem) -> IO TagSig -> IO IfaceInfoItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO TagSig
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance Binary IfaceUnfolding where
put_ :: WriteBinHandle -> IfaceUnfolding -> IO ()
put_ WriteBinHandle
bh (IfCoreUnfold UnfoldingSource
s IfUnfoldingCache
c IfGuidance
g IfaceExpr
e) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
WriteBinHandle -> UnfoldingSource -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh UnfoldingSource
s
WriteBinHandle -> IfUnfoldingCache -> IO ()
putUnfoldingCache WriteBinHandle
bh IfUnfoldingCache
c
WriteBinHandle -> IfGuidance -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfGuidance
g
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
e
put_ WriteBinHandle
bh (IfDFunUnfold [IfaceBndr]
as [IfaceExpr]
bs) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> [IfaceBndr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceBndr]
as
WriteBinHandle -> [IfaceExpr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceExpr]
bs
get :: ReadBinHandle -> IO IfaceUnfolding
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> do s <- ReadBinHandle -> IO UnfoldingSource
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
c <- getUnfoldingCache bh
g <- get bh
e <- get bh
return (IfCoreUnfold s c g e)
Word8
_ -> do as <- ReadBinHandle -> IO [IfaceBndr]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
bs <- get bh
return (IfDFunUnfold as bs)
instance Binary IfGuidance where
put_ :: WriteBinHandle -> IfGuidance -> IO ()
put_ WriteBinHandle
bh IfGuidance
IfNoGuidance = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
put_ WriteBinHandle
bh (IfWhen Int
a Bool
b Bool
c ) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Int
a
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
b
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
c
get :: ReadBinHandle -> IO IfGuidance
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> IfGuidance -> IO IfGuidance
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfGuidance
IfNoGuidance
Word8
_ -> do a <- ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
b <- get bh
c <- get bh
return (IfWhen a b c)
putUnfoldingCache :: WriteBinHandle -> IfUnfoldingCache -> IO ()
putUnfoldingCache :: WriteBinHandle -> IfUnfoldingCache -> IO ()
putUnfoldingCache WriteBinHandle
bh (UnfoldingCache { uf_is_value :: IfUnfoldingCache -> Bool
uf_is_value = Bool
hnf, uf_is_conlike :: IfUnfoldingCache -> Bool
uf_is_conlike = Bool
conlike
, uf_is_work_free :: IfUnfoldingCache -> Bool
uf_is_work_free = Bool
wf, uf_expandable :: IfUnfoldingCache -> Bool
uf_expandable = Bool
exp }) = do
let b :: Word8
b = Word8
forall a. Bits a => a
zeroBits Word8 -> Bool -> Word8
forall a. (Num a, Bits a) => a -> Bool -> a
.<<|. Bool
hnf Word8 -> Bool -> Word8
forall a. (Num a, Bits a) => a -> Bool -> a
.<<|. Bool
conlike Word8 -> Bool -> Word8
forall a. (Num a, Bits a) => a -> Bool -> a
.<<|. Bool
wf Word8 -> Bool -> Word8
forall a. (Num a, Bits a) => a -> Bool -> a
.<<|. Bool
exp
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
b
getUnfoldingCache :: ReadBinHandle -> IO IfUnfoldingCache
getUnfoldingCache :: ReadBinHandle -> IO IfUnfoldingCache
getUnfoldingCache ReadBinHandle
bh = do
b <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
let hnf = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
b Int
3
conlike = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
b Int
2
wf = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
b Int
1
exp = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
b Int
0
return (UnfoldingCache { uf_is_value = hnf, uf_is_conlike = conlike
, uf_is_work_free = wf, uf_expandable = exp })
infixl 9 .<<|.
(.<<|.) :: (Num a, Bits a) => a -> Bool -> a
a
x .<<|. :: forall a. (Num a, Bits a) => a -> Bool -> a
.<<|. Bool
b = (if Bool
b then (a -> Int -> a
forall a. (Num a, Bits a) => a -> Int -> a
`setBit` Int
0) else a -> a
forall a. a -> a
id) (a
x a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
1)
{-# INLINE (.<<|.) #-}
instance Binary IfaceAlt where
put_ :: WriteBinHandle -> IfaceAlt -> IO ()
put_ WriteBinHandle
bh (IfaceAlt IfaceConAlt
a [IfLclName]
b IfaceExpr
c) = do
WriteBinHandle -> IfaceConAlt -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceConAlt
a
WriteBinHandle -> [IfLclName] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfLclName]
b
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
c
get :: ReadBinHandle -> IO IfaceAlt
get ReadBinHandle
bh = do
a <- ReadBinHandle -> IO IfaceConAlt
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
b <- get bh
c <- get bh
return (IfaceAlt a b c)
instance Binary IfaceExpr where
put_ :: WriteBinHandle -> IfaceExpr -> IO ()
put_ WriteBinHandle
bh (IfaceLcl IfLclName
aa) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
WriteBinHandle -> IfLclName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfLclName
aa
put_ WriteBinHandle
bh (IfaceType IfaceType
ab) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
ab
put_ WriteBinHandle
bh (IfaceCo IfaceCoercion
ab) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2
WriteBinHandle -> IfaceCoercion -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceCoercion
ab
put_ WriteBinHandle
bh (IfaceTuple TupleSort
ac [IfaceExpr]
ad) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3
WriteBinHandle -> TupleSort -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh TupleSort
ac
WriteBinHandle -> [IfaceExpr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceExpr]
ad
put_ WriteBinHandle
bh (IfaceLam (IfaceBndr
ae, IfaceOneShot
os) IfaceExpr
af) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
4
WriteBinHandle -> IfaceBndr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceBndr
ae
WriteBinHandle -> IfaceOneShot -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceOneShot
os
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
af
put_ WriteBinHandle
bh (IfaceApp IfaceExpr
ag IfaceExpr
ah) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
5
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
ag
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
ah
put_ WriteBinHandle
bh (IfaceCase IfaceExpr
ai IfLclName
aj [IfaceAlt]
ak) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
6
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
ai
WriteBinHandle -> IfLclName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfLclName
aj
WriteBinHandle -> [IfaceAlt] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceAlt]
ak
put_ WriteBinHandle
bh (IfaceLet IfaceBindingX IfaceExpr IfaceLetBndr
al IfaceExpr
am) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
7
WriteBinHandle -> IfaceBindingX IfaceExpr IfaceLetBndr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceBindingX IfaceExpr IfaceLetBndr
al
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
am
put_ WriteBinHandle
bh (IfaceTick IfaceTickish
an IfaceExpr
ao) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
8
WriteBinHandle -> IfaceTickish -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceTickish
an
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
ao
put_ WriteBinHandle
bh (IfaceLit Literal
ap) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
9
WriteBinHandle -> Literal -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Literal
ap
put_ WriteBinHandle
bh (IfaceFCall ForeignCall
as IfaceType
at) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
10
WriteBinHandle -> ForeignCall -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh ForeignCall
as
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
at
put_ WriteBinHandle
bh (IfaceExt IfExtName
aa) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
11
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
aa
put_ WriteBinHandle
bh (IfaceCast IfaceExpr
ie IfaceCoercion
ico) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
12
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
ie
WriteBinHandle -> IfaceCoercion -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceCoercion
ico
put_ WriteBinHandle
bh (IfaceECase IfaceExpr
a IfaceType
b) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
13
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
a
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
b
put_ WriteBinHandle
bh (IfaceLitRubbish TypeOrConstraint
TypeLike IfaceType
r) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
14
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
r
put_ WriteBinHandle
bh (IfaceLitRubbish TypeOrConstraint
ConstraintLike IfaceType
r) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
15
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
r
get :: ReadBinHandle -> IO IfaceExpr
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> do aa <- ReadBinHandle -> IO IfLclName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
return (IfaceLcl aa)
Word8
1 -> do ab <- ReadBinHandle -> IO IfaceType
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
return (IfaceType ab)
Word8
2 -> do ab <- ReadBinHandle -> IO IfaceCoercion
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
return (IfaceCo ab)
Word8
3 -> do ac <- ReadBinHandle -> IO TupleSort
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
ad <- get bh
return (IfaceTuple ac ad)
Word8
4 -> do ae <- ReadBinHandle -> IO IfaceBndr
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
os <- get bh
af <- get bh
return (IfaceLam (ae, os) af)
Word8
5 -> do ag <- ReadBinHandle -> IO IfaceExpr
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
ah <- get bh
return (IfaceApp ag ah)
Word8
6 -> do ai <- ReadBinHandle -> IO IfaceExpr
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
aj <- get bh
ak <- get bh
return (IfaceCase ai aj ak)
Word8
7 -> do al <- ReadBinHandle -> IO (IfaceBindingX IfaceExpr IfaceLetBndr)
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
am <- get bh
return (IfaceLet al am)
Word8
8 -> do an <- ReadBinHandle -> IO IfaceTickish
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
ao <- get bh
return (IfaceTick an ao)
Word8
9 -> do ap <- ReadBinHandle -> IO Literal
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
return (IfaceLit ap)
Word8
10 -> do as <- ReadBinHandle -> IO ForeignCall
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
at <- get bh
return (IfaceFCall as at)
Word8
11 -> do aa <- ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
return (IfaceExt aa)
Word8
12 -> do ie <- ReadBinHandle -> IO IfaceExpr
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
ico <- get bh
return (IfaceCast ie ico)
Word8
13 -> do a <- ReadBinHandle -> IO IfaceExpr
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
b <- get bh
return (IfaceECase a b)
Word8
14 -> do r <- ReadBinHandle -> IO IfaceType
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
return (IfaceLitRubbish TypeLike r)
Word8
15 -> do r <- ReadBinHandle -> IO IfaceType
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
return (IfaceLitRubbish ConstraintLike r)
Word8
_ -> String -> IO IfaceExpr
forall a. HasCallStack => String -> a
panic (String
"get IfaceExpr " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
h)
instance Binary IfaceTickish where
put_ :: WriteBinHandle -> IfaceTickish -> IO ()
put_ WriteBinHandle
bh (IfaceHpcTick Module
m Int
ix) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
WriteBinHandle -> Module -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Module
m
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Int
ix
put_ WriteBinHandle
bh (IfaceSCC CostCentre
cc Bool
tick Bool
push) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> CostCentre -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh CostCentre
cc
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
tick
WriteBinHandle -> Bool -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Bool
push
put_ WriteBinHandle
bh (IfaceSource RealSrcSpan
src FastString
name) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2
WriteBinHandle -> FastString -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
src)
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
src)
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
src)
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
src)
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh (RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
src)
WriteBinHandle -> FastString -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh FastString
name
put_ WriteBinHandle
bh (IfaceBreakpoint Int
m [IfaceExpr]
ix Module
fvs) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
3
WriteBinHandle -> Int -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Int
m
WriteBinHandle -> [IfaceExpr] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceExpr]
ix
WriteBinHandle -> Module -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Module
fvs
get :: ReadBinHandle -> IO IfaceTickish
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> do m <- ReadBinHandle -> IO Module
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
ix <- get bh
return (IfaceHpcTick m ix)
Word8
1 -> do cc <- ReadBinHandle -> IO CostCentre
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
tick <- get bh
push <- get bh
return (IfaceSCC cc tick push)
Word8
2 -> do file <- ReadBinHandle -> IO FastString
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
sl <- get bh
sc <- get bh
el <- get bh
ec <- get bh
let start = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
file Int
sl Int
sc
end = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
file Int
el Int
ec
name <- get bh
return (IfaceSource (mkRealSrcSpan start end) name)
Word8
3 -> do m <- ReadBinHandle -> IO Int
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
ix <- get bh
fvs <- get bh
return (IfaceBreakpoint m ix fvs)
Word8
_ -> String -> IO IfaceTickish
forall a. HasCallStack => String -> a
panic (String
"get IfaceTickish " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
h)
instance Binary IfaceConAlt where
put_ :: WriteBinHandle -> IfaceConAlt -> IO ()
put_ WriteBinHandle
bh IfaceConAlt
IfaceDefaultAlt = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
put_ WriteBinHandle
bh (IfaceDataAlt IfExtName
aa) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
aa
put_ WriteBinHandle
bh (IfaceLitAlt Literal
ac) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> Literal -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Literal
ac
get :: ReadBinHandle -> IO IfaceConAlt
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> IfaceConAlt -> IO IfaceConAlt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceConAlt
IfaceDefaultAlt
Word8
1 -> (IfExtName -> IfaceConAlt) -> IO IfExtName -> IO IfaceConAlt
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM IfExtName -> IfaceConAlt
IfaceDataAlt (IO IfExtName -> IO IfaceConAlt) -> IO IfExtName -> IO IfaceConAlt
forall a b. (a -> b) -> a -> b
$ ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> (Literal -> IfaceConAlt) -> IO Literal -> IO IfaceConAlt
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Literal -> IfaceConAlt
IfaceLitAlt (IO Literal -> IO IfaceConAlt) -> IO Literal -> IO IfaceConAlt
forall a b. (a -> b) -> a -> b
$ ReadBinHandle -> IO Literal
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance (Binary r, Binary b) => Binary (IfaceBindingX b r) where
put_ :: WriteBinHandle -> IfaceBindingX b r -> IO ()
put_ WriteBinHandle
bh (IfaceNonRec r
aa b
ab) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> r -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh r
aa IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> b -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh b
ab
put_ WriteBinHandle
bh (IfaceRec [(r, b)]
ac) = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> [(r, b)] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [(r, b)]
ac
get :: ReadBinHandle -> IO (IfaceBindingX b r)
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> do { aa <- ReadBinHandle -> IO r
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh; ab <- get bh; return (IfaceNonRec aa ab) }
Word8
_ -> do { ac <- ReadBinHandle -> IO [(r, b)]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh; return (IfaceRec ac) }
instance Binary IfaceLetBndr where
put_ :: WriteBinHandle -> IfaceLetBndr -> IO ()
put_ WriteBinHandle
bh (IfLetBndr IfLclName
a IfaceType
b IfaceIdInfo
c JoinPointHood
d) = do
WriteBinHandle -> IfLclName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfLclName
a
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
b
WriteBinHandle -> IfaceIdInfo -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceIdInfo
c
WriteBinHandle -> JoinPointHood -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh JoinPointHood
d
get :: ReadBinHandle -> IO IfaceLetBndr
get ReadBinHandle
bh = do a <- ReadBinHandle -> IO IfLclName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
b <- get bh
c <- get bh
d <- get bh
return (IfLetBndr a b c d)
instance Binary IfaceTopBndrInfo where
put_ :: WriteBinHandle -> IfaceTopBndrInfo -> IO ()
put_ WriteBinHandle
bh (IfLclTopBndr IfLclName
lcl IfaceType
ty IfaceIdInfo
info IfaceIdDetails
dets) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
WriteBinHandle -> IfLclName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfLclName
lcl
WriteBinHandle -> IfaceType -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceType
ty
WriteBinHandle -> IfaceIdInfo -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceIdInfo
info
WriteBinHandle -> IfaceIdDetails -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceIdDetails
dets
put_ WriteBinHandle
bh (IfGblTopBndr IfExtName
gbl) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
gbl
get :: ReadBinHandle -> IO IfaceTopBndrInfo
get ReadBinHandle
bh = do
tag <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case tag of
Word8
0 -> IfLclName
-> IfaceType -> IfaceIdInfo -> IfaceIdDetails -> IfaceTopBndrInfo
IfLclTopBndr (IfLclName
-> IfaceType -> IfaceIdInfo -> IfaceIdDetails -> IfaceTopBndrInfo)
-> IO IfLclName
-> IO
(IfaceType -> IfaceIdInfo -> IfaceIdDetails -> IfaceTopBndrInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO IfLclName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (IfaceType -> IfaceIdInfo -> IfaceIdDetails -> IfaceTopBndrInfo)
-> IO IfaceType
-> IO (IfaceIdInfo -> IfaceIdDetails -> IfaceTopBndrInfo)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceType
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (IfaceIdInfo -> IfaceIdDetails -> IfaceTopBndrInfo)
-> IO IfaceIdInfo -> IO (IfaceIdDetails -> IfaceTopBndrInfo)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceIdInfo
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (IfaceIdDetails -> IfaceTopBndrInfo)
-> IO IfaceIdDetails -> IO IfaceTopBndrInfo
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO IfaceIdDetails
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
1 -> IfExtName -> IfaceTopBndrInfo
IfGblTopBndr (IfExtName -> IfaceTopBndrInfo)
-> IO IfExtName -> IO IfaceTopBndrInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> String -> SDoc -> IO IfaceTopBndrInfo
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"IfaceTopBndrInfo" (Word8 -> SDoc
forall a. Integral a => a -> SDoc
intWithCommas Word8
tag)
instance Binary IfaceMaybeRhs where
put_ :: WriteBinHandle -> IfaceMaybeRhs -> IO ()
put_ WriteBinHandle
bh IfaceMaybeRhs
IfUseUnfoldingRhs = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
put_ WriteBinHandle
bh (IfRhs IfaceExpr
e) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> IfaceExpr -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceExpr
e
get :: ReadBinHandle -> IO IfaceMaybeRhs
get ReadBinHandle
bh = do
b <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case b of
Word8
0 -> IfaceMaybeRhs -> IO IfaceMaybeRhs
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceMaybeRhs
IfUseUnfoldingRhs
Word8
1 -> IfaceExpr -> IfaceMaybeRhs
IfRhs (IfaceExpr -> IfaceMaybeRhs) -> IO IfaceExpr -> IO IfaceMaybeRhs
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO IfaceExpr
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
Word8
_ -> String -> SDoc -> IO IfaceMaybeRhs
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"IfaceMaybeRhs" (Word8 -> SDoc
forall a. Integral a => a -> SDoc
intWithCommas Word8
b)
instance Binary IfaceTyConParent where
put_ :: WriteBinHandle -> IfaceTyConParent -> IO ()
put_ WriteBinHandle
bh IfaceTyConParent
IfNoParent = WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
0
put_ WriteBinHandle
bh (IfDataInstance IfExtName
ax IfaceTyCon
pr IfaceAppArgs
ty) = do
WriteBinHandle -> Word8 -> IO ()
putByte WriteBinHandle
bh Word8
1
WriteBinHandle -> IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfExtName
ax
WriteBinHandle -> IfaceTyCon -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceTyCon
pr
WriteBinHandle -> IfaceAppArgs -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceAppArgs
ty
get :: ReadBinHandle -> IO IfaceTyConParent
get ReadBinHandle
bh = do
h <- ReadBinHandle -> IO Word8
getByte ReadBinHandle
bh
case h of
Word8
0 -> IfaceTyConParent -> IO IfaceTyConParent
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return IfaceTyConParent
IfNoParent
Word8
_ -> do
ax <- ReadBinHandle -> IO IfExtName
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
pr <- get bh
ty <- get bh
return $ IfDataInstance ax pr ty
instance Binary IfaceCompleteMatch where
put_ :: WriteBinHandle -> IfaceCompleteMatch -> IO ()
put_ WriteBinHandle
bh (IfaceCompleteMatch [IfExtName]
cs Maybe IfExtName
mtc) = WriteBinHandle -> [IfExtName] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfExtName]
cs IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> WriteBinHandle -> Maybe IfExtName -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe IfExtName
mtc
get :: ReadBinHandle -> IO IfaceCompleteMatch
get ReadBinHandle
bh = [IfExtName] -> Maybe IfExtName -> IfaceCompleteMatch
IfaceCompleteMatch ([IfExtName] -> Maybe IfExtName -> IfaceCompleteMatch)
-> IO [IfExtName] -> IO (Maybe IfExtName -> IfaceCompleteMatch)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadBinHandle -> IO [IfExtName]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh IO (Maybe IfExtName -> IfaceCompleteMatch)
-> IO (Maybe IfExtName) -> IO IfaceCompleteMatch
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadBinHandle -> IO (Maybe IfExtName)
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
instance NFData IfaceImport where
rnf :: IfaceImport -> ()
rnf (IfaceImport ImpDeclSpec
a ImpIfaceList
b) = ImpDeclSpec -> ()
forall a. NFData a => a -> ()
rnf ImpDeclSpec
a () -> () -> ()
forall a b. a -> b -> b
`seq` ImpIfaceList -> ()
forall a. NFData a => a -> ()
rnf ImpIfaceList
b
instance NFData ImpIfaceList where
rnf :: ImpIfaceList -> ()
rnf ImpIfaceList
ImpIfaceAll = ()
rnf (ImpIfaceEverythingBut NameSet
ns) = NameSet -> ()
forall a. NFData a => a -> ()
rnf NameSet
ns
rnf (ImpIfaceExplicit IfGlobalRdrEnv
gre) = IfGlobalRdrEnv -> ()
forall a. NFData a => a -> ()
rnf IfGlobalRdrEnv
gre
instance NFData IfaceDecl where
rnf :: IfaceDecl -> ()
rnf = \case
IfaceId IfExtName
f1 IfaceType
f2 IfaceIdDetails
f3 IfaceIdInfo
f4 ->
IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceIdDetails -> ()
forall a. NFData a => a -> ()
rnf IfaceIdDetails
f3 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceIdInfo -> ()
forall a. NFData a => a -> ()
rnf IfaceIdInfo
f4
IfaceData IfExtName
f1 [IfaceTyConBinder]
f2 IfaceType
f3 Maybe CType
f4 [Role]
f5 IfaceContext
f6 IfaceConDecls
f7 Bool
f8 IfaceTyConParent
f9 ->
IfExtName
f1 IfExtName -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceTyConBinder] -> ZonkAny 0 -> ZonkAny 0
forall a b. [a] -> b -> b
seqList [IfaceTyConBinder]
f2 (ZonkAny 0 -> ZonkAny 0) -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType
f3 IfaceType -> () -> ()
forall a b. a -> b -> b
`seq` Maybe CType
f4 Maybe CType -> () -> ()
forall a b. a -> b -> b
`seq` [Role]
f5 [Role] -> () -> ()
forall a b. a -> b -> b
`seq`
IfaceContext -> ()
forall a. NFData a => a -> ()
rnf IfaceContext
f6 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceConDecls -> ()
forall a. NFData a => a -> ()
rnf IfaceConDecls
f7 () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
f8 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceTyConParent -> ()
forall a. NFData a => a -> ()
rnf IfaceTyConParent
f9
IfaceSynonym IfExtName
f1 [Role]
f2 [IfaceTyConBinder]
f3 IfaceType
f4 IfaceType
f5 ->
IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` [Role]
f2 [Role] -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceTyConBinder] -> ZonkAny 1 -> ZonkAny 1
forall a b. [a] -> b -> b
seqList [IfaceTyConBinder]
f3 (ZonkAny 1 -> ZonkAny 1) -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
f4 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
f5
IfaceFamily IfExtName
f1 Maybe IfLclName
f2 [IfaceTyConBinder]
f3 IfaceType
f4 IfaceFamTyConFlav
f5 Injectivity
f6 ->
IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfLclName -> ()
forall a. NFData a => a -> ()
rnf Maybe IfLclName
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceTyConBinder] -> ZonkAny 2 -> ZonkAny 2
forall a b. [a] -> b -> b
seqList [IfaceTyConBinder]
f3 (ZonkAny 2 -> ZonkAny 2) -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
f4 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceFamTyConFlav -> ()
forall a. NFData a => a -> ()
rnf IfaceFamTyConFlav
f5 () -> () -> ()
forall a b. a -> b -> b
`seq` Injectivity
f6 Injectivity -> () -> ()
forall a b. a -> b -> b
`seq` ()
IfaceClass IfExtName
f1 [Role]
f2 [IfaceTyConBinder]
f3 [FunDep IfLclName]
f4 IfaceClassBody
f5 ->
IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` [Role]
f2 [Role] -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceTyConBinder] -> ZonkAny 3 -> ZonkAny 3
forall a b. [a] -> b -> b
seqList [IfaceTyConBinder]
f3 (ZonkAny 3 -> ZonkAny 3) -> () -> ()
forall a b. a -> b -> b
`seq` [FunDep IfLclName] -> ()
forall a. NFData a => a -> ()
rnf [FunDep IfLclName]
f4 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceClassBody -> ()
forall a. NFData a => a -> ()
rnf IfaceClassBody
f5
IfaceAxiom IfExtName
nm IfaceTyCon
tycon Role
role [IfaceAxBranch]
ax ->
IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
nm () -> () -> ()
forall a b. a -> b -> b
`seq`
IfaceTyCon -> ()
forall a. NFData a => a -> ()
rnf IfaceTyCon
tycon () -> () -> ()
forall a b. a -> b -> b
`seq`
Role
role Role -> () -> ()
forall a b. a -> b -> b
`seq`
[IfaceAxBranch] -> ()
forall a. NFData a => a -> ()
rnf [IfaceAxBranch]
ax
IfacePatSyn IfExtName
f1 Bool
f2 (IfExtName, Bool)
f3 Maybe (IfExtName, Bool)
f4 [IfaceForAllSpecBndr]
f5 [IfaceForAllSpecBndr]
f6 IfaceContext
f7 IfaceContext
f8 IfaceContext
f9 IfaceType
f10 [FieldLabel]
f11 ->
IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` (IfExtName, Bool) -> ()
forall a. NFData a => a -> ()
rnf (IfExtName, Bool)
f3 () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe (IfExtName, Bool) -> ()
forall a. NFData a => a -> ()
rnf Maybe (IfExtName, Bool)
f4 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceForAllSpecBndr]
f5 [IfaceForAllSpecBndr] -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceForAllSpecBndr]
f6 [IfaceForAllSpecBndr] -> () -> ()
forall a b. a -> b -> b
`seq`
IfaceContext -> ()
forall a. NFData a => a -> ()
rnf IfaceContext
f7 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceContext -> ()
forall a. NFData a => a -> ()
rnf IfaceContext
f8 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceContext -> ()
forall a. NFData a => a -> ()
rnf IfaceContext
f9 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
f10 () -> () -> ()
forall a b. a -> b -> b
`seq` [FieldLabel]
f11 [FieldLabel] -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceAxBranch where
rnf :: IfaceAxBranch -> ()
rnf (IfaceAxBranch [IfaceTvBndr]
f1 [IfaceTvBndr]
f2 [IfaceIdBndr]
f3 IfaceAppArgs
f4 [Role]
f5 IfaceType
f6 [Int]
f7) =
[IfaceTvBndr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceTvBndr]
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceTvBndr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceTvBndr]
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceIdBndr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceIdBndr]
f3 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceAppArgs -> ()
forall a. NFData a => a -> ()
rnf IfaceAppArgs
f4 () -> () -> ()
forall a b. a -> b -> b
`seq` [Role]
f5 [Role] -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
f6 () -> () -> ()
forall a b. a -> b -> b
`seq` [Int] -> ()
forall a. NFData a => a -> ()
rnf [Int]
f7
instance NFData IfaceClassBody where
rnf :: IfaceClassBody -> ()
rnf = \case
IfaceClassBody
IfAbstractClass -> ()
IfConcreteClass IfaceContext
f1 [IfaceAT]
f2 [IfaceClassOp]
f3 IfaceBooleanFormula
f4 -> IfaceContext -> ()
forall a. NFData a => a -> ()
rnf IfaceContext
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceAT] -> ()
forall a. NFData a => a -> ()
rnf [IfaceAT]
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceClassOp] -> ()
forall a. NFData a => a -> ()
rnf [IfaceClassOp]
f3 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceBooleanFormula -> ()
forall a. NFData a => a -> ()
rnf IfaceBooleanFormula
f4 () -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceBooleanFormula where
rnf :: IfaceBooleanFormula -> ()
rnf = \case
IfVar IfLclName
f1 -> IfLclName -> ()
forall a. NFData a => a -> ()
rnf IfLclName
f1
IfAnd [IfaceBooleanFormula]
f1 -> [IfaceBooleanFormula] -> ()
forall a. NFData a => a -> ()
rnf [IfaceBooleanFormula]
f1
IfOr [IfaceBooleanFormula]
f1 -> [IfaceBooleanFormula] -> ()
forall a. NFData a => a -> ()
rnf [IfaceBooleanFormula]
f1
IfParens IfaceBooleanFormula
f1 -> IfaceBooleanFormula -> ()
forall a. NFData a => a -> ()
rnf IfaceBooleanFormula
f1
instance NFData IfaceAT where
rnf :: IfaceAT -> ()
rnf (IfaceAT IfaceDecl
f1 Maybe IfaceType
f2) = IfaceDecl -> ()
forall a. NFData a => a -> ()
rnf IfaceDecl
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfaceType -> ()
forall a. NFData a => a -> ()
rnf Maybe IfaceType
f2
instance NFData IfaceClassOp where
rnf :: IfaceClassOp -> ()
rnf (IfaceClassOp IfExtName
f1 IfaceType
f2 Maybe (DefMethSpec IfaceType)
f3) = IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe (DefMethSpec IfaceType)
f3 Maybe (DefMethSpec IfaceType) -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceTyConParent where
rnf :: IfaceTyConParent -> ()
rnf = \case
IfaceTyConParent
IfNoParent -> ()
IfDataInstance IfExtName
f1 IfaceTyCon
f2 IfaceAppArgs
f3 -> IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceTyCon -> ()
forall a. NFData a => a -> ()
rnf IfaceTyCon
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceAppArgs -> ()
forall a. NFData a => a -> ()
rnf IfaceAppArgs
f3
instance NFData IfaceConDecls where
rnf :: IfaceConDecls -> ()
rnf = \case
IfaceConDecls
IfAbstractTyCon -> ()
IfDataTyCon Bool
_ [IfaceConDecl]
f1 -> [IfaceConDecl] -> ()
forall a. NFData a => a -> ()
rnf [IfaceConDecl]
f1
IfNewTyCon IfaceConDecl
f1 -> IfaceConDecl -> ()
forall a. NFData a => a -> ()
rnf IfaceConDecl
f1
instance NFData IfaceConDecl where
rnf :: IfaceConDecl -> ()
rnf (IfCon IfExtName
f1 Bool
f2 Bool
f3 [IfaceBndr]
f4 [IfaceForAllSpecBndr]
f5 [IfaceTvBndr]
f6 IfaceContext
f7 [(IfaceType, IfaceType)]
f8 [FieldLabel]
f9 [IfaceBang]
f10 [IfaceSrcBang]
f11) =
IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
f3 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceBndr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceBndr]
f4 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceForAllSpecBndr]
f5 [IfaceForAllSpecBndr] -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceTvBndr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceTvBndr]
f6 () -> () -> ()
forall a b. a -> b -> b
`seq`
IfaceContext -> ()
forall a. NFData a => a -> ()
rnf IfaceContext
f7 () -> () -> ()
forall a b. a -> b -> b
`seq` [(IfaceType, IfaceType)] -> ()
forall a. NFData a => a -> ()
rnf [(IfaceType, IfaceType)]
f8 () -> () -> ()
forall a b. a -> b -> b
`seq` [FieldLabel]
f9 [FieldLabel] -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceBang] -> ()
forall a. NFData a => a -> ()
rnf [IfaceBang]
f10 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceSrcBang] -> ()
forall a. NFData a => a -> ()
rnf [IfaceSrcBang]
f11
instance NFData IfaceSrcBang where
rnf :: IfaceSrcBang -> ()
rnf (IfSrcBang SrcUnpackedness
f1 SrcStrictness
f2) = SrcUnpackedness
f1 SrcUnpackedness -> () -> ()
forall a b. a -> b -> b
`seq` SrcStrictness
f2 SrcStrictness -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceBang where
rnf :: IfaceBang -> ()
rnf IfaceBang
x = IfaceBang
x IfaceBang -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceIdDetails where
rnf :: IfaceIdDetails -> ()
rnf = \case
IfaceIdDetails
IfVanillaId -> ()
IfWorkerLikeId [CbvMark]
dmds -> [CbvMark]
dmds [CbvMark] -> () -> ()
forall a b. [a] -> b -> b
`seqList` ()
IfRecSelId (Left IfaceTyCon
tycon) IfExtName
b Bool
c FieldLabel
d -> IfaceTyCon -> ()
forall a. NFData a => a -> ()
rnf IfaceTyCon
tycon () -> () -> ()
forall a b. a -> b -> b
`seq` IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
b () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
c () -> () -> ()
forall a b. a -> b -> b
`seq` FieldLabel -> ()
forall a. NFData a => a -> ()
rnf FieldLabel
d
IfRecSelId (Right IfaceDecl
decl) IfExtName
b Bool
c FieldLabel
d -> IfaceDecl -> ()
forall a. NFData a => a -> ()
rnf IfaceDecl
decl () -> () -> ()
forall a b. a -> b -> b
`seq` IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
b () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
c () -> () -> ()
forall a b. a -> b -> b
`seq` FieldLabel -> ()
forall a. NFData a => a -> ()
rnf FieldLabel
d
IfaceIdDetails
IfDFunId -> ()
instance NFData IfaceInfoItem where
rnf :: IfaceInfoItem -> ()
rnf = \case
HsArity Int
a -> Int -> ()
forall a. NFData a => a -> ()
rnf Int
a
HsDmdSig DmdSig
str -> DmdSig -> ()
seqDmdSig DmdSig
str
HsInline InlinePragma
p -> InlinePragma
p InlinePragma -> () -> ()
forall a b. a -> b -> b
`seq` ()
HsUnfold Bool
b IfaceUnfolding
unf -> Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
b () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceUnfolding -> ()
forall a. NFData a => a -> ()
rnf IfaceUnfolding
unf
IfaceInfoItem
HsNoCafRefs -> ()
HsCprSig CprSig
cpr -> CprSig
cpr CprSig -> () -> ()
forall a b. a -> b -> b
`seq` ()
HsLFInfo IfaceLFInfo
lf_info -> IfaceLFInfo
lf_info IfaceLFInfo -> () -> ()
forall a b. a -> b -> b
`seq` ()
HsTagSig TagSig
sig -> TagSig
sig TagSig -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfGuidance where
rnf :: IfGuidance -> ()
rnf = \case
IfGuidance
IfNoGuidance -> ()
IfWhen Int
a Bool
b Bool
c -> Int
a Int -> () -> ()
forall a b. a -> b -> b
`seq` Bool
b Bool -> () -> ()
forall a b. a -> b -> b
`seq` Bool
c Bool -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceUnfolding where
rnf :: IfaceUnfolding -> ()
rnf = \case
IfCoreUnfold UnfoldingSource
src IfUnfoldingCache
cache IfGuidance
guidance IfaceExpr
expr -> UnfoldingSource
src UnfoldingSource -> () -> ()
forall a b. a -> b -> b
`seq` IfUnfoldingCache
cache IfUnfoldingCache -> () -> ()
forall a b. a -> b -> b
`seq` IfGuidance -> ()
forall a. NFData a => a -> ()
rnf IfGuidance
guidance () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
expr
IfDFunUnfold [IfaceBndr]
bndrs [IfaceExpr]
exprs -> [IfaceBndr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceBndr]
bndrs () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceExpr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceExpr]
exprs
instance NFData IfaceExpr where
rnf :: IfaceExpr -> ()
rnf = \case
IfaceLcl IfLclName
nm -> IfLclName -> ()
forall a. NFData a => a -> ()
rnf IfLclName
nm
IfaceExt IfExtName
nm -> IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
nm
IfaceType IfaceType
ty -> IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
ty
IfaceCo IfaceCoercion
co -> IfaceCoercion -> ()
forall a. NFData a => a -> ()
rnf IfaceCoercion
co
IfaceTuple TupleSort
sort [IfaceExpr]
exprs -> TupleSort
sort TupleSort -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceExpr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceExpr]
exprs
IfaceLam IfaceLamBndr
bndr IfaceExpr
expr -> IfaceLamBndr -> ()
forall a. NFData a => a -> ()
rnf IfaceLamBndr
bndr () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
expr
IfaceApp IfaceExpr
e1 IfaceExpr
e2 -> IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
e1 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
e2
IfaceCase IfaceExpr
e IfLclName
nm [IfaceAlt]
alts -> IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
e () -> () -> ()
forall a b. a -> b -> b
`seq` IfLclName
nm IfLclName -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceAlt] -> ()
forall a. NFData a => a -> ()
rnf [IfaceAlt]
alts
IfaceECase IfaceExpr
e IfaceType
ty -> IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
e () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
ty
IfaceLet IfaceBindingX IfaceExpr IfaceLetBndr
bind IfaceExpr
e -> IfaceBindingX IfaceExpr IfaceLetBndr -> ()
forall a. NFData a => a -> ()
rnf IfaceBindingX IfaceExpr IfaceLetBndr
bind () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
e
IfaceCast IfaceExpr
e IfaceCoercion
co -> IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
e () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceCoercion -> ()
forall a. NFData a => a -> ()
rnf IfaceCoercion
co
IfaceLit Literal
l -> Literal
l Literal -> () -> ()
forall a b. a -> b -> b
`seq` ()
IfaceLitRubbish TypeOrConstraint
tc IfaceType
r -> TypeOrConstraint
tc TypeOrConstraint -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
r () -> () -> ()
forall a b. a -> b -> b
`seq` ()
IfaceFCall ForeignCall
fc IfaceType
ty -> ForeignCall
fc ForeignCall -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
ty
IfaceTick IfaceTickish
tick IfaceExpr
e -> IfaceTickish -> ()
forall a. NFData a => a -> ()
rnf IfaceTickish
tick () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
e
instance NFData IfaceAlt where
rnf :: IfaceAlt -> ()
rnf (IfaceAlt IfaceConAlt
con [IfLclName]
bndrs IfaceExpr
rhs) = IfaceConAlt -> ()
forall a. NFData a => a -> ()
rnf IfaceConAlt
con () -> () -> ()
forall a b. a -> b -> b
`seq` [IfLclName] -> ()
forall a. NFData a => a -> ()
rnf [IfLclName]
bndrs () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
rhs
instance (NFData b, NFData a) => NFData (IfaceBindingX a b) where
rnf :: IfaceBindingX a b -> ()
rnf = \case
IfaceNonRec b
bndr a
e -> b -> ()
forall a. NFData a => a -> ()
rnf b
bndr () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
forall a. NFData a => a -> ()
rnf a
e
IfaceRec [(b, a)]
binds -> [(b, a)] -> ()
forall a. NFData a => a -> ()
rnf [(b, a)]
binds
instance NFData IfaceTopBndrInfo where
rnf :: IfaceTopBndrInfo -> ()
rnf (IfGblTopBndr IfExtName
n) = IfExtName
n IfExtName -> () -> ()
forall a b. a -> b -> b
`seq` ()
rnf (IfLclTopBndr IfLclName
fs IfaceType
ty IfaceIdInfo
info IfaceIdDetails
dets) = IfLclName -> ()
forall a. NFData a => a -> ()
rnf IfLclName
fs () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
ty () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceIdInfo -> ()
forall a. NFData a => a -> ()
rnf IfaceIdInfo
info () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceIdDetails -> ()
forall a. NFData a => a -> ()
rnf IfaceIdDetails
dets () -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceMaybeRhs where
rnf :: IfaceMaybeRhs -> ()
rnf IfaceMaybeRhs
IfUseUnfoldingRhs = ()
rnf (IfRhs IfaceExpr
ce) = IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
ce () -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceLetBndr where
rnf :: IfaceLetBndr -> ()
rnf (IfLetBndr IfLclName
nm IfaceType
ty IfaceIdInfo
id_info JoinPointHood
join_info) =
IfLclName -> ()
forall a. NFData a => a -> ()
rnf IfLclName
nm () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceType -> ()
forall a. NFData a => a -> ()
rnf IfaceType
ty () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceIdInfo -> ()
forall a. NFData a => a -> ()
rnf IfaceIdInfo
id_info () -> () -> ()
forall a b. a -> b -> b
`seq` JoinPointHood -> ()
forall a. NFData a => a -> ()
rnf JoinPointHood
join_info
instance NFData IfaceFamTyConFlav where
rnf :: IfaceFamTyConFlav -> ()
rnf = \case
IfaceFamTyConFlav
IfaceDataFamilyTyCon -> ()
IfaceFamTyConFlav
IfaceOpenSynFamilyTyCon -> ()
IfaceClosedSynFamilyTyCon Maybe (IfExtName, [IfaceAxBranch])
f1 -> Maybe (IfExtName, [IfaceAxBranch]) -> ()
forall a. NFData a => a -> ()
rnf Maybe (IfExtName, [IfaceAxBranch])
f1
IfaceFamTyConFlav
IfaceAbstractClosedSynFamilyTyCon -> ()
IfaceFamTyConFlav
IfaceBuiltInSynFamTyCon -> ()
instance NFData IfaceTickish where
rnf :: IfaceTickish -> ()
rnf = \case
IfaceHpcTick Module
m Int
i -> Module -> ()
forall a. NFData a => a -> ()
rnf Module
m () -> () -> ()
forall a b. a -> b -> b
`seq` Int -> ()
forall a. NFData a => a -> ()
rnf Int
i
IfaceSCC CostCentre
cc Bool
b1 Bool
b2 -> CostCentre
cc CostCentre -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
b1 () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
b2
IfaceSource RealSrcSpan
src FastString
str -> RealSrcSpan
src RealSrcSpan -> () -> ()
forall a b. a -> b -> b
`seq` FastString -> ()
forall a. NFData a => a -> ()
rnf FastString
str
IfaceBreakpoint Int
m [IfaceExpr]
i Module
fvs -> Int -> ()
forall a. NFData a => a -> ()
rnf Int
m () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceExpr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceExpr]
i () -> () -> ()
forall a b. a -> b -> b
`seq` Module -> ()
forall a. NFData a => a -> ()
rnf Module
fvs
instance NFData IfaceConAlt where
rnf :: IfaceConAlt -> ()
rnf = \case
IfaceConAlt
IfaceDefaultAlt -> ()
IfaceDataAlt IfExtName
nm -> IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
nm
IfaceLitAlt Literal
lit -> Literal
lit Literal -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceCompleteMatch where
rnf :: IfaceCompleteMatch -> ()
rnf (IfaceCompleteMatch [IfExtName]
f1 Maybe IfExtName
mtc) = [IfExtName] -> ()
forall a. NFData a => a -> ()
rnf [IfExtName]
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfExtName -> ()
forall a. NFData a => a -> ()
rnf Maybe IfExtName
mtc
instance NFData IfaceRule where
rnf :: IfaceRule -> ()
rnf (IfaceRule FastString
f1 Activation
f2 [IfaceBndr]
f3 IfExtName
f4 [IfaceExpr]
f5 IfaceExpr
f6 Bool
f7 IsOrphan
f8) =
FastString -> ()
forall a. NFData a => a -> ()
rnf FastString
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` Activation
f2 Activation -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceBndr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceBndr]
f3 () -> () -> ()
forall a b. a -> b -> b
`seq` IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f4 () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceExpr] -> ()
forall a. NFData a => a -> ()
rnf [IfaceExpr]
f5 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceExpr -> ()
forall a. NFData a => a -> ()
rnf IfaceExpr
f6 () -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
f7 () -> () -> ()
forall a b. a -> b -> b
`seq` IsOrphan
f8 IsOrphan -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceDefault where
rnf :: IfaceDefault -> ()
rnf (IfaceDefault IfaceTyCon
f1 IfaceContext
f2 Maybe IfaceWarningTxt
f3) =
IfaceTyCon -> ()
forall a. NFData a => a -> ()
rnf IfaceTyCon
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceContext -> ()
forall a. NFData a => a -> ()
rnf IfaceContext
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfaceWarningTxt -> ()
forall a. NFData a => a -> ()
rnf Maybe IfaceWarningTxt
f3
instance NFData IfaceFamInst where
rnf :: IfaceFamInst -> ()
rnf (IfaceFamInst IfExtName
f1 [Maybe IfaceTyCon]
f2 IfExtName
f3 IsOrphan
f4) =
IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` [Maybe IfaceTyCon] -> ()
forall a. NFData a => a -> ()
rnf [Maybe IfaceTyCon]
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f3 () -> () -> ()
forall a b. a -> b -> b
`seq` IsOrphan
f4 IsOrphan -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData IfaceClsInst where
rnf :: IfaceClsInst -> ()
rnf (IfaceClsInst IfExtName
f1 [Maybe IfaceTyCon]
f2 IfExtName
f3 OverlapFlag
f4 IsOrphan
f5 Maybe IfaceWarningTxt
f6) =
IfExtName
f1 IfExtName -> () -> ()
forall a b. a -> b -> b
`seq` [Maybe IfaceTyCon] -> ()
forall a. NFData a => a -> ()
rnf [Maybe IfaceTyCon]
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` IfExtName -> ()
forall a. NFData a => a -> ()
rnf IfExtName
f3 () -> () -> ()
forall a b. a -> b -> b
`seq` OverlapFlag
f4 OverlapFlag -> () -> ()
forall a b. a -> b -> b
`seq` IsOrphan
f5 IsOrphan -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfaceWarningTxt -> ()
forall a. NFData a => a -> ()
rnf Maybe IfaceWarningTxt
f6
instance NFData IfaceWarnings where
rnf :: IfaceWarnings -> ()
rnf = \case
IfWarnAll IfaceWarningTxt
txt -> IfaceWarningTxt -> ()
forall a. NFData a => a -> ()
rnf IfaceWarningTxt
txt
IfWarnSome [(OccName, IfaceWarningTxt)]
vs [(IfExtName, IfaceWarningTxt)]
ds -> [(OccName, IfaceWarningTxt)] -> ()
forall a. NFData a => a -> ()
rnf [(OccName, IfaceWarningTxt)]
vs () -> () -> ()
forall a b. a -> b -> b
`seq` [(IfExtName, IfaceWarningTxt)] -> ()
forall a. NFData a => a -> ()
rnf [(IfExtName, IfaceWarningTxt)]
ds
instance NFData IfaceWarningTxt where
rnf :: IfaceWarningTxt -> ()
rnf = \case
IfWarningTxt Maybe WarningCategory
f1 SourceText
f2 [(IfaceStringLiteral, [IfExtName])]
f3 -> Maybe WarningCategory -> ()
forall a. NFData a => a -> ()
rnf Maybe WarningCategory
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` SourceText -> ()
forall a. NFData a => a -> ()
rnf SourceText
f2 () -> () -> ()
forall a b. a -> b -> b
`seq` [(IfaceStringLiteral, [IfExtName])] -> ()
forall a. NFData a => a -> ()
rnf [(IfaceStringLiteral, [IfExtName])]
f3
IfDeprecatedTxt SourceText
f1 [(IfaceStringLiteral, [IfExtName])]
f2 -> SourceText -> ()
forall a. NFData a => a -> ()
rnf SourceText
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` [(IfaceStringLiteral, [IfExtName])] -> ()
forall a. NFData a => a -> ()
rnf [(IfaceStringLiteral, [IfExtName])]
f2
instance NFData IfaceStringLiteral where
rnf :: IfaceStringLiteral -> ()
rnf (IfStringLiteral SourceText
f1 FastString
f2) = SourceText -> ()
forall a. NFData a => a -> ()
rnf SourceText
f1 () -> () -> ()
forall a b. a -> b -> b
`seq` FastString -> ()
forall a. NFData a => a -> ()
rnf FastString
f2
instance NFData IfaceAnnotation where
rnf :: IfaceAnnotation -> ()
rnf (IfaceAnnotation IfaceAnnTarget
f1 AnnPayload
f2) = IfaceAnnTarget
f1 IfaceAnnTarget -> () -> ()
forall a b. a -> b -> b
`seq` AnnPayload
f2 AnnPayload -> () -> ()
forall a b. a -> b -> b
`seq` ()