{-# LANGUAGE BinaryLiterals, CPP, ScopedTypeVariables, BangPatterns #-}
{-# OPTIONS_GHC -O2 #-}
module GHC.Iface.Binary (
writeBinIface,
readBinIface,
readBinIface_,
getSymtabName,
getDictFastString,
CheckHiWay(..),
TraceBinIFaceReading(..),
getWithUserData,
putWithUserData,
getSymbolTable,
putName,
putDictionary,
putFastString,
putSymbolTable,
BinSymbolTable(..),
BinDictionary(..)
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Tc.Utils.Monad
import GHC.Builtin.Utils ( isKnownKeyName, lookupKnownKeyName )
import GHC.Iface.Env
import GHC.Driver.Types
import GHC.Unit
import GHC.Types.Name
import GHC.Driver.Session
import GHC.Driver.Ways
import GHC.Types.Unique.FM
import GHC.Types.Unique.Supply
import GHC.Utils.Panic
import GHC.Utils.Binary as Binary
import GHC.Types.SrcLoc
import GHC.Utils.Error
import GHC.Data.FastMutInt
import GHC.Types.Unique
import GHC.Utils.Outputable
import GHC.Types.Name.Cache
import GHC.Platform
import GHC.Data.FastString
import GHC.Settings.Constants
import GHC.Utils.Misc
import Data.Set (Set)
import Data.Array
import Data.Array.ST
import Data.Array.Unsafe
import Data.Bits
import Data.Char
import Data.Word
import Data.IORef
import Data.Foldable
import Control.Monad
import Control.Monad.ST
import Control.Monad.Trans.Class
import qualified Control.Monad.Trans.State.Strict as State
data CheckHiWay = CheckHiWay | IgnoreHiWay
deriving CheckHiWay -> CheckHiWay -> Bool
(CheckHiWay -> CheckHiWay -> Bool)
-> (CheckHiWay -> CheckHiWay -> Bool) -> Eq CheckHiWay
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckHiWay -> CheckHiWay -> Bool
$c/= :: CheckHiWay -> CheckHiWay -> Bool
== :: CheckHiWay -> CheckHiWay -> Bool
$c== :: CheckHiWay -> CheckHiWay -> Bool
Eq
data TraceBinIFaceReading = TraceBinIFaceReading | QuietBinIFaceReading
deriving TraceBinIFaceReading -> TraceBinIFaceReading -> Bool
(TraceBinIFaceReading -> TraceBinIFaceReading -> Bool)
-> (TraceBinIFaceReading -> TraceBinIFaceReading -> Bool)
-> Eq TraceBinIFaceReading
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceBinIFaceReading -> TraceBinIFaceReading -> Bool
$c/= :: TraceBinIFaceReading -> TraceBinIFaceReading -> Bool
== :: TraceBinIFaceReading -> TraceBinIFaceReading -> Bool
$c== :: TraceBinIFaceReading -> TraceBinIFaceReading -> Bool
Eq
readBinIface :: CheckHiWay -> TraceBinIFaceReading -> FilePath
-> TcRnIf a b ModIface
readBinIface :: forall a b.
CheckHiWay -> TraceBinIFaceReading -> String -> TcRnIf a b ModIface
readBinIface CheckHiWay
checkHiWay TraceBinIFaceReading
traceBinIFaceReading String
hi_path = do
NameCacheUpdater
ncu <- TcRnIf a b NameCacheUpdater
forall a b. TcRnIf a b NameCacheUpdater
mkNameCacheUpdater
DynFlags
dflags <- IOEnv (Env a b) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
IO ModIface -> TcRnIf a b ModIface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModIface -> TcRnIf a b ModIface)
-> IO ModIface -> TcRnIf a b ModIface
forall a b. (a -> b) -> a -> b
$ DynFlags
-> CheckHiWay
-> TraceBinIFaceReading
-> String
-> NameCacheUpdater
-> IO ModIface
readBinIface_ DynFlags
dflags CheckHiWay
checkHiWay TraceBinIFaceReading
traceBinIFaceReading String
hi_path NameCacheUpdater
ncu
readBinIface_ :: DynFlags -> CheckHiWay -> TraceBinIFaceReading -> FilePath
-> NameCacheUpdater
-> IO ModIface
readBinIface_ :: DynFlags
-> CheckHiWay
-> TraceBinIFaceReading
-> String
-> NameCacheUpdater
-> IO ModIface
readBinIface_ DynFlags
dflags CheckHiWay
checkHiWay TraceBinIFaceReading
traceBinIFaceReading String
hi_path NameCacheUpdater
ncu = do
let platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
printer :: SDoc -> IO ()
printer :: SDoc -> IO ()
printer = case TraceBinIFaceReading
traceBinIFaceReading of
TraceBinIFaceReading
TraceBinIFaceReading -> \SDoc
sd ->
DynFlags -> WarnReason -> Severity -> SrcSpan -> SDoc -> IO ()
putLogMsg DynFlags
dflags
WarnReason
NoReason
Severity
SevOutput
SrcSpan
noSrcSpan
(SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultDumpStyle SDoc
sd
TraceBinIFaceReading
QuietBinIFaceReading -> \SDoc
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
wantedGot :: String -> a -> a -> (a -> SDoc) -> IO ()
wantedGot :: forall a. String -> a -> a -> (a -> SDoc) -> IO ()
wantedGot String
what a
wanted a
got a -> SDoc
ppr' =
SDoc -> IO ()
printer (String -> SDoc
text String
what SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
": " SDoc -> SDoc -> SDoc
<>
[SDoc] -> SDoc
vcat [String -> SDoc
text String
"Wanted " SDoc -> SDoc -> SDoc
<> a -> SDoc
ppr' a
wanted SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
",",
String -> SDoc
text String
"got " SDoc -> SDoc -> SDoc
<> a -> SDoc
ppr' a
got])
errorOnMismatch :: (Eq a, Show a) => String -> a -> a -> IO ()
errorOnMismatch :: forall a. (Eq a, Show a) => String -> a -> a -> IO ()
errorOnMismatch String
what a
wanted a
got =
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (a
wanted a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
got) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ GhcException -> IO ()
forall a. GhcException -> IO a
throwGhcExceptionIO (GhcException -> IO ()) -> GhcException -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> GhcException
ProgramError
(String
what String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (wanted " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
wanted
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", got " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
got String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")")
BinHandle
bh <- String -> IO BinHandle
Binary.readBinMem String
hi_path
FixedLengthEncoding Word32
magic <- BinHandle -> IO (FixedLengthEncoding Word32)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
String
-> FixedLengthEncoding Word32
-> FixedLengthEncoding Word32
-> (FixedLengthEncoding Word32 -> SDoc)
-> IO ()
forall a. String -> a -> a -> (a -> SDoc) -> IO ()
wantedGot String
"Magic" (Platform -> FixedLengthEncoding Word32
binaryInterfaceMagic Platform
platform) FixedLengthEncoding Word32
magic (Word32 -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Word32 -> SDoc)
-> (FixedLengthEncoding Word32 -> Word32)
-> FixedLengthEncoding Word32
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FixedLengthEncoding Word32 -> Word32
forall a. FixedLengthEncoding a -> a
unFixedLength)
String -> Word32 -> Word32 -> IO ()
forall a. (Eq a, Show a) => String -> a -> a -> IO ()
errorOnMismatch String
"magic number mismatch: old/corrupt interface file?"
(FixedLengthEncoding Word32 -> Word32
forall a. FixedLengthEncoding a -> a
unFixedLength (FixedLengthEncoding Word32 -> Word32)
-> FixedLengthEncoding Word32 -> Word32
forall a b. (a -> b) -> a -> b
$ Platform -> FixedLengthEncoding Word32
binaryInterfaceMagic Platform
platform) (FixedLengthEncoding Word32 -> Word32
forall a. FixedLengthEncoding a -> a
unFixedLength FixedLengthEncoding Word32
magic)
String
check_ver <- BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
let our_ver :: String
our_ver = Integer -> String
forall a. Show a => a -> String
show Integer
hiVersion
String -> String -> String -> (String -> SDoc) -> IO ()
forall a. String -> a -> a -> (a -> SDoc) -> IO ()
wantedGot String
"Version" String
our_ver String
check_ver String -> SDoc
text
String -> String -> String -> IO ()
forall a. (Eq a, Show a) => String -> a -> a -> IO ()
errorOnMismatch String
"mismatched interface file versions" String
our_ver String
check_ver
String
check_way <- BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
let way_descr :: String
way_descr = Platform -> Set Way -> String
getWayDescr Platform
platform (DynFlags -> Set Way
ways DynFlags
dflags)
String -> String -> String -> (String -> SDoc) -> IO ()
forall a. String -> a -> a -> (a -> SDoc) -> IO ()
wantedGot String
"Way" String
way_descr String
check_way String -> SDoc
forall a. Outputable a => a -> SDoc
ppr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CheckHiWay
checkHiWay CheckHiWay -> CheckHiWay -> Bool
forall a. Eq a => a -> a -> Bool
== CheckHiWay
CheckHiWay) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> String -> String -> IO ()
forall a. (Eq a, Show a) => String -> a -> a -> IO ()
errorOnMismatch String
"mismatched interface file ways" String
way_descr String
check_way
Bin Any
extFields_p <- BinHandle -> IO (Bin Any)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
ModIface
mod_iface <- NameCacheUpdater -> BinHandle -> IO ModIface
forall a. Binary a => NameCacheUpdater -> BinHandle -> IO a
getWithUserData NameCacheUpdater
ncu BinHandle
bh
BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
extFields_p
ExtensibleFields
extFields <- BinHandle -> IO ExtensibleFields
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
ModIface -> IO ModIface
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
mod_iface{mi_ext_fields :: ExtensibleFields
mi_ext_fields = ExtensibleFields
extFields}
getWithUserData :: Binary a => NameCacheUpdater -> BinHandle -> IO a
getWithUserData :: forall a. Binary a => NameCacheUpdater -> BinHandle -> IO a
getWithUserData NameCacheUpdater
ncu BinHandle
bh = do
Bin Any
dict_p <- BinHandle -> IO (Bin Any)
forall a. Binary a => BinHandle -> IO a
Binary.get BinHandle
bh
Bin Any
data_p <- BinHandle -> IO (Bin Any)
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
dict_p
Dictionary
dict <- BinHandle -> IO Dictionary
getDictionary BinHandle
bh
BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
data_p
BinHandle
bh <- do
BinHandle
bh <- BinHandle -> IO BinHandle
forall (m :: * -> *) a. Monad m => a -> m a
return (BinHandle -> IO BinHandle) -> BinHandle -> IO BinHandle
forall a b. (a -> b) -> a -> b
$ BinHandle -> UserData -> BinHandle
setUserData BinHandle
bh (UserData -> BinHandle) -> UserData -> BinHandle
forall a b. (a -> b) -> a -> b
$ (BinHandle -> IO Name) -> (BinHandle -> IO FastString) -> UserData
newReadState (String -> BinHandle -> IO Name
forall a. HasCallStack => String -> a
error String
"getSymtabName")
(Dictionary -> BinHandle -> IO FastString
getDictFastString Dictionary
dict)
Bin Any
symtab_p <- BinHandle -> IO (Bin Any)
forall a. Binary a => BinHandle -> IO a
Binary.get BinHandle
bh
Bin Any
data_p <- BinHandle -> IO (Bin Any)
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
symtab_p
SymbolTable
symtab <- BinHandle -> NameCacheUpdater -> IO SymbolTable
getSymbolTable BinHandle
bh NameCacheUpdater
ncu
BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
data_p
BinHandle -> IO BinHandle
forall (m :: * -> *) a. Monad m => a -> m a
return (BinHandle -> IO BinHandle) -> BinHandle -> IO BinHandle
forall a b. (a -> b) -> a -> b
$ BinHandle -> UserData -> BinHandle
setUserData BinHandle
bh (UserData -> BinHandle) -> UserData -> BinHandle
forall a b. (a -> b) -> a -> b
$ (BinHandle -> IO Name) -> (BinHandle -> IO FastString) -> UserData
newReadState (NameCacheUpdater
-> Dictionary -> SymbolTable -> BinHandle -> IO Name
getSymtabName NameCacheUpdater
ncu Dictionary
dict SymbolTable
symtab)
(Dictionary -> BinHandle -> IO FastString
getDictFastString Dictionary
dict)
BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
writeBinIface :: DynFlags -> FilePath -> ModIface -> IO ()
writeBinIface :: DynFlags -> String -> ModIface -> IO ()
writeBinIface DynFlags
dflags String
hi_path ModIface
mod_iface = do
BinHandle
bh <- Int -> IO BinHandle
openBinMem Int
initBinMemSize
let platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
BinHandle -> FixedLengthEncoding Word32 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Platform -> FixedLengthEncoding Word32
binaryInterfaceMagic Platform
platform)
BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Integer -> String
forall a. Show a => a -> String
show Integer
hiVersion)
let way_descr :: String
way_descr = Platform -> Set Way -> String
getWayDescr Platform
platform (DynFlags -> Set Way
ways DynFlags
dflags)
BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh String
way_descr
Bin (Bin Any)
extFields_p_p <- BinHandle -> IO (Bin (Bin Any))
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
BinHandle -> Bin (Bin Any) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bin (Bin Any)
extFields_p_p
(SDoc -> IO ()) -> BinHandle -> ModIface -> IO ()
forall a. Binary a => (SDoc -> IO ()) -> BinHandle -> a -> IO ()
putWithUserData (DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg DynFlags
dflags Int
3) BinHandle
bh ModIface
mod_iface
Bin Any
extFields_p <- BinHandle -> IO (Bin Any)
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
BinHandle -> Bin (Bin Any) -> Bin Any -> IO ()
forall a. Binary a => BinHandle -> Bin a -> a -> IO ()
putAt BinHandle
bh Bin (Bin Any)
extFields_p_p Bin Any
extFields_p
BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
extFields_p
BinHandle -> ExtensibleFields -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (ModIface -> ExtensibleFields
forall (phase :: ModIfacePhase).
ModIface_ phase -> ExtensibleFields
mi_ext_fields ModIface
mod_iface)
BinHandle -> String -> IO ()
writeBinMem BinHandle
bh String
hi_path
putWithUserData :: Binary a => (SDoc -> IO ()) -> BinHandle -> a -> IO ()
putWithUserData :: forall a. Binary a => (SDoc -> IO ()) -> BinHandle -> a -> IO ()
putWithUserData SDoc -> IO ()
log_action BinHandle
bh a
payload = do
Bin (Bin Any)
dict_p_p <- BinHandle -> IO (Bin (Bin Any))
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
BinHandle -> Bin (Bin Any) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bin (Bin Any)
dict_p_p
Bin (Bin Any)
symtab_p_p <- BinHandle -> IO (Bin (Bin Any))
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
BinHandle -> Bin (Bin Any) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bin (Bin Any)
symtab_p_p
FastMutInt
symtab_next <- IO FastMutInt
newFastMutInt
FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
symtab_next Int
0
IORef (UniqFM Name (Int, Name))
symtab_map <- UniqFM Name (Int, Name) -> IO (IORef (UniqFM Name (Int, Name)))
forall a. a -> IO (IORef a)
newIORef UniqFM Name (Int, Name)
forall key elt. UniqFM key elt
emptyUFM
let bin_symtab :: BinSymbolTable
bin_symtab = BinSymbolTable :: FastMutInt -> IORef (UniqFM Name (Int, Name)) -> BinSymbolTable
BinSymbolTable {
bin_symtab_next :: FastMutInt
bin_symtab_next = FastMutInt
symtab_next,
bin_symtab_map :: IORef (UniqFM Name (Int, Name))
bin_symtab_map = IORef (UniqFM Name (Int, Name))
symtab_map }
FastMutInt
dict_next_ref <- IO FastMutInt
newFastMutInt
FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
dict_next_ref Int
0
IORef (UniqFM FastString (Int, FastString))
dict_map_ref <- UniqFM FastString (Int, FastString)
-> IO (IORef (UniqFM FastString (Int, FastString)))
forall a. a -> IO (IORef a)
newIORef UniqFM FastString (Int, FastString)
forall key elt. UniqFM key elt
emptyUFM
let bin_dict :: BinDictionary
bin_dict = BinDictionary :: FastMutInt
-> IORef (UniqFM FastString (Int, FastString)) -> BinDictionary
BinDictionary {
bin_dict_next :: FastMutInt
bin_dict_next = FastMutInt
dict_next_ref,
bin_dict_map :: IORef (UniqFM FastString (Int, FastString))
bin_dict_map = IORef (UniqFM FastString (Int, FastString))
dict_map_ref }
BinHandle
bh <- BinHandle -> IO BinHandle
forall (m :: * -> *) a. Monad m => a -> m a
return (BinHandle -> IO BinHandle) -> BinHandle -> IO BinHandle
forall a b. (a -> b) -> a -> b
$ BinHandle -> UserData -> BinHandle
setUserData BinHandle
bh (UserData -> BinHandle) -> UserData -> BinHandle
forall a b. (a -> b) -> a -> b
$ (BinHandle -> Name -> IO ())
-> (BinHandle -> Name -> IO ())
-> (BinHandle -> FastString -> IO ())
-> UserData
newWriteState (BinDictionary -> BinSymbolTable -> BinHandle -> Name -> IO ()
putName BinDictionary
bin_dict BinSymbolTable
bin_symtab)
(BinDictionary -> BinSymbolTable -> BinHandle -> Name -> IO ()
putName BinDictionary
bin_dict BinSymbolTable
bin_symtab)
(BinDictionary -> BinHandle -> FastString -> IO ()
putFastString BinDictionary
bin_dict)
BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
payload
Bin Any
symtab_p <- BinHandle -> IO (Bin Any)
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
BinHandle -> Bin (Bin Any) -> Bin Any -> IO ()
forall a. Binary a => BinHandle -> Bin a -> a -> IO ()
putAt BinHandle
bh Bin (Bin Any)
symtab_p_p Bin Any
symtab_p
BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
symtab_p
Int
symtab_next <- FastMutInt -> IO Int
readFastMutInt FastMutInt
symtab_next
UniqFM Name (Int, Name)
symtab_map <- IORef (UniqFM Name (Int, Name)) -> IO (UniqFM Name (Int, Name))
forall a. IORef a -> IO a
readIORef IORef (UniqFM Name (Int, Name))
symtab_map
BinHandle -> Int -> UniqFM Name (Int, Name) -> IO ()
putSymbolTable BinHandle
bh Int
symtab_next UniqFM Name (Int, Name)
symtab_map
SDoc -> IO ()
log_action (String -> SDoc
text String
"writeBinIface:" SDoc -> SDoc -> SDoc
<+> Int -> SDoc
int Int
symtab_next
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"Names")
Bin Any
dict_p <- BinHandle -> IO (Bin Any)
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
BinHandle -> Bin (Bin Any) -> Bin Any -> IO ()
forall a. Binary a => BinHandle -> Bin a -> a -> IO ()
putAt BinHandle
bh Bin (Bin Any)
dict_p_p Bin Any
dict_p
BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
dict_p
Int
dict_next <- FastMutInt -> IO Int
readFastMutInt FastMutInt
dict_next_ref
UniqFM FastString (Int, FastString)
dict_map <- IORef (UniqFM FastString (Int, FastString))
-> IO (UniqFM FastString (Int, FastString))
forall a. IORef a -> IO a
readIORef IORef (UniqFM FastString (Int, FastString))
dict_map_ref
BinHandle -> Int -> UniqFM FastString (Int, FastString) -> IO ()
putDictionary BinHandle
bh Int
dict_next UniqFM FastString (Int, FastString)
dict_map
SDoc -> IO ()
log_action (String -> SDoc
text String
"writeBinIface:" SDoc -> SDoc -> SDoc
<+> Int -> SDoc
int Int
dict_next
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"dict entries")
initBinMemSize :: Int
initBinMemSize :: Int
initBinMemSize = Int
1024 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
1024
binaryInterfaceMagic :: Platform -> FixedLengthEncoding Word32
binaryInterfaceMagic :: Platform -> FixedLengthEncoding Word32
binaryInterfaceMagic Platform
platform
| Platform -> Bool
target32Bit Platform
platform = Word32 -> FixedLengthEncoding Word32
forall a. a -> FixedLengthEncoding a
FixedLengthEncoding Word32
0x1face
| Bool
otherwise = Word32 -> FixedLengthEncoding Word32
forall a. a -> FixedLengthEncoding a
FixedLengthEncoding Word32
0x1face64
putSymbolTable :: BinHandle -> Int -> UniqFM Name (Int,Name) -> IO ()
putSymbolTable :: BinHandle -> Int -> UniqFM Name (Int, Name) -> IO ()
putSymbolTable BinHandle
bh Int
next_off UniqFM Name (Int, Name)
symtab = do
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
next_off
let names :: [Name]
names = SymbolTable -> [Name]
forall i e. Array i e -> [e]
elems ((Int, Int) -> [(Int, Name)] -> SymbolTable
forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e
array (Int
0,Int
next_offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (UniqFM Name (Int, Name) -> [(Int, Name)]
forall key elt. UniqFM key elt -> [elt]
nonDetEltsUFM UniqFM Name (Int, Name)
symtab))
(Name -> IO ()) -> [Name] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\Name
n -> BinHandle -> Name -> UniqFM Name (Int, Name) -> IO ()
forall key. BinHandle -> Name -> UniqFM key (Int, Name) -> IO ()
serialiseName BinHandle
bh Name
n UniqFM Name (Int, Name)
symtab) [Name]
names
getSymbolTable :: BinHandle -> NameCacheUpdater -> IO SymbolTable
getSymbolTable :: BinHandle -> NameCacheUpdater -> IO SymbolTable
getSymbolTable BinHandle
bh NameCacheUpdater
ncu = do
Int
sz <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
[OnDiskName]
od_names <- [IO OnDiskName] -> IO [OnDiskName]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence (Int -> IO OnDiskName -> [IO OnDiskName]
forall a. Int -> a -> [a]
replicate Int
sz (BinHandle -> IO OnDiskName
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh))
NameCacheUpdater -> forall c. (NameCache -> (NameCache, c)) -> IO c
updateNameCache NameCacheUpdater
ncu ((NameCache -> (NameCache, SymbolTable)) -> IO SymbolTable)
-> (NameCache -> (NameCache, SymbolTable)) -> IO SymbolTable
forall a b. (a -> b) -> a -> b
$ \NameCache
namecache ->
(forall s. ST s (NameCache, SymbolTable))
-> (NameCache, SymbolTable)
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (NameCache, SymbolTable))
-> (NameCache, SymbolTable))
-> (forall s. ST s (NameCache, SymbolTable))
-> (NameCache, SymbolTable)
forall a b. (a -> b) -> a -> b
$ (StateT NameCache (ST s) (NameCache, SymbolTable)
-> NameCache -> ST s (NameCache, SymbolTable))
-> NameCache
-> StateT NameCache (ST s) (NameCache, SymbolTable)
-> ST s (NameCache, SymbolTable)
forall a b c. (a -> b -> c) -> b -> a -> c
flip StateT NameCache (ST s) (NameCache, SymbolTable)
-> NameCache -> ST s (NameCache, SymbolTable)
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
State.evalStateT NameCache
namecache (StateT NameCache (ST s) (NameCache, SymbolTable)
-> ST s (NameCache, SymbolTable))
-> StateT NameCache (ST s) (NameCache, SymbolTable)
-> ST s (NameCache, SymbolTable)
forall a b. (a -> b) -> a -> b
$ do
STArray s Int Name
mut_arr <- ST s (STArray s Int Name)
-> StateT NameCache (ST s) (STArray s Int Name)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ST s (STArray s Int Name)
-> StateT NameCache (ST s) (STArray s Int Name))
-> ST s (STArray s Int Name)
-> StateT NameCache (ST s) (STArray s Int Name)
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> ST s (STArray s Int Name)
forall s. (Int, Int) -> ST s (STArray s Int Name)
newSTArray_ (Int
0, Int
szInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
[(Int, OnDiskName)]
-> ((Int, OnDiskName) -> StateT NameCache (ST s) ())
-> StateT NameCache (ST s) ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ ([Int] -> [OnDiskName] -> [(Int, OnDiskName)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] [OnDiskName]
od_names) (((Int, OnDiskName) -> StateT NameCache (ST s) ())
-> StateT NameCache (ST s) ())
-> ((Int, OnDiskName) -> StateT NameCache (ST s) ())
-> StateT NameCache (ST s) ()
forall a b. (a -> b) -> a -> b
$ \(Int
i, OnDiskName
odn) -> do
(NameCache
nc, !Name
n) <- (NameCache -> (NameCache, Name))
-> StateT NameCache (ST s) (NameCache, Name)
forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
State.gets ((NameCache -> (NameCache, Name))
-> StateT NameCache (ST s) (NameCache, Name))
-> (NameCache -> (NameCache, Name))
-> StateT NameCache (ST s) (NameCache, Name)
forall a b. (a -> b) -> a -> b
$ \NameCache
nc -> NameCache -> OnDiskName -> (NameCache, Name)
fromOnDiskName NameCache
nc OnDiskName
odn
ST s () -> StateT NameCache (ST s) ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ST s () -> StateT NameCache (ST s) ())
-> ST s () -> StateT NameCache (ST s) ()
forall a b. (a -> b) -> a -> b
$ STArray s Int Name -> Int -> Name -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STArray s Int Name
mut_arr Int
i Name
n
NameCache -> StateT NameCache (ST s) ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
State.put NameCache
nc
SymbolTable
arr <- ST s SymbolTable -> StateT NameCache (ST s) SymbolTable
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ST s SymbolTable -> StateT NameCache (ST s) SymbolTable)
-> ST s SymbolTable -> StateT NameCache (ST s) SymbolTable
forall a b. (a -> b) -> a -> b
$ STArray s Int Name -> ST s SymbolTable
forall i (a :: * -> * -> *) e (m :: * -> *) (b :: * -> * -> *).
(Ix i, MArray a e m, IArray b e) =>
a i e -> m (b i e)
unsafeFreeze STArray s Int Name
mut_arr
NameCache
namecache' <- StateT NameCache (ST s) NameCache
forall (m :: * -> *) s. Monad m => StateT s m s
State.get
(NameCache, SymbolTable)
-> StateT NameCache (ST s) (NameCache, SymbolTable)
forall (m :: * -> *) a. Monad m => a -> m a
return (NameCache
namecache', SymbolTable
arr)
where
newSTArray_ :: forall s. (Int, Int) -> ST s (STArray s Int Name)
newSTArray_ :: forall s. (Int, Int) -> ST s (STArray s Int Name)
newSTArray_ = (Int, Int) -> ST s (STArray s Int Name)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_
type OnDiskName = (Unit, ModuleName, OccName)
fromOnDiskName :: NameCache -> OnDiskName -> (NameCache, Name)
fromOnDiskName :: NameCache -> OnDiskName -> (NameCache, Name)
fromOnDiskName NameCache
nc (GenUnit UnitId
pid, ModuleName
mod_name, OccName
occ) =
let mod :: GenModule (GenUnit UnitId)
mod = GenUnit UnitId -> ModuleName -> GenModule (GenUnit UnitId)
forall u. u -> ModuleName -> GenModule u
mkModule GenUnit UnitId
pid ModuleName
mod_name
cache :: OrigNameCache
cache = NameCache -> OrigNameCache
nsNames NameCache
nc
in case OrigNameCache
-> GenModule (GenUnit UnitId) -> OccName -> Maybe Name
lookupOrigNameCache OrigNameCache
cache GenModule (GenUnit UnitId)
mod OccName
occ of
Just Name
name -> (NameCache
nc, Name
name)
Maybe Name
Nothing ->
let (Unique
uniq, UniqSupply
us) = UniqSupply -> (Unique, UniqSupply)
takeUniqFromSupply (NameCache -> UniqSupply
nsUniqs NameCache
nc)
name :: Name
name = Unique -> GenModule (GenUnit UnitId) -> OccName -> SrcSpan -> Name
mkExternalName Unique
uniq GenModule (GenUnit UnitId)
mod OccName
occ SrcSpan
noSrcSpan
new_cache :: OrigNameCache
new_cache = OrigNameCache
-> GenModule (GenUnit UnitId) -> OccName -> Name -> OrigNameCache
extendNameCache OrigNameCache
cache GenModule (GenUnit UnitId)
mod OccName
occ Name
name
in ( NameCache
nc{ nsUniqs :: UniqSupply
nsUniqs = UniqSupply
us, nsNames :: OrigNameCache
nsNames = OrigNameCache
new_cache }, Name
name )
serialiseName :: BinHandle -> Name -> UniqFM key (Int,Name) -> IO ()
serialiseName :: forall key. BinHandle -> Name -> UniqFM key (Int, Name) -> IO ()
serialiseName BinHandle
bh Name
name UniqFM key (Int, Name)
_ = do
let mod :: GenModule (GenUnit UnitId)
mod = ASSERT2( isExternalName name, ppr name ) nameModule name
BinHandle -> OnDiskName -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (GenModule (GenUnit UnitId) -> GenUnit UnitId
forall unit. GenModule unit -> unit
moduleUnit GenModule (GenUnit UnitId)
mod, GenModule (GenUnit UnitId) -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName GenModule (GenUnit UnitId)
mod, Name -> OccName
nameOccName Name
name)
putName :: BinDictionary -> BinSymbolTable -> BinHandle -> Name -> IO ()
putName :: BinDictionary -> BinSymbolTable -> BinHandle -> Name -> IO ()
putName BinDictionary
_dict BinSymbolTable{
bin_symtab_map :: BinSymbolTable -> IORef (UniqFM Name (Int, Name))
bin_symtab_map = IORef (UniqFM Name (Int, Name))
symtab_map_ref,
bin_symtab_next :: BinSymbolTable -> FastMutInt
bin_symtab_next = FastMutInt
symtab_next }
BinHandle
bh Name
name
| Name -> Bool
isKnownKeyName Name
name
, let (Char
c, Int
u) = Unique -> (Char, Int)
unpkUnique (Name -> Unique
nameUnique Name
name)
=
BinHandle -> Word32 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Word32
0x80000000
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c) Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` Int
22)
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
u :: Word32))
| Bool
otherwise
= do UniqFM Name (Int, Name)
symtab_map <- IORef (UniqFM Name (Int, Name)) -> IO (UniqFM Name (Int, Name))
forall a. IORef a -> IO a
readIORef IORef (UniqFM Name (Int, Name))
symtab_map_ref
case UniqFM Name (Int, Name) -> Name -> Maybe (Int, Name)
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM Name (Int, Name)
symtab_map Name
name of
Just (Int
off,Name
_) -> BinHandle -> Word32 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off :: Word32)
Maybe (Int, Name)
Nothing -> do
Int
off <- FastMutInt -> IO Int
readFastMutInt FastMutInt
symtab_next
FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
symtab_next (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
IORef (UniqFM Name (Int, Name)) -> UniqFM Name (Int, Name) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (UniqFM Name (Int, Name))
symtab_map_ref
(UniqFM Name (Int, Name) -> IO ())
-> UniqFM Name (Int, Name) -> IO ()
forall a b. (a -> b) -> a -> b
$! UniqFM Name (Int, Name)
-> Name -> (Int, Name) -> UniqFM Name (Int, Name)
forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM UniqFM Name (Int, Name)
symtab_map Name
name (Int
off,Name
name)
BinHandle -> Word32 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
off :: Word32)
getSymtabName :: NameCacheUpdater
-> Dictionary -> SymbolTable
-> BinHandle -> IO Name
getSymtabName :: NameCacheUpdater
-> Dictionary -> SymbolTable -> BinHandle -> IO Name
getSymtabName NameCacheUpdater
_ncu Dictionary
_dict SymbolTable
symtab BinHandle
bh = do
Word32
i :: Word32 <- BinHandle -> IO Word32
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
case Word32
i Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
0xC0000000 of
Word32
0x00000000 -> Name -> IO Name
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> IO Name) -> Name -> IO Name
forall a b. (a -> b) -> a -> b
$! SymbolTable
symtab SymbolTable -> Int -> Name
forall i e. Ix i => Array i e -> i -> e
! Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
i
Word32
0x80000000 ->
let
tag :: Char
tag = Int -> Char
chr (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word32
i Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
0x3FC00000) Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` Int
22))
ix :: Int
ix = Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
i Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x003FFFFF
u :: Unique
u = Char -> Int -> Unique
mkUnique Char
tag Int
ix
in
Name -> IO Name
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> IO Name) -> Name -> IO Name
forall a b. (a -> b) -> a -> b
$! case Unique -> Maybe Name
lookupKnownKeyName Unique
u of
Maybe Name
Nothing -> String -> SDoc -> Name
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getSymtabName:unknown known-key unique"
(Word32 -> SDoc
forall a. Outputable a => a -> SDoc
ppr Word32
i SDoc -> SDoc -> SDoc
$$ (Char, Int) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Unique -> (Char, Int)
unpkUnique Unique
u))
Just Name
n -> Name
n
Word32
_ -> String -> SDoc -> IO Name
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"getSymtabName:unknown name tag" (Word32 -> SDoc
forall a. Outputable a => a -> SDoc
ppr Word32
i)
data BinSymbolTable = BinSymbolTable {
BinSymbolTable -> FastMutInt
bin_symtab_next :: !FastMutInt,
BinSymbolTable -> IORef (UniqFM Name (Int, Name))
bin_symtab_map :: !(IORef (UniqFM Name (Int,Name)))
}
putFastString :: BinDictionary -> BinHandle -> FastString -> IO ()
putFastString :: BinDictionary -> BinHandle -> FastString -> IO ()
putFastString BinDictionary
dict BinHandle
bh FastString
fs = BinDictionary -> FastString -> IO Word32
allocateFastString BinDictionary
dict FastString
fs IO Word32 -> (Word32 -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= BinHandle -> Word32 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh
allocateFastString :: BinDictionary -> FastString -> IO Word32
allocateFastString :: BinDictionary -> FastString -> IO Word32
allocateFastString BinDictionary { bin_dict_next :: BinDictionary -> FastMutInt
bin_dict_next = FastMutInt
j_r,
bin_dict_map :: BinDictionary -> IORef (UniqFM FastString (Int, FastString))
bin_dict_map = IORef (UniqFM FastString (Int, FastString))
out_r} FastString
f = do
UniqFM FastString (Int, FastString)
out <- IORef (UniqFM FastString (Int, FastString))
-> IO (UniqFM FastString (Int, FastString))
forall a. IORef a -> IO a
readIORef IORef (UniqFM FastString (Int, FastString))
out_r
let !uniq :: Unique
uniq = FastString -> Unique
forall a. Uniquable a => a -> Unique
getUnique FastString
f
case UniqFM FastString (Int, FastString)
-> Unique -> Maybe (Int, FastString)
forall key elt. UniqFM key elt -> Unique -> Maybe elt
lookupUFM_Directly UniqFM FastString (Int, FastString)
out Unique
uniq of
Just (Int
j, FastString
_) -> Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
j :: Word32)
Maybe (Int, FastString)
Nothing -> do
Int
j <- FastMutInt -> IO Int
readFastMutInt FastMutInt
j_r
FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
j_r (Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
IORef (UniqFM FastString (Int, FastString))
-> UniqFM FastString (Int, FastString) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (UniqFM FastString (Int, FastString))
out_r (UniqFM FastString (Int, FastString) -> IO ())
-> UniqFM FastString (Int, FastString) -> IO ()
forall a b. (a -> b) -> a -> b
$! UniqFM FastString (Int, FastString)
-> Unique
-> (Int, FastString)
-> UniqFM FastString (Int, FastString)
forall key elt. UniqFM key elt -> Unique -> elt -> UniqFM key elt
addToUFM_Directly UniqFM FastString (Int, FastString)
out Unique
uniq (Int
j, FastString
f)
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
j :: Word32)
getDictFastString :: Dictionary -> BinHandle -> IO FastString
getDictFastString :: Dictionary -> BinHandle -> IO FastString
getDictFastString Dictionary
dict BinHandle
bh = do
Word32
j <- BinHandle -> IO Word32
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
FastString -> IO FastString
forall (m :: * -> *) a. Monad m => a -> m a
return (FastString -> IO FastString) -> FastString -> IO FastString
forall a b. (a -> b) -> a -> b
$! (Dictionary
dict Dictionary -> Int -> FastString
forall i e. Ix i => Array i e -> i -> e
! Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
j :: Word32))
data BinDictionary = BinDictionary {
BinDictionary -> FastMutInt
bin_dict_next :: !FastMutInt,
BinDictionary -> IORef (UniqFM FastString (Int, FastString))
bin_dict_map :: !(IORef (UniqFM FastString (Int,FastString)))
}
getWayDescr :: Platform -> Set Way -> String
getWayDescr :: Platform -> Set Way -> String
getWayDescr Platform
platform Set Way
ws
| Platform -> Bool
platformUnregisterised Platform
platform = Char
'u'Char -> String -> String
forall a. a -> [a] -> [a]
:String
tag
| Bool
otherwise = String
tag
where tag :: String
tag = Set Way -> String
waysBuildTag Set Way
ws