{-# LANGUAGE CPP #-}
module Agda.TypeChecking.Serialise
( encode, encodeFile, encodeInterface
, decode, decodeFile, decodeInterface, decodeHashes
, EmbPrj
)
where
import Prelude hiding ( null )
import System.Directory ( createDirectoryIfMissing )
import System.FilePath ( takeDirectory )
import Control.Arrow (second)
import Control.DeepSeq
import qualified Control.Exception as E
import Control.Monad
import Control.Monad.Except
import Control.Monad.IO.Class ( MonadIO(..) )
import Control.Monad.Reader
import Control.Monad.State.Strict
import Control.Monad.ST.Trans
import Data.Array.IArray
import Data.Array.IO
import Data.Word
import Data.Int (Int32)
import Data.ByteString.Lazy ( ByteString )
import Data.ByteString.Builder ( byteString, toLazyByteString )
import qualified Data.ByteString.Lazy as L
import qualified Data.Map as Map
import qualified Data.Binary as B
import qualified Data.Binary.Get as B
import qualified Data.Binary.Put as B
import qualified Data.List as List
import Data.Function
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup((<>))
#endif
import qualified Codec.Compression.GZip as G
import qualified Codec.Compression.Zlib.Internal as Z
#if __GLASGOW_HASKELL__ >= 804
import GHC.Compact as C
#endif
import qualified Agda.TypeChecking.Monad.Benchmark as Bench
import Agda.TypeChecking.Serialise.Base
import Agda.TypeChecking.Serialise.Instances ()
import Agda.TypeChecking.Monad
import Agda.Utils.Hash
import qualified Agda.Utils.HashTable as H
import Agda.Utils.IORef
import Agda.Utils.Null
import qualified Agda.Utils.ProfileOptions as Profile
import Agda.Utils.Impossible
currentInterfaceVersion :: Word64
currentInterfaceVersion :: Word64
currentInterfaceVersion = Word64
20221031 forall a. Num a => a -> a -> a
* Word64
10 forall a. Num a => a -> a -> a
+ Word64
0
data Encoded = Encoded
{ Encoded -> ByteString
uncompressed :: ByteString
, Encoded -> ByteString
compressed :: ByteString
}
encode :: EmbPrj a => a -> TCM Encoded
encode :: forall a. EmbPrj a => a -> TCM Encoded
encode a
a = do
Bool
collectStats <- forall (m :: * -> *). MonadDebug m => ProfileOption -> m Bool
hasProfileOption ProfileOption
Profile.Serialize
newD :: Dict
newD@(Dict HashTable Node Int32
nD HashTable String Int32
ltD HashTable Text Int32
stD HashTable Text Int32
bD HashTable Integer Int32
iD HashTable Double Int32
dD HashTable (Ptr Term) Int32
_tD
HashTable NameId Int32
_nameD
HashTable QNameId Int32
_qnameD
IORef FreshAndReuse
nC IORef FreshAndReuse
ltC IORef FreshAndReuse
stC IORef FreshAndReuse
bC IORef FreshAndReuse
iC IORef FreshAndReuse
dC IORef FreshAndReuse
tC
IORef FreshAndReuse
nameC
IORef FreshAndReuse
qnameC
HashTable String Int
stats Bool
_) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Bool -> IO Dict
emptyDict Bool
collectStats
Int32
root <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
`runReaderT` Dict
newD) forall a b. (a -> b) -> a -> b
$ forall a. EmbPrj a => a -> ReaderT Dict IO Int32
icode a
a
[Node]
nL <- forall {c}. IO c -> TCMT IO c
benchSort forall a b. (a -> b) -> a -> b
$ forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Node Int32
nD
[Text]
stL <- forall {c}. IO c -> TCMT IO c
benchSort forall a b. (a -> b) -> a -> b
$ forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Text Int32
stD
[String]
ltL <- forall {c}. IO c -> TCMT IO c
benchSort forall a b. (a -> b) -> a -> b
$ forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable String Int32
ltD
[Text]
bL <- forall {c}. IO c -> TCMT IO c
benchSort forall a b. (a -> b) -> a -> b
$ forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Text Int32
bD
[Integer]
iL <- forall {c}. IO c -> TCMT IO c
benchSort forall a b. (a -> b) -> a -> b
$ forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Integer Int32
iD
[Double]
dL <- forall {c}. IO c -> TCMT IO c
benchSort forall a b. (a -> b) -> a -> b
$ forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Double Int32
dD
forall (m :: * -> *). MonadDebug m => ProfileOption -> m () -> m ()
whenProfile ProfileOption
Profile.Sharing forall a b. (a -> b) -> a -> b
$ do
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"pointers" IORef FreshAndReuse
tC
forall (m :: * -> *). MonadDebug m => ProfileOption -> m () -> m ()
whenProfile ProfileOption
Profile.Serialize forall a b. (a -> b) -> a -> b
$ do
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"Integer" IORef FreshAndReuse
iC
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"Lazy Text" IORef FreshAndReuse
ltC
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"Strict Text" IORef FreshAndReuse
stC
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"Text" IORef FreshAndReuse
bC
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"Double" IORef FreshAndReuse
dC
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"Node" IORef FreshAndReuse
nC
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"Shared Term" IORef FreshAndReuse
tC
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"A.QName" IORef FreshAndReuse
qnameC
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"A.Name" IORef FreshAndReuse
nameC
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
collectStats forall a b. (a -> b) -> a -> b
$ do
Map String Integer
stats <- forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith forall a. HasCallStack => a
__IMPOSSIBLE__ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall a. Integral a => a -> Integer
toInteger) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall k v. (Eq k, Hashable k) => HashTable k v -> IO [(k, v)]
H.toList HashTable String Int
stats
(Map String Integer -> Map String Integer) -> TCMT IO ()
modifyStatistics forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith forall a. Num a => a -> a -> a
(+) Map String Integer
stats
ByteString
bits1 <- forall (m :: * -> *) c.
MonadBench m =>
Account (BenchPhase m) -> m c -> m c
Bench.billTo [ Phase
Bench.Serialization, Phase
Bench.BinaryEncode ] forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. NFData a => (a -> b) -> a -> b
$!! forall a. Binary a => a -> ByteString
B.encode (Int32
root, [Node]
nL, [String]
ltL, [Text]
stL, [Text]
bL, [Integer]
iL, [Double]
dL)
let compressParams :: CompressParams
compressParams = CompressParams
G.defaultCompressParams
{ compressLevel :: CompressionLevel
G.compressLevel = CompressionLevel
G.bestSpeed
, compressStrategy :: CompressionStrategy
G.compressStrategy = CompressionStrategy
G.huffmanOnlyStrategy
}
ByteString
cbits <- forall (m :: * -> *) c.
MonadBench m =>
Account (BenchPhase m) -> m c -> m c
Bench.billTo [ Phase
Bench.Serialization, Phase
Bench.Compress ] forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. NFData a => (a -> b) -> a -> b
$!! CompressParams -> ByteString -> ByteString
G.compressWith CompressParams
compressParams ByteString
bits1
let x :: ByteString
x = forall a. Binary a => a -> ByteString
B.encode Word64
currentInterfaceVersion forall a. Semigroup a => a -> a -> a
<> ByteString
cbits
forall (m :: * -> *) a. Monad m => a -> m a
return (Encoded { uncompressed :: ByteString
uncompressed = ByteString
bits1, compressed :: ByteString
compressed = ByteString
x })
where
l :: HashTable b b -> IO [b]
l HashTable b b
h = forall a b. (a -> b) -> [a] -> [b]
List.map forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Ordering) -> [a] -> [a]
List.sortBy (forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. (a, b) -> b
snd) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k v. (Eq k, Hashable k) => HashTable k v -> IO [(k, v)]
H.toList HashTable b b
h
benchSort :: IO c -> TCMT IO c
benchSort = forall (m :: * -> *) c.
MonadBench m =>
Account (BenchPhase m) -> m c -> m c
Bench.billTo [Phase
Bench.Serialization, Phase
Bench.Sort] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
statistics :: String -> IORef FreshAndReuse -> TCM ()
statistics :: String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
kind IORef FreshAndReuse
ioref = do
FreshAndReuse Int32
fresh
#ifdef DEBUG
reused
#endif
<- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IORef a -> IO a
readIORef IORef FreshAndReuse
ioref
forall (m :: * -> *).
MonadStatistics m =>
String -> Integer -> m ()
tickN (String
kind forall a. [a] -> [a] -> [a]
++ String
" (fresh)") forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
fresh
#ifdef DEBUG
tickN (kind ++ " (reused)") $ fromIntegral reused
#endif
newtype ListLike a = ListLike { forall a. ListLike a -> Array Int32 a
unListLike :: Array Int32 a }
instance B.Binary a => B.Binary (ListLike a) where
put :: ListLike a -> Put
put = forall a. HasCallStack => a
__IMPOSSIBLE__
get :: Get (ListLike a)
get = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Array Int32 a -> ListLike a
ListLike forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) i e.
Monad m =>
(forall s. STT s m (STArray s i e)) -> m (Array i e)
runSTArray forall a b. (a -> b) -> a -> b
$ do
Int
n <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall t. Binary t => Get t
B.get :: B.Get Int)
STArray s Int32 a
arr <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int32
0, forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n forall a. Num a => a -> a -> a
- Int32
1) :: STT s B.Get (STArray s Int32 a)
let
getMany :: Int -> STT s Get ()
getMany Int
i = if Int
i forall a. Eq a => a -> a -> Bool
== Int
n then forall (m :: * -> *) a. Monad m => a -> m a
return () else do
a
x <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall t. Binary t => Get t
B.get
forall (m :: * -> *) s i e.
Applicative m =>
STArray s i e -> Int -> e -> STT s m ()
unsafeWriteSTArray STArray s Int32 a
arr Int
i a
x
Int -> STT s Get ()
getMany (Int
i forall a. Num a => a -> a -> a
+ Int
1)
() <- Int -> STT s Get ()
getMany Int
0
forall (m :: * -> *) a. Monad m => a -> m a
return STArray s Int32 a
arr
decode :: EmbPrj a => ByteString -> TCM (Maybe a)
decode :: forall a. EmbPrj a => ByteString -> TCM (Maybe a)
decode ByteString
s = do
ModuleToSource
mf <- forall (m :: * -> *) a. ReadTCState m => Lens' a TCState -> m a
useTC Lens' ModuleToSource TCState
stModuleToSource
[AbsolutePath]
incs <- forall (m :: * -> *). HasOptions m => m [AbsolutePath]
getIncludeDirs
(Maybe ModuleToSource
mf, Either TypeError a
r) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => (e -> IO a) -> IO a -> IO a
E.handle (\(E.ErrorCall String
s) -> forall {m :: * -> *} {a} {b}.
Monad m =>
String -> m (Maybe a, Either TypeError b)
noResult String
s) forall a b. (a -> b) -> a -> b
$ do
((Int32
r, ListLike Node
nL, ListLike String
ltL, ListLike Text
stL, ListLike Text
bL, ListLike Integer
iL, ListLike Double
dL), ByteString
s, Int64
_) <- forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Get a -> ByteString -> Int64 -> (a, ByteString, Int64)
runGetState forall t. Binary t => Get t
B.get ByteString
s Int64
0
if Bool -> Bool
not (forall a. Null a => a -> Bool
null ByteString
s)
then forall {m :: * -> *} {a} {b}.
Monad m =>
String -> m (Maybe a, Either TypeError b)
noResult String
"Garbage at end."
else do
let nL' :: Array Int32 Node
nL' = forall a. ListLike a -> Array Int32 a
ar ListLike Node
nL
St
st <- Array Int32 Node
-> Array Int32 String
-> Array Int32 Text
-> Array Int32 Text
-> Array Int32 Integer
-> Array Int32 Double
-> Memo
-> ModuleToSource
-> [AbsolutePath]
-> St
St Array Int32 Node
nL' (forall a. ListLike a -> Array Int32 a
ar ListLike String
ltL) (forall a. ListLike a -> Array Int32 a
ar ListLike Text
stL) (forall a. ListLike a -> Array Int32 a
ar ListLike Text
bL) (forall a. ListLike a -> Array Int32 a
ar ListLike Integer
iL) (forall a. ListLike a -> Array Int32 a
ar ListLike Double
dL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray (forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
bounds Array Int32 Node
nL') forall a. Monoid a => a
mempty)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (m :: * -> *) a. Monad m => a -> m a
return ModuleToSource
mf forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (m :: * -> *) a. Monad m => a -> m a
return [AbsolutePath]
incs
(Either TypeError a
r, St
st) <- forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (forall a. EmbPrj a => Int32 -> R a
value Int32
r)) St
st
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ St -> ModuleToSource
modFile St
st, Either TypeError a
r)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Maybe ModuleToSource
mf (forall (m :: * -> *) a.
MonadTCState m =>
Lens' a TCState -> a -> m ()
setTCLens Lens' ModuleToSource TCState
stModuleToSource)
case Either TypeError a
r of
Right a
x -> do
#if __GLASGOW_HASKELL__ >= 804
forall (m :: * -> *) c.
MonadBench m =>
Account (BenchPhase m) -> m c -> m c
Bench.billTo [Phase
Bench.Deserialization, Phase
Bench.Compaction] forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Compact a -> a
C.getCompact forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. a -> IO (Compact a)
C.compactWithSharing a
x)
#else
return (Just x)
#endif
Left TypeError
err -> do
forall (m :: * -> *).
MonadDebug m =>
String -> Int -> String -> m ()
reportSLn String
"import.iface" Int
5 forall a b. (a -> b) -> a -> b
$ String
"Error when decoding interface file"
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
where
ar :: ListLike a -> Array Int32 a
ar = forall a. ListLike a -> Array Int32 a
unListLike
noResult :: String -> m (Maybe a, Either TypeError b)
noResult String
s = forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Maybe a
Nothing, forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ String -> TypeError
GenericError String
s)
encodeInterface :: Interface -> TCM Encoded
encodeInterface :: Interface -> TCM Encoded
encodeInterface Interface
i = do
Encoded
r <- forall a. EmbPrj a => a -> TCM Encoded
encode Interface
i
forall (m :: * -> *) a. Monad m => a -> m a
return Encoded
r{ compressed :: ByteString
compressed = ByteString
hashes forall a. Semigroup a => a -> a -> a
<> Encoded -> ByteString
compressed Encoded
r }
where
hashes :: ByteString
hashes :: ByteString
hashes = Put -> ByteString
B.runPut forall a b. (a -> b) -> a -> b
$ forall t. Binary t => t -> Put
B.put (Interface -> Word64
iSourceHash Interface
i) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
B.put (Interface -> Word64
iFullHash Interface
i)
encodeFile :: FilePath -> Interface -> TCM ByteString
encodeFile :: String -> Interface -> TCMT IO ByteString
encodeFile String
f Interface
i = do
Encoded
r <- Interface -> TCM Encoded
encodeInterface Interface
i
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> String
takeDirectory String
f)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
L.writeFile String
f (Encoded -> ByteString
compressed Encoded
r)
forall (m :: * -> *) a. Monad m => a -> m a
return (Encoded -> ByteString
uncompressed Encoded
r)
decodeInterface :: ByteString -> TCM (Maybe Interface)
decodeInterface :: ByteString -> TCM (Maybe Interface)
decodeInterface ByteString
s = do
Either String ByteString
s <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
E.handle (\(E.ErrorCall String
s) -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left String
s)) forall a b. (a -> b) -> a -> b
$
forall a. a -> IO a
E.evaluate forall a b. (a -> b) -> a -> b
$
let (Word64
ver, ByteString
s', Int64
_) = forall a. Get a -> ByteString -> Int64 -> (a, ByteString, Int64)
runGetState forall t. Binary t => Get t
B.get (Int64 -> ByteString -> ByteString
L.drop Int64
16 ByteString
s) Int64
0 in
if Word64
ver forall a. Eq a => a -> a -> Bool
/= Word64
currentInterfaceVersion
then forall a b. a -> Either a b
Left String
"Wrong interface version."
else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$
Builder -> ByteString
toLazyByteString forall a b. (a -> b) -> a -> b
$
forall a.
(ByteString -> a -> a)
-> (ByteString -> a)
-> (DecompressError -> a)
-> (forall s. DecompressStream (ST s))
-> ByteString
-> a
Z.foldDecompressStreamWithInput
(\ByteString
s -> (ByteString -> Builder
byteString ByteString
s forall a. Semigroup a => a -> a -> a
<>))
(\ByteString
s -> if forall a. Null a => a -> Bool
null ByteString
s
then forall a. Monoid a => a
mempty
else forall a. HasCallStack => String -> a
error String
"Garbage at end.")
(\DecompressError
err -> forall a. HasCallStack => String -> a
error (forall a. Show a => a -> String
show DecompressError
err))
(forall s. Format -> DecompressParams -> DecompressStream (ST s)
Z.decompressST Format
Z.gzipFormat DecompressParams
Z.defaultDecompressParams)
ByteString
s'
case Either String ByteString
s of
Right ByteString
s -> forall a. EmbPrj a => ByteString -> TCM (Maybe a)
decode ByteString
s
Left String
err -> do
forall (m :: * -> *).
MonadDebug m =>
String -> Int -> String -> m ()
reportSLn String
"import.iface" Int
5 forall a b. (a -> b) -> a -> b
$
String
"Error when decoding interface file: " forall a. [a] -> [a] -> [a]
++ String
err
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
decodeHashes :: ByteString -> Maybe (Hash, Hash)
decodeHashes :: ByteString -> Maybe (Word64, Word64)
decodeHashes ByteString
s
| ByteString -> Int64
L.length ByteString
s forall a. Ord a => a -> a -> Bool
< Int64
16 = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Get a -> ByteString -> a
B.runGet Get (Word64, Word64)
getH forall a b. (a -> b) -> a -> b
$ Int64 -> ByteString -> ByteString
L.take Int64
16 ByteString
s
where getH :: Get (Word64, Word64)
getH = (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
B.get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
B.get
decodeFile :: FilePath -> TCM (Maybe Interface)
decodeFile :: String -> TCM (Maybe Interface)
decodeFile String
f = ByteString -> TCM (Maybe Interface)
decodeInterface forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO ByteString
L.readFile String
f)