ghc-8.2.1: The GHC API

Safe HaskellNone
LanguageHaskell2010

Binary

Contents

Synopsis

Documentation

data Bin a Source #

Instances

Bounded (Bin k a) Source # 

Methods

minBound :: Bin k a #

maxBound :: Bin k a #

Eq (Bin k a) Source # 

Methods

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

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

Ord (Bin k a) Source # 

Methods

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

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

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

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

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

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

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

Show (Bin k a) Source # 

Methods

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

show :: Bin k a -> String #

showList :: [Bin k a] -> ShowS #

Binary (Bin k a) Source # 

Methods

put_ :: BinHandle -> Bin k a -> IO () Source #

put :: BinHandle -> Bin k a -> IO (Bin * (Bin k a)) Source #

get :: BinHandle -> IO (Bin k a) Source #

class Binary a where Source #

Minimal complete definition

get

Methods

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

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

get :: BinHandle -> IO a Source #

Instances

Binary Bool Source # 
Binary Char Source # 
Binary Int Source # 

Methods

put_ :: BinHandle -> Int -> IO () Source #

put :: BinHandle -> Int -> IO (Bin * Int) Source #

get :: BinHandle -> IO Int Source #

Binary Int8 Source # 
Binary Int16 Source # 
Binary Int32 Source # 
Binary Int64 Source # 
Binary Integer Source # 
Binary Word8 Source # 
Binary Word16 Source # 
Binary Word32 Source # 
Binary Word64 Source # 
Binary RuntimeRep Source # 
Binary VecCount Source # 
Binary VecElem Source # 
Binary SomeTypeRep Source # 
Binary () Source # 

Methods

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

put :: BinHandle -> () -> IO (Bin * ()) Source #

get :: BinHandle -> IO () Source #

Binary TyCon Source # 
Binary KindRep Source # 
Binary TypeLitSort Source # 
Binary Fingerprint Source # 
Binary ByteString Source # 
Binary Serialized Source # 
Binary UTCTime Source # 
Binary DiffTime Source # 
Binary Day Source # 

Methods

put_ :: BinHandle -> Day -> IO () Source #

put :: BinHandle -> Day -> IO (Bin * Day) Source #

get :: BinHandle -> IO Day Source #

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.

Binary OccName Source # 
Binary FastString Source # 
Binary ComponentId Source # 
Binary InstalledUnitId Source # 
Binary UnitId Source # 
Binary ModuleName Source # 
Binary Module Source # 
Binary SrcSpan Source # 
Binary InlineSpec Source # 
Binary InlinePragma Source # 
Binary RuleMatchInfo Source # 
Binary Activation Source # 
Binary SourceText Source # 
Binary TupleSort Source # 
Binary OverlapMode Source # 
Binary OverlapFlag Source # 
Binary RecFlag Source # 
Binary FixityDirection Source # 
Binary Fixity Source # 
Binary WarningTxt Source # 
Binary StringLiteral Source # 
Binary FunctionOrData Source # 
Binary LeftOrRight Source # 
Binary DefUnitId Source # 
Binary IndefUnitId Source # 
Binary CType Source # 
Binary Header Source # 
Binary CCallConv Source # 
Binary CCallTarget Source # 
Binary CCallSpec Source # 
Binary CExportSpec Source # 
Binary Safety Source # 
Binary ForeignCall Source # 
Binary HscSource Source # 
Binary NameSpace Source # 
Binary AvailInfo Source # 
Binary ArgFlag Source # 
Binary IsCafCC Source # 
Binary CostCentre Source # 
Binary Role Source # 
Binary Injectivity Source # 
Binary TyConBndrVis Source # 
Binary IfaceTcArgs Source # 
Binary IfaceCoercion Source # 
Binary IfaceTyLit Source # 
Binary IfaceTyCon Source # 
Binary IfaceType Source # 
Binary IfaceUnivCoProv Source # 
Binary IfaceTyConInfo Source # 
Binary IfaceTyConSort Source # 
Binary IsPromoted Source # 
Binary IfaceOneShot Source # 
Binary IfaceBndr Source # 
Binary Literal Source # 
Binary SrcUnpackedness Source # 
Binary SrcStrictness Source # 
Binary StrictSig Source # 
Binary DmdType Source # 
Binary CPRResult Source # 
Binary DmdResult Source # 
Binary Count Source # 
Binary UseDmd Source # 
Binary StrDmd Source # 
Binary IsOrphan Source # 
Binary IfaceJoinInfo Source # 
Binary IfaceLetBndr Source # 
Binary IfaceBinding Source # 
Binary IfaceConAlt Source # 
Binary IfaceTickish Source # 
Binary IfaceExpr Source # 
Binary IfaceIdDetails Source # 
Binary IfaceUnfolding Source # 
Binary IfaceInfoItem Source # 
Binary IfaceIdInfo Source # 
Binary IfaceCompleteMatch Source # 
Binary IfaceAnnotation Source # 
Binary IfaceRule Source # 
Binary IfaceFamInst Source # 
Binary IfaceClsInst Source # 
Binary IfaceSrcBang Source # 
Binary IfaceBang Source # 
Binary IfaceConDecl Source # 
Binary IfaceConDecls Source # 
Binary IfaceAxBranch Source # 
Binary IfaceAT Source # 
Binary IfaceClassOp Source # 
Binary IfaceFamTyConFlav Source # 
Binary IfaceTyConParent Source # 
Binary IfaceDecl Source # 
Binary IfaceTrustInfo Source # 
Binary IfaceVectInfo Source # 
Binary Usage Source # 
Binary Dependencies Source # 
Binary Warnings Source # 
Binary ModIface Source # 
Binary a => Binary [a] Source # 

