ghc-9.11: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Utils.Binary

Synopsis

Documentation

data Bin (a :: k) Source #

Instances

Instances details
Binary (Bin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> Bin a -> IO () Source #

put :: WriteBinHandle -> Bin a -> IO (Bin (Bin a)) Source #

get :: ReadBinHandle -> IO (Bin a) Source #

Bounded (Bin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

minBound :: Bin a #

maxBound :: Bin a #

Show (Bin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

showsPrec :: Int -> Bin a -> ShowS #

show :: Bin a -> String #

showList :: [Bin a] -> ShowS #

Eq (Bin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

(==) :: Bin a -> Bin a -> Bool #

(/=) :: Bin a -> Bin a -> Bool #

Ord (Bin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

compare :: Bin a -> Bin a -> Ordering #

(<) :: Bin a -> Bin a -> Bool #

(<=) :: Bin a -> Bin a -> Bool #

(>) :: Bin a -> Bin a -> Bool #

(>=) :: Bin a -> Bin a -> Bool #

max :: Bin a -> Bin a -> Bin a #

min :: Bin a -> Bin a -> Bin a #

data RelBin (a :: k) Source #

Like a Bin but is used to store relative offset pointers. Relative offset pointers store a relative location, but also contain an anchor that allow to obtain the absolute offset.

Constructors

RelBin 

Fields

Instances

Instances details
Bounded (RelBin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

minBound :: RelBin a #

maxBound :: RelBin a #

Show (RelBin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

showsPrec :: Int -> RelBin a -> ShowS #

show :: RelBin a -> String #

showList :: [RelBin a] -> ShowS #

Eq (RelBin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

(==) :: RelBin a -> RelBin a -> Bool #

(/=) :: RelBin a -> RelBin a -> Bool #

Ord (RelBin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

compare :: RelBin a -> RelBin a -> Ordering #

(<) :: RelBin a -> RelBin a -> Bool #

(<=) :: RelBin a -> RelBin a -> Bool #

(>) :: RelBin a -> RelBin a -> Bool #

(>=) :: RelBin a -> RelBin a -> Bool #

max :: RelBin a -> RelBin a -> RelBin a #

min :: RelBin a -> RelBin a -> RelBin a #

getRelBin :: forall {k} (a :: k). ReadBinHandle -> IO (RelBin a) Source #

Read a relative offset location and wrap it in RelBin.

The resulting RelBin can be translated into an absolute offset location using makeAbsoluteBin

class Binary a where Source #

Do not rely on instance sizes for general types, we use variable length encoding for many of them.

Minimal complete definition

get

Methods

put_ :: WriteBinHandle -> a -> IO () Source #

put :: WriteBinHandle -> a -> IO (Bin a) Source #

get :: ReadBinHandle -> IO a Source #

Instances

Instances details
Binary ByteString Source # 
Instance details

Defined in GHC.Utils.Binary

Binary IsOrphan Source # 
Instance details

Defined in GHC.Core

Binary StrictnessMark Source # 
Instance details

Defined in GHC.Core.DataCon

Binary CallerCcFilter Source # 
Instance details

Defined in GHC.Core.Opt.CallerCC.Types

Binary NamePattern Source # 
Instance details

Defined in GHC.Core.Opt.CallerCC.Types

Binary CoSel Source # 
Instance details

Defined in GHC.Core.TyCo.Rep

Binary Injectivity Source # 
Instance details

Defined in GHC.Core.TyCon

Binary PrimElemRep Source # 
Instance details

Defined in GHC.Core.TyCon

Binary PrimRep Source # 
Instance details

Defined in GHC.Core.TyCon

Binary TyConBndrVis Source # 
Instance details

Defined in GHC.Core.TyCon

Binary FastString Source # 
Instance details

Defined in GHC.Utils.Binary

Binary LexicalFastString Source # 
Instance details

Defined in GHC.Utils.Binary

Binary NonDetFastString Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Language Source # 
Instance details

Defined in GHC.Driver.Flags

Binary DocStructureItem Source # 
Instance details

Defined in GHC.Hs.Doc

Binary Docs Source # 
Instance details

Defined in GHC.Hs.Doc

Binary HsDocString Source # 
Instance details

Defined in GHC.Hs.DocString

Binary HsDocStringChunk Source # 
Instance details

Defined in GHC.Hs.DocString

Binary HsDocStringDecorator Source # 
Instance details

Defined in GHC.Hs.DocString

Binary ExtensibleFields Source # 
Instance details

Defined in GHC.Iface.Ext.Fields

Binary BindType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary ContextInfo Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary DeclType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary EvBindDeps Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary EvVarSource Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary HieFile Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary IEType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary NodeAnnotation Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary NodeOrigin Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary RecFieldContext Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary Scope Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary TyVarScope Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary IfGuidance Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceAT Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceAlt Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceAnnotation Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceAxBranch Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceBang Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceBooleanFormula Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceClassOp Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceClsInst Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceCompleteMatch Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceConAlt Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceConDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceConDecls Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceDefault Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceExpr Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceFamInst Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceFamTyConFlav Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceIdDetails Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceInfoItem Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceLFInfo Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceLetBndr Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceMaybeRhs Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceRule Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceSrcBang Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceStringLiteral Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceTickish Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceTopBndrInfo Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceTyConParent Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceUnfolding Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceWarningTxt Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfaceWarnings Source # 
Instance details

Defined in GHC.Iface.Syntax

Binary IfLclName Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceAppArgs Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceBndr Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceCoercion Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceMCoercion Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceOneShot Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceTyCon Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceTyConInfo Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceTyConSort Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceTyLit Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceType Source # 
Instance details

Defined in GHC.Iface.Type

Binary IfaceUnivCoProv Source # 
Instance details

Defined in GHC.Iface.Type

Binary Ident Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary AOp Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary JExpr Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary JStat Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary JVal Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary Op Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary UOp Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary TagInfo Source # 
Instance details

Defined in GHC.Stg.InferTags.TagSig

Binary TagSig Source # 
Instance details

Defined in GHC.Stg.InferTags.TagSig

Binary BlockDeps Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary BlockInfo Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary ExportedFun Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary IndexEntry Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary JSOptions Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary CILayout Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary CIRegs Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary CIStatic Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary CIType Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary ClosureInfo Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary ExpFun Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary ForeignJSRef Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary JSFFIType Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary JSRep Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary StaticArg Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary StaticInfo Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary StaticLit Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary StaticUnboxed Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary StaticVal Source # 
Instance details

Defined in GHC.StgToJS.Object

Binary AvailInfo Source # 
Instance details

Defined in GHC.Types.Avail

Binary Activation Source # 
Instance details

Defined in GHC.Types.Basic

Binary CbvMark Source # 
Instance details

Defined in GHC.Types.Basic

Binary FunctionOrData Source # 
Instance details

Defined in GHC.Types.Basic

Binary InlinePragma Source # 
Instance details

Defined in GHC.Types.Basic

Binary InlineSpec Source # 
Instance details

Defined in GHC.Types.Basic

Binary LeftOrRight Source # 
Instance details

Defined in GHC.Types.Basic

Binary Levity Source # 
Instance details

Defined in GHC.Types.Basic

Binary OverlapFlag Source # 
Instance details

Defined in GHC.Types.Basic

Binary OverlapMode Source # 
Instance details

Defined in GHC.Types.Basic

Binary RecFlag Source # 
Instance details

Defined in GHC.Types.Basic

Binary RuleMatchInfo Source # 
Instance details

Defined in GHC.Types.Basic

Binary TupleSort Source # 
Instance details

Defined in GHC.Types.Basic

Binary UnfoldingSource Source # 
Instance details

Defined in GHC.Types.Basic

Binary CCFlavour Source # 
Instance details

Defined in GHC.Types.CostCentre

Binary CostCentre Source # 
Instance details

Defined in GHC.Types.CostCentre

Binary CostCentreIndex Source # 
Instance details

Defined in GHC.Types.CostCentre.State

Binary Cpr Source # 
Instance details

Defined in GHC.Types.Cpr

Binary CprSig Source # 
Instance details

Defined in GHC.Types.Cpr

Binary CprType Source # 
Instance details

Defined in GHC.Types.Cpr

Binary Card Source # 
Instance details

Defined in GHC.Types.Demand

Binary Demand Source # 
Instance details

Defined in GHC.Types.Demand

Binary Divergence Source # 
Instance details

Defined in GHC.Types.Demand

Binary DmdEnv Source # 
Instance details

Defined in GHC.Types.Demand

Binary DmdSig Source # 
Instance details

Defined in GHC.Types.Demand

Binary DmdType Source # 
Instance details

Defined in GHC.Types.Demand

Binary SubDemand Source # 
Instance details

Defined in GHC.Types.Demand

Binary DuplicateRecordFields Source # 
Instance details

Defined in GHC.Types.FieldLabel

Binary Name => Binary FieldLabel Source #

We need the Binary Name constraint here even though there is an instance defined in GHC.Types.Name, because the we have a SOURCE import, so the instance is not in scope. And the instance cannot be added to Name.hs-boot because GHC.Utils.Binary itself depends on GHC.Types.Name.

Instance details

Defined in GHC.Types.FieldLabel

Binary FieldSelectors Source # 
Instance details

Defined in GHC.Types.FieldLabel

Binary CCallConv Source # 
Instance details

Defined in GHC.Types.ForeignCall

Binary CCallSpec Source # 
Instance details

Defined in GHC.Types.ForeignCall

Binary CCallTarget Source # 
Instance details

Defined in GHC.Types.ForeignCall

Binary CExportSpec Source # 
Instance details

Defined in GHC.Types.ForeignCall

Binary CType Source # 
Instance details

Defined in GHC.Types.ForeignCall

Binary ForeignCall Source # 
Instance details

Defined in GHC.Types.ForeignCall

Binary Header Source # 
Instance details

Defined in GHC.Types.ForeignCall

Binary Safety Source # 
Instance details

Defined in GHC.Types.ForeignCall

Binary LitNumType Source # 
Instance details

Defined in GHC.Types.Literal

Binary Literal Source # 
Instance details

Defined in GHC.Types.Literal

Binary Name Source #

Assumes that the Name is a non-binding one. See putIfaceTopBndr and getIfaceTopBndr for serializing binding Names. See UserData for the rationale for this distinction.

Instance details

Defined in GHC.Types.Name

Binary NameSpace Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Binary OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Binary IfaceTrustInfo Source # 
Instance details

Defined in GHC.Types.SafeHaskell

Binary SaneDouble Source # 
Instance details

Defined in GHC.Types.SaneDouble

Binary HscSource Source # 
Instance details

Defined in GHC.Types.SourceFile

Binary SourceText Source # 
Instance details

Defined in GHC.Types.SourceText

Binary UnhelpfulSpanReason Source # 
Instance details

Defined in GHC.Utils.Binary

Binary FunTyFlag Source # 
Instance details

Defined in GHC.Types.Var

Binary Dependencies Source # 
Instance details

Defined in GHC.Unit.Module.Deps

Binary Usage Source # 
Instance details

Defined in GHC.Unit.Module.Deps

Binary ModIface Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

Binary WarningCategory Source # 
Instance details

Defined in GHC.Unit.Module.Warnings

Binary IfaceCLabel Source # 
Instance details

Defined in GHC.Unit.Module.WholeCoreBindings

Binary IfaceCStubs Source # 
Instance details

Defined in GHC.Unit.Module.WholeCoreBindings

Binary IfaceForeign Source # 
Instance details

Defined in GHC.Unit.Module.WholeCoreBindings

Binary IfaceForeignFile Source # 
Instance details

Defined in GHC.Unit.Module.WholeCoreBindings

Binary InstantiatedUnit Source # 
Instance details

Defined in GHC.Unit.Types

Binary Unit Source # 
Instance details

Defined in GHC.Unit.Types

Binary UnitId Source # 
Instance details

Defined in GHC.Unit.Types

Binary BinData Source # 
Instance details

Defined in GHC.Utils.Binary

Binary BinSpan Source # 
Instance details

Defined in GHC.Utils.Binary

Binary BinSrcSpan Source # 
Instance details

Defined in GHC.Utils.Binary

Binary JoinPointHood Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Boxity Source # 
Instance details

Defined in GHC.Types.Basic

Binary Fixity Source # 
Instance details

Defined in GHC.Hs.Basic

Binary FixityDirection Source # 
Instance details

Defined in GHC.Hs.Basic

Binary Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Binary SrcStrictness Source # 
Instance details

Defined in GHC.Core.DataCon

Binary SrcUnpackedness Source # 
Instance details

Defined in GHC.Core.DataCon

Binary IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Binary ModuleName Source # 
Instance details

Defined in GHC.Utils.Binary

Binary ForAllTyFlag Source # 
Instance details

Defined in GHC.Hs.Specificity

Binary Specificity Source # 
Instance details

Defined in GHC.Hs.Specificity

Binary PromotionFlag Source # 
Instance details

Defined in GHC.Types.Basic

Binary Serialized Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

Binary SomeTypeRep Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

Binary Fingerprint Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Int16 Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Int32 Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Int64 Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Int8 Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Word16 Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Word32 Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Word64 Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Word8 Source # 
Instance details

Defined in GHC.Utils.Binary

Binary KindRep Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

Binary TyCon Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

Binary TypeLitSort Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

Binary Day Source # 
Instance details

Defined in GHC.Utils.Binary

Binary DiffTime Source # 
Instance details

Defined in GHC.Utils.Binary

Binary UTCTime Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Integer Source # 
Instance details

Defined in GHC.Utils.Binary

Binary () Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> () -> IO () Source #

put :: WriteBinHandle -> () -> IO (Bin ()) Source #

get :: ReadBinHandle -> IO () Source #

Binary Bool Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Char Source # 
Instance details

Defined in GHC.Utils.Binary

Binary Int Source # 
Instance details

Defined in GHC.Utils.Binary

Binary RuntimeRep Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

Binary VecCount Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

Binary VecElem Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

Binary v => Binary (IntMap v) Source # 
Instance details

Defined in GHC.Utils.Binary

(Binary a, Ord a) => Binary (Set a) Source #

This instance doesn't rely on the determinism of the keys' Ord instance, so it works e.g. for Names too.

Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> Set a -> IO () Source #

put :: WriteBinHandle -> Set a -> IO (Bin (Set a)) Source #

get :: ReadBinHandle -> IO (Set a) Source #

Binary a => Binary (Maybe a) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary (HieAST TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary (HieASTs TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary (HieArgs TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary (HieType TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary (IdentifierDetails TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary (NodeInfo TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary (SourcedNodeInfo TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary name => Binary (AnnTarget name) Source # 
Instance details

Defined in GHC.Types.Annotations

Binary (DefMethSpec IfaceType) Source # 
Instance details

Defined in GHC.Iface.Type

Binary unit => Binary (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: WriteBinHandle -> Definite unit -> IO () Source #

put :: WriteBinHandle -> Definite unit -> IO (Bin (Definite unit)) Source #

get :: ReadBinHandle -> IO (Definite unit) Source #

Binary a => Binary (GenModule a) Source # 
Instance details

Defined in GHC.Unit.Types

Binary a => Binary (GenWithIsBoot a) Source # 
Instance details

Defined in GHC.Unit.Types

Binary a => Binary (BinLocated a) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary (FixedLengthEncoding Word16) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary (FixedLengthEncoding Word32) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary (FixedLengthEncoding Word64) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary (FixedLengthEncoding Word8) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary a => Binary (NonEmpty a) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary a => Binary (Ratio a) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary a => Binary (Maybe a) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary a => Binary [a] Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> [a] -> IO () Source #

put :: WriteBinHandle -> [a] -> IO (Bin [a]) Source #

get :: ReadBinHandle -> IO [a] Source #

Binary (EnumSet a) Source #

Represents the EnumSet as a bit set.

Assumes that all elements are non-negative.

This is only efficient for values that are sufficiently small, for example in the lower hundreds.

Instance details

Defined in GHC.Data.EnumSet

Binary a => Binary (WithHsDocIdentifiers a GhcRn) Source # 
Instance details

Defined in GHC.Hs.Doc

(Binary r, Binary b) => Binary (IfaceBindingX b r) Source # 
Instance details

Defined in GHC.Iface.Syntax

(Binary tv, Binary vis) => Binary (VarBndr tv vis) Source # 
Instance details

Defined in GHC.Types.Var

Methods

put_ :: WriteBinHandle -> VarBndr tv vis -> IO () Source #

put :: WriteBinHandle -> VarBndr tv vis -> IO (Bin (VarBndr tv vis)) Source #

get :: ReadBinHandle -> IO (VarBndr tv vis) Source #

Binary (Bin a) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> Bin a -> IO () Source #

put :: WriteBinHandle -> Bin a -> IO (Bin (Bin a)) Source #

get :: ReadBinHandle -> IO (Bin a) Source #

(Ix a, Binary a, Binary b) => Binary (Array a b) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> Array a b -> IO () Source #

put :: WriteBinHandle -> Array a b -> IO (Bin (Array a b)) Source #

get :: ReadBinHandle -> IO (Array a b) Source #

(Binary a, Binary b) => Binary (Either a b) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> Either a b -> IO () Source #

put :: WriteBinHandle -> Either a b -> IO (Bin (Either a b)) Source #

get :: ReadBinHandle -> IO (Either a b) Source #

Typeable a => Binary (TypeRep a) Source # 
Instance details

Defined in GHC.Utils.Binary.Typeable

(Binary a, Binary b) => Binary (a, b) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> (a, b) -> IO () Source #

put :: WriteBinHandle -> (a, b) -> IO (Bin (a, b)) Source #

get :: ReadBinHandle -> IO (a, b) Source #

(Binary a, Binary b, Binary c) => Binary (a, b, c) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> (a, b, c) -> IO () Source #

put :: WriteBinHandle -> (a, b, c) -> IO (Bin (a, b, c)) Source #

get :: ReadBinHandle -> IO (a, b, c) Source #

(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> (a, b, c, d) -> IO () Source #

put :: WriteBinHandle -> (a, b, c, d) -> IO (Bin (a, b, c, d)) Source #

get :: ReadBinHandle -> IO (a, b, c, d) Source #

(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> (a, b, c, d, e) -> IO () Source #

put :: WriteBinHandle -> (a, b, c, d, e) -> IO (Bin (a, b, c, d, e)) Source #

get :: ReadBinHandle -> IO (a, b, c, d, e) Source #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a, b, c, d, e, f) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> (a, b, c, d, e, f) -> IO () Source #

put :: WriteBinHandle -> (a, b, c, d, e, f) -> IO (Bin (a, b, c, d, e, f)) Source #

get :: ReadBinHandle -> IO (a, b, c, d, e, f) Source #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a, b, c, d, e, f, g) Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

put_ :: WriteBinHandle -> (a, b, c, d, e, f, g) -> IO () Source #

put :: WriteBinHandle -> (a, b, c, d, e, f, g) -> IO (Bin (a, b, c, d, e, f, g)) Source #

get :: ReadBinHandle -> IO (a, b, c, d, e, f, g) Source #

data ReadBinHandle Source #

A read-only handle that can be used to deserialise binary data from a buffer.

The buffer is an unboxed binary array.

data WriteBinHandle Source #

A write-only handle that can be used to serialise binary data into a buffer.

The buffer is an unboxed binary array.

type SymbolTable a = Array Int a Source #

Symbols that are read from disk. The SymbolTable index starts on '0'.

data BinData Source #

Constructors

BinData Int BinArray 

Instances

Instances details
NFData BinData Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

rnf :: BinData -> () Source #

Binary BinData Source # 
Instance details

Defined in GHC.Utils.Binary

seekBinWriter :: forall {k} (a :: k). WriteBinHandle -> Bin a -> IO () Source #

seekBinReader :: forall {k} (a :: k). ReadBinHandle -> Bin a -> IO () Source #

SeekBin but without calling expandBin

seekBinReaderRel :: forall {k} (a :: k). ReadBinHandle -> RelBin a -> IO () Source #

tellBinReader :: forall {k} (a :: k). ReadBinHandle -> IO (Bin a) Source #

tellBinWriter :: forall {k} (a :: k). WriteBinHandle -> IO (Bin a) Source #

castBin :: forall {k1} {k2} (a :: k1) (b :: k2). Bin a -> Bin b Source #

withBinBuffer :: WriteBinHandle -> (ByteString -> IO a) -> IO a Source #

Get access to the underlying buffer.

freezeWriteHandle :: WriteBinHandle -> IO ReadBinHandle Source #

Freeze the given WriteBinHandle and turn it into an equivalent ReadBinHandle.

The current offset of the WriteBinHandle is maintained in the new ReadBinHandle.

shrinkBinBuffer :: WriteBinHandle -> IO ReadBinHandle Source #

Copy the BinBuffer to a new BinBuffer which is exactly the right size. This performs a copy of the underlying buffer. The buffer may be truncated if the offset is not at the end of the written output.

UserData is also discarded during the copy You should just use this when translating a Put handle into a Get handle.

foldGet :: Binary a => Word -> ReadBinHandle -> b -> (Word -> a -> b -> IO b) -> IO b Source #

foldGet' :: Binary a => Word -> ReadBinHandle -> b -> (Word -> a -> b -> IO b) -> IO b Source #

putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO () Source #

getAt :: Binary a => ReadBinHandle -> Bin a -> IO a Source #

putAtRel :: forall {k} (a :: k). WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO () Source #

forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a, b) Source #

forwardPut put_A put_B outputs A after B but allows A to be read before B by using a forward reference.

forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () Source #

forwardGet :: ReadBinHandle -> IO a -> IO a Source #

Read a value stored using a forward reference

The forward reference is expected to be an absolute offset.

forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a, b) Source #

forwardPutRel put_A put_B outputs A after B but allows A to be read before B by using a forward reference.

This forward reference is a relative offset that allows us to skip over the result of put_A.

forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () Source #

Like forwardGetRel, but discard the result.

forwardGetRel :: ReadBinHandle -> IO a -> IO a Source #

Read a value stored using a forward reference.

The forward reference is expected to be a relative offset.

For writing instances

putByteString :: WriteBinHandle -> ByteString -> IO () Source #

Put a ByteString without its length (can't be read back without knowing the length!)

getByteString :: ReadBinHandle -> Int -> IO ByteString Source #

Get a ByteString whose length is known

Variable length encodings

putSLEB128 :: (Integral a, Bits a) => WriteBinHandle -> a -> IO () Source #

Fixed length encoding

newtype FixedLengthEncoding a Source #

Encode the argument in its full length. This is different from many default binary instances which make no guarantee about the actual encoding and might do things using variable length encoding.

Constructors

FixedLengthEncoding 

Fields

Instances

Instances details
Binary (FixedLengthEncoding Word16) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary (FixedLengthEncoding Word32) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary (FixedLengthEncoding Word64) Source # 
Instance details

Defined in GHC.Utils.Binary

Binary (FixedLengthEncoding Word8) Source # 
Instance details

Defined in GHC.Utils.Binary

Show a => Show (FixedLengthEncoding a) Source # 
Instance details

Defined in GHC.Utils.Binary

Eq a => Eq (FixedLengthEncoding a) Source # 
Instance details

Defined in GHC.Utils.Binary

Ord a => Ord (FixedLengthEncoding a) Source # 
Instance details

Defined in GHC.Utils.Binary

Lazy Binary I/O

lazyPut :: Binary a => WriteBinHandle -> a -> IO () Source #

lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () Source #

lazyGetMaybe :: Binary a => ReadBinHandle -> IO (Maybe a) Source #

Deserialize a value serialized by lazyPutMaybe.

lazyPutMaybe :: Binary a => WriteBinHandle -> Maybe a -> IO () Source #

Serialize the constructor strictly but lazily serialize a value inside a Just.

This way we can check for the presence of a value without deserializing the value itself.

User data

data ReaderUserData Source #

UserData required to deserialise symbols for interface files.

See Note [Binary UserData]

data WriterUserData Source #

UserData required to serialise symbols for interface files.

See Note [Binary UserData]

newReadState Source #

Arguments

:: (ReadBinHandle -> IO Name)

how to deserialize Names

-> (ReadBinHandle -> IO FastString) 
-> ReaderUserData 

newWriteState Source #

Arguments

:: (WriteBinHandle -> Name -> IO ())

how to serialize non-binding Names

-> (WriteBinHandle -> Name -> IO ())

how to serialize binding Names

-> (WriteBinHandle -> FastString -> IO ()) 
-> WriterUserData 

addReaderToUserData :: Typeable a => BinaryReader a -> ReadBinHandle -> ReadBinHandle Source #

Add SomeBinaryReader as a known binary decoder. If a BinaryReader for the associated type already exists in ReaderUserData, it is overwritten.

addWriterToUserData :: Typeable a => BinaryWriter a -> WriteBinHandle -> WriteBinHandle Source #

Add SomeBinaryWriter as a known binary encoder. If a BinaryWriter for the associated type already exists in WriterUserData, it is overwritten.

findUserDataReader :: Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a Source #

Find the BinaryReader for the Binary instance for the type identified by 'Proxy a'.

If no BinaryReader has been configured before, this function will panic.

findUserDataWriter :: Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a Source #

Find the BinaryWriter for the Binary instance for the type identified by 'Proxy a'.

If no BinaryWriter has been configured before, this function will panic.

Binary Readers & Writers

newtype BinaryReader s Source #

Constructors

BinaryReader 

Fields

Instances

Instances details
Functor BinaryReader Source # 
Instance details

Defined in GHC.Utils.Binary

Methods

fmap :: (a -> b) -> BinaryReader a -> BinaryReader b #

(<$) :: a -> BinaryReader b -> BinaryReader a #

newtype BinaryWriter s Source #

Constructors

BinaryWriter 

Fields

data SomeBinaryReader Source #

Existential for BinaryReader with a type witness.

data SomeBinaryWriter Source #

Existential for BinaryWriter with a type witness.

Tables

data ReaderTable a Source #

A ReaderTable describes how to deserialise a table from disk, and how to create a BinaryReader that looks up values in the deduplication table.

Constructors

ReaderTable 

Fields

newtype WriterTable Source #

A WriterTable is an interface any deduplication table can implement to describe how the table can be written to disk.

Constructors

WriterTable 

Fields

String table ("dictionary")

Generic deduplication table

data GenericSymbolTable (m :: Type -> Type) Source #

The GenericSymbolTable stores a mapping from already seen elements to an index. If an element wasn't seen before, it is added to the mapping together with a fresh index.

GenericSymbolTable is a variant of a BinSymbolTable that is polymorphic in the table implementation. As such it can be used with any container that implements the TrieMap type class.

While GenericSymbolTable is similar to the BinSymbolTable, it supports storing tree-like structures such as Type and IfaceType more efficiently.

Constructors

GenericSymbolTable 

Fields

  • gen_symtab_next :: !FastMutInt

    The next index to use.

  • gen_symtab_map :: !(IORef (m Int))

    Given a symbol, find the symbol and return its index.

  • gen_symtab_to_write :: !(IORef [Key m])

    Reversed list of values to write into the buffer. This is an optimisation, as it allows us to write out quickly all newly discovered values that are discovered when serialising 'Key m' to disk.

initGenericSymbolTable :: forall (m :: Type -> Type). TrieMap m => IO (GenericSymbolTable m) Source #

Initialise a GenericSymbolTable, initialising the index to '0'.

getGenericSymtab :: Binary a => SymbolTable a -> ReadBinHandle -> IO a Source #

Read a value from a SymbolTable.

putGenericSymTab :: forall (m :: Type -> Type). TrieMap m => GenericSymbolTable m -> WriteBinHandle -> Key m -> IO () Source #

Write an element 'Key m' to the given WriteBinHandle.

If the element was seen before, we simply write the index of that element to the WriteBinHandle. If we haven't seen it before, we add the element to the GenericSymbolTable, increment the index, and return this new index.

getGenericSymbolTable :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) Source #

Read the elements of a GenericSymbolTable from disk into a SymbolTable.

putGenericSymbolTable :: forall (m :: Type -> Type). TrieMap m => GenericSymbolTable m -> (WriteBinHandle -> Key m -> IO ()) -> WriteBinHandle -> IO Int Source #

Serialise the GenericSymbolTable to disk.

Since GenericSymbolTable stores tree-like structures, such as IfaceType, serialising an element can add new elements to the mapping. Thus, putGenericSymbolTable first serialises all values, and then checks whether any new elements have been discovered. If so, repeat the loop.

Newtype wrappers

newtype BinSpan Source #

Constructors

BinSpan 

Instances

Instances details
Binary BinSpan Source # 
Instance details

Defined in GHC.Utils.Binary

newtype BinSrcSpan Source #

Constructors

BinSrcSpan 

Instances

Instances details
Binary BinSrcSpan Source # 
Instance details

Defined in GHC.Utils.Binary

newtype BinLocated a Source #

Constructors

BinLocated 

Fields

Instances

Instances details
Binary a => Binary (BinLocated a) Source # 
Instance details

Defined in GHC.Utils.Binary

Newtypes for types that have canonically more than one valid encoding

newtype BindingName Source #

Newtype to serialise binding names differently to non-binding Name. See Note [Binary UserData]

Constructors

BindingName 

Fields

Instances

Instances details
Eq BindingName Source # 
Instance details

Defined in GHC.Utils.Binary

data FullBinData Source #

FullBinData stores a slice to a BinArray.

It requires less memory than ReadBinHandle, and can be constructed from a ReadBinHandle via freezeBinHandle and turned back into a ReadBinHandle using thawBinHandle. Additionally, the byte array slice can be put into a WriteBinHandle without extra conversions via putFullBinData.

Constructors

FullBinData 

Fields

freezeBinHandle :: forall {k} (a :: k). ReadBinHandle -> Bin a -> IO FullBinData Source #

Freeze a ReadBinHandle and a start index into a FullBinData.

FullBinData stores a slice starting from the 'Bin a' location to the current offset of the ReadBinHandle.

thawBinHandle :: FullBinData -> IO ReadBinHandle Source #

Turn the FullBinData into a ReadBinHandle, setting the ReadBinHandle offset to the start of the FullBinData and restore the ReaderUserData that was obtained from freezeBinHandle.