{-# LANGUAGE CPP #-}
{-# LANGUAGE NondecreasingIndentation #-}
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.Word (Word32)
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 (on)
import qualified Codec.Compression.GZip as G
import qualified Codec.Compression.Zlib.Internal as Z
import GHC.Compact as C
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
20250703 Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
10 Word64 -> Word64 -> Word64
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 <- ProfileOption -> TCMT IO Bool
forall (m :: * -> *). MonadDebug m => ProfileOption -> m Bool
hasProfileOption ProfileOption
Profile.Serialize
newD :: Dict
newD@(Dict HashTable Node Word32
nD HashTable String Word32
ltD HashTable Text Word32
stD HashTable Text Word32
bD HashTable Integer Word32
iD HashTable Double Word32
dD
HashTable NameId Word32
_nameD
HashTable QNameId Word32
_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
_) <- IO Dict -> TCMT IO Dict
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Dict -> TCMT IO Dict) -> IO Dict -> TCMT IO Dict
forall a b. (a -> b) -> a -> b
$ Bool -> IO Dict
emptyDict Bool
collectStats
Word32
root <- IO Word32 -> TCMT IO Word32
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> TCMT IO Word32) -> IO Word32 -> TCMT IO Word32
forall a b. (a -> b) -> a -> b
$ (ReaderT Dict IO Word32 -> Dict -> IO Word32
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
`runReaderT` Dict
newD) (ReaderT Dict IO Word32 -> IO Word32)
-> ReaderT Dict IO Word32 -> IO Word32
forall a b. (a -> b) -> a -> b
$ a -> ReaderT Dict IO Word32
forall a. EmbPrj a => a -> ReaderT Dict IO Word32
icode a
a
[Node]
nL <- IO [Node] -> TCMT IO [Node]
forall a. IO a -> TCMT IO a
benchSort (IO [Node] -> TCMT IO [Node]) -> IO [Node] -> TCMT IO [Node]
forall a b. (a -> b) -> a -> b
$ HashTable Node Word32 -> IO [Node]
forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Node Word32
nD
[Text]
stL <- IO [Text] -> TCMT IO [Text]
forall a. IO a -> TCMT IO a
benchSort (IO [Text] -> TCMT IO [Text]) -> IO [Text] -> TCMT IO [Text]
forall a b. (a -> b) -> a -> b
$ HashTable Text Word32 -> IO [Text]
forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Text Word32
stD
[String]
ltL <- IO [String] -> TCMT IO [String]
forall a. IO a -> TCMT IO a
benchSort (IO [String] -> TCMT IO [String])
-> IO [String] -> TCMT IO [String]
forall a b. (a -> b) -> a -> b
$ HashTable String Word32 -> IO [String]
forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable String Word32
ltD
[Text]
bL <- IO [Text] -> TCMT IO [Text]
forall a. IO a -> TCMT IO a
benchSort (IO [Text] -> TCMT IO [Text]) -> IO [Text] -> TCMT IO [Text]
forall a b. (a -> b) -> a -> b
$ HashTable Text Word32 -> IO [Text]
forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Text Word32
bD
[Integer]
iL <- IO [Integer] -> TCMT IO [Integer]
forall a. IO a -> TCMT IO a
benchSort (IO [Integer] -> TCMT IO [Integer])
-> IO [Integer] -> TCMT IO [Integer]
forall a b. (a -> b) -> a -> b
$ HashTable Integer Word32 -> IO [Integer]
forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Integer Word32
iD
[Double]
dL <- IO [Double] -> TCMT IO [Double]
forall a. IO a -> TCMT IO a
benchSort (IO [Double] -> TCMT IO [Double])
-> IO [Double] -> TCMT IO [Double]
forall a b. (a -> b) -> a -> b
$ HashTable Double Word32 -> IO [Double]
forall {b} {b}. (Ord b, Hashable b) => HashTable b b -> IO [b]
l HashTable Double Word32
dD
ProfileOption -> TCMT IO () -> TCMT IO ()
forall (m :: * -> *). MonadDebug m => ProfileOption -> m () -> m ()
whenProfile ProfileOption
Profile.Sharing (TCMT IO () -> TCMT IO ()) -> TCMT IO () -> TCMT IO ()
forall a b. (a -> b) -> a -> b
$ do
String -> IORef FreshAndReuse -> TCMT IO ()
statistics String
"pointers" IORef FreshAndReuse
tC
ProfileOption -> TCMT IO () -> TCMT IO ()
forall (m :: * -> *). MonadDebug m => ProfileOption -> m () -> m ()
whenProfile ProfileOption
Profile.Serialize (TCMT IO () -> TCMT IO ()) -> TCMT IO () -> TCMT IO ()
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
Bool -> TCMT IO () -> TCMT IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
collectStats (TCMT IO () -> TCMT IO ()) -> TCMT IO () -> TCMT IO ()
forall a b. (a -> b) -> a -> b
$ do
Map String Integer
stats <- (Integer -> Integer -> Integer)
-> [(String, Integer)] -> Map String Integer
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith Integer -> Integer -> Integer
forall a. HasCallStack => a
__IMPOSSIBLE__ ([(String, Integer)] -> Map String Integer)
-> ([(String, Int)] -> [(String, Integer)])
-> [(String, Int)]
-> Map String Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, Int) -> (String, Integer))
-> [(String, Int)] -> [(String, Integer)]
forall a b. (a -> b) -> [a] -> [b]
map ((Int -> Integer) -> (String, Int) -> (String, Integer)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second Int -> Integer
forall a. Integral a => a -> Integer
toInteger) ([(String, Int)] -> Map String Integer)
-> TCMT IO [(String, Int)] -> TCMT IO (Map String Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
IO [(String, Int)] -> TCMT IO [(String, Int)]
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [(String, Int)] -> TCMT IO [(String, Int)])
-> IO [(String, Int)] -> TCMT IO [(String, Int)]
forall a b. (a -> b) -> a -> b
$ [(String, Int)] -> [(String, Int)]
forall a. Ord a => [a] -> [a]
List.sort ([(String, Int)] -> [(String, Int)])
-> IO [(String, Int)] -> IO [(String, Int)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashTable String Int -> IO [(String, Int)]
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 ((Map String Integer -> Map String Integer) -> TCMT IO ())
-> (Map String Integer -> Map String Integer) -> TCMT IO ()
forall a b. (a -> b) -> a -> b
$ (Integer -> Integer -> Integer)
-> Map String Integer -> Map String Integer -> Map String Integer
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Map.unionWith Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(+) Map String Integer
stats
ByteString
bits1 <- Account (BenchPhase (TCMT IO))
-> TCMT IO ByteString -> TCMT IO ByteString
forall (m :: * -> *) c.
MonadBench m =>
Account (BenchPhase m) -> m c -> m c
Bench.billTo [ BenchPhase (TCMT IO)
Phase
Bench.Serialization, BenchPhase (TCMT IO)
Phase
Bench.BinaryEncode ] (TCMT IO ByteString -> TCMT IO ByteString)
-> TCMT IO ByteString -> TCMT IO ByteString
forall a b. (a -> b) -> a -> b
$
ByteString -> TCMT IO ByteString
forall a. a -> TCMT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> TCMT IO ByteString)
-> ByteString -> TCMT IO ByteString
forall a b. NFData a => (a -> b) -> a -> b
$!! (Word32, [Node], [String], [Text], [Text], [Integer], [Double])
-> ByteString
forall a. Binary a => a -> ByteString
B.encode (Word32
root, [Node]
nL, [String]
ltL, [Text]
stL, [Text]
bL, [Integer]
iL, [Double]
dL)
let compressParams :: CompressParams
compressParams = CompressParams
G.defaultCompressParams
{ G.compressLevel = G.bestSpeed
, G.compressStrategy = G.huffmanOnlyStrategy
}
ByteString
cbits <- Account (BenchPhase (TCMT IO))
-> TCMT IO ByteString -> TCMT IO ByteString
forall (m :: * -> *) c.
MonadBench m =>
Account (BenchPhase m) -> m c -> m c
Bench.billTo [ BenchPhase (TCMT IO)
Phase
Bench.Serialization, BenchPhase (TCMT IO)
Phase
Bench.Compress ] (TCMT IO ByteString -> TCMT IO ByteString)
-> TCMT IO ByteString -> TCMT IO ByteString
forall a b. (a -> b) -> a -> b
$
ByteString -> TCMT IO ByteString
forall a. a -> TCMT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> TCMT IO ByteString)
-> ByteString -> TCMT IO ByteString
forall a b. NFData a => (a -> b) -> a -> b
$!! CompressParams -> ByteString -> ByteString
G.compressWith CompressParams
compressParams ByteString
bits1
let x :: ByteString
x = Word64 -> ByteString
forall a. Binary a => a -> ByteString
B.encode Word64
currentInterfaceVersion ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
cbits
Encoded -> TCM Encoded
forall a. a -> TCMT IO a
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 = ((b, b) -> b) -> [(b, b)] -> [b]
forall a b. (a -> b) -> [a] -> [b]
List.map (b, b) -> b
forall a b. (a, b) -> a
fst ([(b, b)] -> [b]) -> ([(b, b)] -> [(b, b)]) -> [(b, b)] -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((b, b) -> (b, b) -> Ordering) -> [(b, b)] -> [(b, b)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
List.sortBy (b -> b -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (b -> b -> Ordering)
-> ((b, b) -> b) -> (b, b) -> (b, b) -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (b, b) -> b
forall a b. (a, b) -> b
snd) ([(b, b)] -> [b]) -> IO [(b, b)] -> IO [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HashTable b b -> IO [(b, 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 = Account (BenchPhase (TCMT IO)) -> TCMT IO c -> TCMT IO c
forall (m :: * -> *) c.
MonadBench m =>
Account (BenchPhase m) -> m c -> m c
Bench.billTo [BenchPhase (TCMT IO)
Phase
Bench.Serialization, BenchPhase (TCMT IO)
Phase
Bench.Sort] (TCMT IO c -> TCMT IO c)
-> (IO c -> TCMT IO c) -> IO c -> TCMT IO c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO c -> TCMT IO c
forall a. IO a -> TCMT IO a
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 Word32
fresh
#ifdef DEBUG_SERIALISATION
reused
#endif
<- IO FreshAndReuse -> TCMT IO FreshAndReuse
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FreshAndReuse -> TCMT IO FreshAndReuse)
-> IO FreshAndReuse -> TCMT IO FreshAndReuse
forall a b. (a -> b) -> a -> b
$ IORef FreshAndReuse -> IO FreshAndReuse
forall a. IORef a -> IO a
readIORef IORef FreshAndReuse
ioref
String -> Integer -> TCMT IO ()
forall (m :: * -> *).
MonadStatistics m =>
String -> Integer -> m ()
tickN (String
kind String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (fresh)") (Integer -> TCMT IO ()) -> Integer -> TCMT IO ()
forall a b. (a -> b) -> a -> b
$ Word32 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
fresh
#ifdef DEBUG_SERIALISATION
tickN (kind ++ " (reused)") $ fromIntegral reused
#endif
newtype ListLike a = ListLike { forall a. ListLike a -> Array Word32 a
unListLike :: Array Word32 a }
instance B.Binary a => B.Binary (ListLike a) where
put :: ListLike a -> Put
put = ListLike a -> Put
forall a. HasCallStack => a
__IMPOSSIBLE__
get :: Get (ListLike a)
get = (Array Word32 a -> ListLike a)
-> Get (Array Word32 a) -> Get (ListLike a)
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Array Word32 a -> ListLike a
forall a. Array Word32 a -> ListLike a
ListLike (Get (Array Word32 a) -> Get (ListLike a))
-> Get (Array Word32 a) -> Get (ListLike a)
forall a b. (a -> b) -> a -> b
$ (forall s. STT s Get (STArray s Word32 a)) -> Get (Array Word32 a)
forall (m :: * -> *) i e.
Monad m =>
(forall s. STT s m (STArray s i e)) -> m (Array i e)
runSTArray ((forall s. STT s Get (STArray s Word32 a))
-> Get (Array Word32 a))
-> (forall s. STT s Get (STArray s Word32 a))
-> Get (Array Word32 a)
forall a b. (a -> b) -> a -> b
$ do
Int
n <- Get Int -> STT s Get Int
forall (m :: * -> *) a. Monad m => m a -> STT s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Get Int
forall t. Binary t => Get t
B.get :: B.Get Int)
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 then ((Word32, Word32) -> STT s Get (STArray s Word32 a)
forall i. Ix i => (i, i) -> STT s Get (STArray s i a)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Word32
1,Word32
0) :: STT s B.Get (STArray s Word32 a)) else do
STArray s Word32 a
arr <- (Word32, Word32) -> STT s Get (STArray s Word32 a)
forall i. Ix i => (i, i) -> STT s Get (STArray s i a)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Word32
0, Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
- Word32
1) :: STT s B.Get (STArray s Word32 a)
let
getMany :: Int -> STT s Get ()
getMany Int
i = if Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
n then () -> STT s Get ()
forall a. a -> STT s Get a
forall (m :: * -> *) a. Monad m => a -> m a
return () else do
a
x <- Get a -> STT s Get a
forall (m :: * -> *) a. Monad m => m a -> STT s m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Get a
forall t. Binary t => Get t
B.get
STArray s Word32 a -> Int -> a -> STT s Get ()
forall (m :: * -> *) s i e.
Applicative m =>
STArray s i e -> Int -> e -> STT s m ()
unsafeWriteSTArray STArray s Word32 a
arr Int
i a
x
Int -> STT s Get ()
getMany (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
() <- Int -> STT s Get ()
getMany Int
0
STArray s Word32 a -> STT s Get (STArray s Word32 a)
forall a. a -> STT s Get a
forall (m :: * -> *) a. Monad m => a -> m a
return STArray s Word32 a
arr
decode :: EmbPrj a => ByteString -> TCM (Maybe a)
decode :: forall a. EmbPrj a => ByteString -> TCM (Maybe a)
decode ByteString
s = do
ModuleToSource
mf <- Lens' TCState ModuleToSource -> TCMT IO ModuleToSource
forall (m :: * -> *) a. ReadTCState m => Lens' TCState a -> m a
useTC (ModuleToSource -> f ModuleToSource) -> TCState -> f TCState
Lens' TCState ModuleToSource
stModuleToSource
List1 AbsolutePath
incs <- TCMT IO (List1 AbsolutePath)
forall (m :: * -> *). HasOptions m => m (List1 AbsolutePath)
getIncludeDirs
Either String (ModuleToSource, a)
res <- IO (Either String (ModuleToSource, a))
-> TCMT IO (Either String (ModuleToSource, a))
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either String (ModuleToSource, a))
-> TCMT IO (Either String (ModuleToSource, a)))
-> IO (Either String (ModuleToSource, a))
-> TCMT IO (Either String (ModuleToSource, a))
forall a b. (a -> b) -> a -> b
$ (ErrorCall -> IO (Either String (ModuleToSource, a)))
-> IO (Either String (ModuleToSource, a))
-> IO (Either String (ModuleToSource, a))
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
E.handle (\(E.ErrorCall String
s) -> Either String (ModuleToSource, a)
-> IO (Either String (ModuleToSource, a))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String (ModuleToSource, a)
-> IO (Either String (ModuleToSource, a)))
-> Either String (ModuleToSource, a)
-> IO (Either String (ModuleToSource, a))
forall a b. (a -> b) -> a -> b
$ String -> Either String (ModuleToSource, a)
forall a b. a -> Either a b
Left String
s) (IO (Either String (ModuleToSource, a))
-> IO (Either String (ModuleToSource, a)))
-> IO (Either String (ModuleToSource, a))
-> IO (Either String (ModuleToSource, a))
forall a b. (a -> b) -> a -> b
$ do
((Word32
r, ListLike [Word32]
nL, ListLike String
ltL, ListLike Text
stL, ListLike Text
bL, ListLike Integer
iL, ListLike Double
dL), ByteString
s, Int64
_) <- ((Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double),
ByteString, Int64)
-> IO
((Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double),
ByteString, Int64)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (((Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double),
ByteString, Int64)
-> IO
((Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double),
ByteString, Int64))
-> ((Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double),
ByteString, Int64)
-> IO
((Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double),
ByteString, Int64)
forall a b. (a -> b) -> a -> b
$ Get
(Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double)
-> ByteString
-> Int64
-> ((Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double),
ByteString, Int64)
forall a. Get a -> ByteString -> Int64 -> (a, ByteString, Int64)
runGetState Get
(Word32, ListLike [Word32], ListLike String, ListLike Text,
ListLike Text, ListLike Integer, ListLike Double)
forall t. Binary t => Get t
B.get ByteString
s Int64
0
let ar :: ListLike a -> Array Word32 a
ar = ListLike a -> Array Word32 a
forall a. ListLike a -> Array Word32 a
unListLike
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (ByteString -> Bool
forall a. Null a => a -> Bool
null ByteString
s)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ErrorCall -> IO ()
forall e a. Exception e => e -> IO a
E.throwIO (ErrorCall -> IO ()) -> ErrorCall -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> ErrorCall
E.ErrorCall String
"Garbage at end."
let nL' :: Array Word32 [Word32]
nL' = ListLike [Word32] -> Array Word32 [Word32]
forall a. ListLike a -> Array Word32 a
ar ListLike [Word32]
nL
St
st <- Array Word32 [Word32]
-> Array Word32 String
-> Array Word32 Text
-> Array Word32 Text
-> Array Word32 Integer
-> Array Word32 Double
-> Memo
-> ModuleToSource
-> List1 AbsolutePath
-> St
St Array Word32 [Word32]
nL' (ListLike String -> Array Word32 String
forall a. ListLike a -> Array Word32 a
ar ListLike String
ltL) (ListLike Text -> Array Word32 Text
forall a. ListLike a -> Array Word32 a
ar ListLike Text
stL) (ListLike Text -> Array Word32 Text
forall a. ListLike a -> Array Word32 a
ar ListLike Text
bL) (ListLike Integer -> Array Word32 Integer
forall a. ListLike a -> Array Word32 a
ar ListLike Integer
iL) (ListLike Double -> Array Word32 Double
forall a. ListLike a -> Array Word32 a
ar ListLike Double
dL)
(Memo -> ModuleToSource -> List1 AbsolutePath -> St)
-> IO Memo -> IO (ModuleToSource -> List1 AbsolutePath -> St)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Memo -> IO Memo
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((Word32, Word32) -> MemoEntry -> IO Memo
forall i. Ix i => (i, i) -> MemoEntry -> IO (IOArray i MemoEntry)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray (Array Word32 [Word32] -> (Word32, Word32)
forall i. Ix i => Array i [Word32] -> (i, i)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
bounds Array Word32 [Word32]
nL') MemoEntry
MEEmpty)
IO (ModuleToSource -> List1 AbsolutePath -> St)
-> IO ModuleToSource -> IO (List1 AbsolutePath -> St)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ModuleToSource -> IO ModuleToSource
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ModuleToSource
mf IO (List1 AbsolutePath -> St) -> IO (List1 AbsolutePath) -> IO St
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> List1 AbsolutePath -> IO (List1 AbsolutePath)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return List1 AbsolutePath
incs
(a
r, St
st) <- StateT St IO a -> St -> IO (a, St)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (Word32 -> StateT St IO a
forall a. EmbPrj a => Word32 -> R a
value Word32
r) St
st
let !mf :: ModuleToSource
mf = St -> ModuleToSource
modFile St
st
Either String (ModuleToSource, a)
-> IO (Either String (ModuleToSource, a))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String (ModuleToSource, a)
-> IO (Either String (ModuleToSource, a)))
-> Either String (ModuleToSource, a)
-> IO (Either String (ModuleToSource, a))
forall a b. (a -> b) -> a -> b
$ (ModuleToSource, a) -> Either String (ModuleToSource, a)
forall a b. b -> Either a b
Right (ModuleToSource
mf, a
r)
case Either String (ModuleToSource, a)
res of
Left String
s -> do
String -> Int -> String -> TCMT IO ()
forall (m :: * -> *).
MonadDebug m =>
String -> Int -> String -> m ()
reportSLn String
"import.iface" Int
5 (String -> TCMT IO ()) -> String -> TCMT IO ()
forall a b. (a -> b) -> a -> b
$ String
"Error when decoding interface file: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
Maybe a -> TCM (Maybe a)
forall a. a -> TCMT IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
Right (ModuleToSource
mf, a
x) -> do
Lens' TCState ModuleToSource -> ModuleToSource -> TCMT IO ()
forall (m :: * -> *) a.
MonadTCState m =>
Lens' TCState a -> a -> m ()
setTCLens (ModuleToSource -> f ModuleToSource) -> TCState -> f TCState
Lens' TCState ModuleToSource
stModuleToSource ModuleToSource
mf
Account (BenchPhase (TCMT IO)) -> TCM (Maybe a) -> TCM (Maybe a)
forall (m :: * -> *) c.
MonadBench m =>
Account (BenchPhase m) -> m c -> m c
Bench.billTo [BenchPhase (TCMT IO)
Phase
Bench.Deserialization, BenchPhase (TCMT IO)
Phase
Bench.Compaction] (TCM (Maybe a) -> TCM (Maybe a)) -> TCM (Maybe a) -> TCM (Maybe a)
forall a b. (a -> b) -> a -> b
$
IO (Maybe a) -> TCM (Maybe a)
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> (Compact a -> a) -> Compact a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compact a -> a
forall a. Compact a -> a
C.getCompact (Compact a -> Maybe a) -> IO (Compact a) -> IO (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> IO (Compact a)
forall a. a -> IO (Compact a)
C.compactWithSharing a
x)
encodeInterface :: Interface -> TCM Encoded
encodeInterface :: Interface -> TCM Encoded
encodeInterface Interface
i = do
Encoded
r <- Interface -> TCM Encoded
forall a. EmbPrj a => a -> TCM Encoded
encode Interface
i
Encoded -> TCM Encoded
forall a. a -> TCMT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Encoded
r{ compressed = hashes <> compressed r }
where
hashes :: ByteString
hashes :: ByteString
hashes = Put -> ByteString
B.runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ Word64 -> Put
forall t. Binary t => t -> Put
B.put (Interface -> Word64
iSourceHash Interface
i) Put -> Put -> Put
forall a b. PutM a -> PutM b -> PutM b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word64 -> Put
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
IO () -> TCMT IO ()
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> TCMT IO ()) -> IO () -> TCMT IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> String
takeDirectory String
f)
IO () -> TCMT IO ()
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> TCMT IO ()) -> IO () -> TCMT IO ()
forall a b. (a -> b) -> a -> b
$ String -> ByteString -> IO ()
L.writeFile String
f (Encoded -> ByteString
compressed Encoded
r)
ByteString -> TCMT IO ByteString
forall a. a -> TCMT IO a
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 <- IO (Either String ByteString) -> TCMT IO (Either String ByteString)
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either String ByteString)
-> TCMT IO (Either String ByteString))
-> IO (Either String ByteString)
-> TCMT IO (Either String ByteString)
forall a b. (a -> b) -> a -> b
$
(ErrorCall -> IO (Either String ByteString))
-> IO (Either String ByteString) -> IO (Either String ByteString)
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
E.handle (\(E.ErrorCall String
s) -> Either String ByteString -> IO (Either String ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String ByteString
forall a b. a -> Either a b
Left String
s)) (IO (Either String ByteString) -> IO (Either String ByteString))
-> IO (Either String ByteString) -> IO (Either String ByteString)
forall a b. (a -> b) -> a -> b
$
Either String ByteString -> IO (Either String ByteString)
forall a. a -> IO a
E.evaluate (Either String ByteString -> IO (Either String ByteString))
-> Either String ByteString -> IO (Either String ByteString)
forall a b. (a -> b) -> a -> b
$
let (Word64
ver, ByteString
s', Int64
_) = Get Word64 -> ByteString -> Int64 -> (Word64, ByteString, Int64)
forall a. Get a -> ByteString -> Int64 -> (a, ByteString, Int64)
runGetState Get Word64
forall t. Binary t => Get t
B.get (Int64 -> ByteString -> ByteString
L.drop Int64
16 ByteString
s) Int64
0 in
if Word64
ver Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word64
currentInterfaceVersion
then String -> Either String ByteString
forall a b. a -> Either a b
Left String
"Wrong interface version."
else ByteString -> Either String ByteString
forall a b. b -> Either a b
Right (ByteString -> Either String ByteString)
-> ByteString -> Either String ByteString
forall a b. (a -> b) -> a -> b
$
Builder -> ByteString
toLazyByteString (Builder -> ByteString) -> Builder -> ByteString
forall a b. (a -> b) -> a -> b
$
(ByteString -> Builder -> Builder)
-> (ByteString -> Builder)
-> (DecompressError -> Builder)
-> (forall s. DecompressStream (ST s))
-> ByteString
-> Builder
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 Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<>))
(\ByteString
s -> if ByteString -> Bool
forall a. Null a => a -> Bool
null ByteString
s
then Builder
forall a. Monoid a => a
mempty
else String -> Builder
forall a. HasCallStack => String -> a
error String
"Garbage at end.")
(\DecompressError
err -> String -> Builder
forall a. HasCallStack => String -> a
error (DecompressError -> String
forall a. Show a => a -> String
show DecompressError
err))
(Format -> DecompressParams -> DecompressStream (ST s)
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 -> ByteString -> TCM (Maybe Interface)
forall a. EmbPrj a => ByteString -> TCM (Maybe a)
decode ByteString
s
Left String
err -> do
String -> Int -> String -> TCMT IO ()
forall (m :: * -> *).
MonadDebug m =>
String -> Int -> String -> m ()
reportSLn String
"import.iface" Int
5 (String -> TCMT IO ()) -> String -> TCMT IO ()
forall a b. (a -> b) -> a -> b
$
String
"Error when decoding interface file: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
err
Maybe Interface -> TCM (Maybe Interface)
forall a. a -> TCMT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Interface
forall a. Maybe a
Nothing
decodeHashes :: ByteString -> Maybe (Hash, Hash)
decodeHashes :: ByteString -> Maybe (Word64, Word64)
decodeHashes ByteString
s
| ByteString -> Int64
L.length ByteString
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
16 = Maybe (Word64, Word64)
forall a. Maybe a
Nothing
| Bool
otherwise = (Word64, Word64) -> Maybe (Word64, Word64)
forall a. a -> Maybe a
Just ((Word64, Word64) -> Maybe (Word64, Word64))
-> (Word64, Word64) -> Maybe (Word64, Word64)
forall a b. (a -> b) -> a -> b
$ Get (Word64, Word64) -> ByteString -> (Word64, Word64)
forall a. Get a -> ByteString -> a
B.runGet Get (Word64, Word64)
getH (ByteString -> (Word64, Word64)) -> ByteString -> (Word64, Word64)
forall a b. (a -> b) -> a -> b
$ Int64 -> ByteString -> ByteString
L.take Int64
16 ByteString
s
where getH :: Get (Word64, Word64)
getH = (,) (Word64 -> Word64 -> (Word64, Word64))
-> Get Word64 -> Get (Word64 -> (Word64, Word64))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
forall t. Binary t => Get t
B.get Get (Word64 -> (Word64, Word64))
-> Get Word64 -> Get (Word64, Word64)
forall a b. Get (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word64
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 (ByteString -> TCM (Maybe Interface))
-> TCMT IO ByteString -> TCM (Maybe Interface)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO ByteString -> TCMT IO ByteString
forall a. IO a -> TCMT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO ByteString
L.readFile String
f)