Methods

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

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

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

Binary a => Binary (Maybe a) Source # 

Methods

put_ :: BinHandle -> Maybe a -> IO () Source #

put :: BinHandle -> Maybe a -> IO (Bin * (Maybe a)) Source #

get :: BinHandle -> IO (Maybe a) Source #

Binary a => Binary (Ratio a) Source # 

Methods

put_ :: BinHandle -> Ratio a -> IO () Source #

put :: BinHandle -> Ratio a -> IO (Bin * (Ratio a)) Source #

get :: BinHandle -> IO (Ratio a) Source #

Binary (DefMethSpec IfaceType) Source # 
Binary a => Binary (BooleanFormula a) Source # 
Binary a => Binary (FieldLbl a) Source # 
Binary name => Binary (AnnTarget name) Source # 

Methods

put_ :: BinHandle -> AnnTarget name -> IO () Source #

put :: BinHandle -> AnnTarget name -> IO (Bin * (AnnTarget name)) Source #

get :: BinHandle -> IO (AnnTarget name) Source #

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

Methods

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

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

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

Typeable k a => Binary (TypeRep k a) Source # 

Methods

put_ :: BinHandle -> TypeRep k a -> IO () Source #

put :: BinHandle -> TypeRep k a -> IO (Bin * (TypeRep k a)) Source #

get :: BinHandle -> IO (TypeRep k a) Source #

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

Methods

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

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

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

Binary a => Binary (GenLocated SrcSpan a) Source # 
Binary (Bin k a) Source # 

Methods

put_ :: BinHandle -> Bin k a -> IO () Source #

put :: BinHandle -> Bin k a -> IO (Bin * (Bin k a)) Source #

get :: BinHandle -> IO (Bin k a) Source #

(Binary tv, Binary vis) => Binary (TyVarBndr tv vis) Source # 

Methods

put_ :: BinHandle -> TyVarBndr tv vis -> IO () Source #

put :: BinHandle -> TyVarBndr tv vis -> IO (Bin * (TyVarBndr tv vis)) Source #

get :: BinHandle -> IO (TyVarBndr tv vis) Source #

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

get :: BinHandle -> 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 # 

Methods

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

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

get :: BinHandle -> 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 # 

Methods

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

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

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

seekBin :: BinHandle -> Bin a -> IO () Source #

castBin :: Bin a -> Bin b Source #

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

Get access to the underlying buffer.

It is quite important that no references to the ByteString leak out of the continuation lest terrible things happen.

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

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

For writing instances

Lazy Binary I/O

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

User data

data UserData Source #

Information we keep around during interface file serialization/deserialization. Namely we keep the functions for serializing and deserializing Names and FastStrings. We do this because we actually use serialization in two distinct settings,

  • When serializing interface files themselves
  • When computing the fingerprint of an IfaceDecl (which we computing by hashing its Binary serialization)

These two settings have different needs while serializing Names:

  • Names in interface files are serialized via a symbol table (see Note [Symbol table representation of names] in BinIface).
  • During fingerprinting a binding Name is serialized as the OccName and a non-binding Name is serialized as the fingerprint of the thing they represent. See Note [Fingerprinting IfaceDecls] for further discussion.

Constructors

UserData 

Fields

newReadState Source #

Arguments

:: (BinHandle -> IO Name)

how to deserialize Names

-> (BinHandle -> IO FastString) 
-> UserData 

newWriteState Source #

Arguments

:: (BinHandle -> Name -> IO ())

how to serialize non-binding Names

-> (BinHandle -> Name -> IO ())

how to serialize binding Names

-> (BinHandle -> FastString -> IO ()) 
-> UserData