{-# LANGUAGE BangPatterns               #-}
{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase                 #-}
{-# LANGUAGE ScopedTypeVariables        #-}

module HiFileParser
  ( Interface (..)
  , List (..)
  , Dictionary (..)
  , Module (..)
  , Usage (..)
  , Dependencies (..)
  , getInterface
  , fromFile
  ) where

{- HLINT ignore "Reduce duplication" -}

import           Control.Monad ( replicateM, replicateM_, when )
import           Data.Binary ( Word32, Word64, Word8)
import qualified Data.Binary.Get as G
                   ( Decoder (..), Get, bytesRead, getByteString, getInt64be
                   , getWord32be, getWord64be, getWord8, lookAhead
                   , runGetIncremental, skip
                   )
import           Data.Bool ( bool )
import           Data.ByteString.Lazy.Internal ( defaultChunkSize )
import           Data.Char ( chr )
import           Data.Functor ( ($>), void )
import           Data.Maybe ( catMaybes )
#if !MIN_VERSION_base(4,11,0)
import           Data.Semigroup ( (<>) )
#endif
import qualified Data.Vector as V
import qualified Data.Text.Encoding as Text
import qualified Data.Text as Text
import           GHC.IO.IOMode ( IOMode (..) )
import           Numeric ( showHex )
import           RIO.ByteString as B ( ByteString, hGetSome, null )
import           RIO ( Generic, Int64, NFData )
import           System.IO ( withBinaryFile )
import           Data.Bits
                   ( FiniteBits (..), (.|.), clearBit, complement, testBit
                   , unsafeShiftL
                   )
import           Control.Monad.State
                   ( StateT, evalStateT, get, gets, lift, modify )
import qualified Debug.Trace

newtype IfaceGetState = IfaceGetState
  { IfaceGetState -> Bool
useLEB128 :: Bool -- ^ Use LEB128 encoding for numbers

  }

data IfaceVersion
  = V7021
  | V7041
  | V7061
  | V7081
  | V8001
  | V8021
  | V8041
  | V8061
  | V8101
  | V9001
  | V9041
  | V9045
  | V9081
  | V9120
  deriving (IfaceVersion -> IfaceVersion -> Bool
(IfaceVersion -> IfaceVersion -> Bool)
-> (IfaceVersion -> IfaceVersion -> Bool) -> Eq IfaceVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IfaceVersion -> IfaceVersion -> Bool
== :: IfaceVersion -> IfaceVersion -> Bool
$c/= :: IfaceVersion -> IfaceVersion -> Bool
/= :: IfaceVersion -> IfaceVersion -> Bool
Eq, Int -> IfaceVersion
IfaceVersion -> Int
IfaceVersion -> [IfaceVersion]
IfaceVersion -> IfaceVersion
IfaceVersion -> IfaceVersion -> [IfaceVersion]
IfaceVersion -> IfaceVersion -> IfaceVersion -> [IfaceVersion]
(IfaceVersion -> IfaceVersion)
-> (IfaceVersion -> IfaceVersion)
-> (Int -> IfaceVersion)
-> (IfaceVersion -> Int)
-> (IfaceVersion -> [IfaceVersion])
-> (IfaceVersion -> IfaceVersion -> [IfaceVersion])
-> (IfaceVersion -> IfaceVersion -> [IfaceVersion])
-> (IfaceVersion -> IfaceVersion -> IfaceVersion -> [IfaceVersion])
-> Enum IfaceVersion
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: IfaceVersion -> IfaceVersion
succ :: IfaceVersion -> IfaceVersion
$cpred :: IfaceVersion -> IfaceVersion
pred :: IfaceVersion -> IfaceVersion
$ctoEnum :: Int -> IfaceVersion
toEnum :: Int -> IfaceVersion
$cfromEnum :: IfaceVersion -> Int
fromEnum :: IfaceVersion -> Int
$cenumFrom :: IfaceVersion -> [IfaceVersion]
enumFrom :: IfaceVersion -> [IfaceVersion]
$cenumFromThen :: IfaceVersion -> IfaceVersion -> [IfaceVersion]
enumFromThen :: IfaceVersion -> IfaceVersion -> [IfaceVersion]
$cenumFromTo :: IfaceVersion -> IfaceVersion -> [IfaceVersion]
enumFromTo :: IfaceVersion -> IfaceVersion -> [IfaceVersion]
$cenumFromThenTo :: IfaceVersion -> IfaceVersion -> IfaceVersion -> [IfaceVersion]
enumFromThenTo :: IfaceVersion -> IfaceVersion -> IfaceVersion -> [IfaceVersion]
Enum, Eq IfaceVersion
Eq IfaceVersion =>
(IfaceVersion -> IfaceVersion -> Ordering)
-> (IfaceVersion -> IfaceVersion -> Bool)
-> (IfaceVersion -> IfaceVersion -> Bool)
-> (IfaceVersion -> IfaceVersion -> Bool)
-> (IfaceVersion -> IfaceVersion -> Bool)
-> (IfaceVersion -> IfaceVersion -> IfaceVersion)
-> (IfaceVersion -> IfaceVersion -> IfaceVersion)
-> Ord IfaceVersion
IfaceVersion -> IfaceVersion -> Bool
IfaceVersion -> IfaceVersion -> Ordering
IfaceVersion -> IfaceVersion -> IfaceVersion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IfaceVersion -> IfaceVersion -> Ordering
compare :: IfaceVersion -> IfaceVersion -> Ordering
$c< :: IfaceVersion -> IfaceVersion -> Bool
< :: IfaceVersion -> IfaceVersion -> Bool
$c<= :: IfaceVersion -> IfaceVersion -> Bool
<= :: IfaceVersion -> IfaceVersion -> Bool
$c> :: IfaceVersion -> IfaceVersion -> Bool
> :: IfaceVersion -> IfaceVersion -> Bool
$c>= :: IfaceVersion -> IfaceVersion -> Bool
>= :: IfaceVersion -> IfaceVersion -> Bool
$cmax :: IfaceVersion -> IfaceVersion -> IfaceVersion
max :: IfaceVersion -> IfaceVersion -> IfaceVersion
$cmin :: IfaceVersion -> IfaceVersion -> IfaceVersion
min :: IfaceVersion -> IfaceVersion -> IfaceVersion
Ord, Int -> IfaceVersion -> ShowS
[IfaceVersion] -> ShowS
IfaceVersion -> String
(Int -> IfaceVersion -> ShowS)
-> (IfaceVersion -> String)
-> ([IfaceVersion] -> ShowS)
-> Show IfaceVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IfaceVersion -> ShowS
showsPrec :: Int -> IfaceVersion -> ShowS
$cshow :: IfaceVersion -> String
show :: IfaceVersion -> String
$cshowList :: [IfaceVersion] -> ShowS
showList :: [IfaceVersion] -> ShowS
Show)
  -- careful, the Ord matters!



type Get a = StateT IfaceGetState G.Get a

enableDebug :: Bool
enableDebug :: Bool
enableDebug = Bool
False

traceGet :: String -> Get ()
traceGet :: String -> Get ()
traceGet String
s
  | Bool
enableDebug = String -> Get () -> Get ()
forall a. String -> a -> a
Debug.Trace.trace String
s (() -> Get ()
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
  | Bool
otherwise   = () -> Get ()
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

traceShow :: Show a => String -> Get a -> Get a
traceShow :: forall a. Show a => String -> Get a -> Get a
traceShow String
s Get a
g
  | Bool -> Bool
not Bool
enableDebug = Get a
g
  | Bool
otherwise = do
    a
a <- Get a
g
    String -> Get ()
traceGet (String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
a)
    a -> Get a
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a

runGetIncremental :: Get a -> G.Decoder a
runGetIncremental :: forall a. Get a -> Decoder a
runGetIncremental Get a
g = Get a -> Decoder a
forall a. Get a -> Decoder a
G.runGetIncremental (Get a -> IfaceGetState -> Get a
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT Get a
g IfaceGetState
emptyState)
 where
  emptyState :: IfaceGetState
emptyState = Bool -> IfaceGetState
IfaceGetState Bool
False

getByteString :: Int -> Get ByteString
getByteString :: Int -> Get ByteString
getByteString Int
i = Get ByteString -> Get ByteString
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Int -> Get ByteString
G.getByteString Int
i)

getWord8 :: Get Word8
getWord8 :: Get Word8
getWord8 = Get Word8 -> Get Word8
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Get Word8
G.getWord8

bytesRead :: Get Int64
bytesRead :: Get Int64
bytesRead = Get Int64 -> Get Int64
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Get Int64
G.bytesRead

skip :: Int -> Get ()
skip :: Int -> Get ()
skip = Get () -> Get ()
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Get () -> Get ()) -> (Int -> Get ()) -> Int -> Get ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Get ()
G.skip

uleb :: Get a -> Get a -> Get a
uleb :: forall a. Get a -> Get a -> Get a
uleb Get a
f Get a
g = do
  Bool
c <- (IfaceGetState -> Bool) -> StateT IfaceGetState Get Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets IfaceGetState -> Bool
useLEB128
  if Bool
c then Get a
f else Get a
g

getWord32be :: Get Word32
getWord32be :: Get Word32
getWord32be = Get Word32 -> Get Word32 -> Get Word32
forall a. Get a -> Get a -> Get a
uleb Get Word32
forall a. (Integral a, FiniteBits a) => Get a
getULEB128 (Get Word32 -> Get Word32
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Get Word32
G.getWord32be)

getWord64be :: Get Word64
getWord64be :: Get Word64
getWord64be = Get Word64 -> Get Word64 -> Get Word64
forall a. Get a -> Get a -> Get a
uleb Get Word64
forall a. (Integral a, FiniteBits a) => Get a
getULEB128 (Get Word64 -> Get Word64
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Get Word64
G.getWord64be)

getInt64be :: Get Int64
getInt64be :: Get Int64
getInt64be = Get Int64 -> Get Int64 -> Get Int64
forall a. Get a -> Get a -> Get a
uleb Get Int64
forall a. (Integral a, FiniteBits a) => Get a
getSLEB128 (Get Int64 -> Get Int64
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Get Int64
G.getInt64be)

lookAhead :: Get b -> Get b
lookAhead :: forall b. Get b -> Get b
lookAhead Get b
g = do
  IfaceGetState
s <- StateT IfaceGetState Get IfaceGetState
forall s (m :: * -> *). MonadState s m => m s
get
  Get b -> Get b
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Get b -> Get b) -> Get b -> Get b
forall a b. (a -> b) -> a -> b
$ Get b -> Get b
forall a. Get a -> Get a
G.lookAhead (Get b -> IfaceGetState -> Get b
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT Get b
g IfaceGetState
s)

getPtr :: Get Word32
getPtr :: Get Word32
getPtr = Get Word32 -> Get Word32
forall (m :: * -> *) a. Monad m => m a -> StateT IfaceGetState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Get Word32
G.getWord32be

type IsBoot = Bool

type ModuleName = ByteString

newtype List a = List
  { forall a. List a -> [a]
unList :: [a]
  } deriving newtype (List a -> ()
(List a -> ()) -> NFData (List a)
forall a. NFData a => List a -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall a. NFData a => List a -> ()
rnf :: List a -> ()
NFData, Int -> List a -> ShowS
[List a] -> ShowS
List a -> String
(Int -> List a -> ShowS)
-> (List a -> String) -> ([List a] -> ShowS) -> Show (List a)
forall a. Show a => Int -> List a -> ShowS
forall a. Show a => [List a] -> ShowS
forall a. Show a => List a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> List a -> ShowS
showsPrec :: Int -> List a -> ShowS
$cshow :: forall a. Show a => List a -> String
show :: List a -> String
$cshowList :: forall a. Show a => [List a] -> ShowS
showList :: [List a] -> ShowS
Show)

newtype Dictionary = Dictionary
  { Dictionary -> Vector ByteString
unDictionary :: V.Vector ByteString
  } deriving newtype (Dictionary -> ()
(Dictionary -> ()) -> NFData Dictionary
forall a. (a -> ()) -> NFData a
$crnf :: Dictionary -> ()
rnf :: Dictionary -> ()
NFData, Int -> Dictionary -> ShowS
[Dictionary] -> ShowS
Dictionary -> String
(Int -> Dictionary -> ShowS)
-> (Dictionary -> String)
-> ([Dictionary] -> ShowS)
-> Show Dictionary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Dictionary -> ShowS
showsPrec :: Int -> Dictionary -> ShowS
$cshow :: Dictionary -> String
show :: Dictionary -> String
$cshowList :: [Dictionary] -> ShowS
showList :: [Dictionary] -> ShowS
Show)

newtype Module = Module
  { Module -> ByteString
unModule :: ModuleName
  } deriving newtype (Module -> ()
(Module -> ()) -> NFData Module
forall a. (a -> ()) -> NFData a
$crnf :: Module -> ()
rnf :: Module -> ()
NFData, Int -> Module -> ShowS
[Module] -> ShowS
Module -> String
(Int -> Module -> ShowS)
-> (Module -> String) -> ([Module] -> ShowS) -> Show Module
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Module -> ShowS
showsPrec :: Int -> Module -> ShowS
$cshow :: Module -> String
show :: Module -> String
$cshowList :: [Module] -> ShowS
showList :: [Module] -> ShowS
Show)

newtype Usage = Usage
  { Usage -> String
unUsage :: FilePath
  } deriving newtype (Usage -> ()
(Usage -> ()) -> NFData Usage
forall a. (a -> ()) -> NFData a
$crnf :: Usage -> ()
rnf :: Usage -> ()
NFData, Int -> Usage -> ShowS
[Usage] -> ShowS
Usage -> String
(Int -> Usage -> ShowS)
-> (Usage -> String) -> ([Usage] -> ShowS) -> Show Usage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Usage -> ShowS
showsPrec :: Int -> Usage -> ShowS
$cshow :: Usage -> String
show :: Usage -> String
$cshowList :: [Usage] -> ShowS
showList :: [Usage] -> ShowS
Show)

data Dependencies = Dependencies
  { Dependencies -> List (ByteString, Bool)
dmods    :: List (ModuleName, IsBoot)
  , Dependencies -> List (ByteString, Bool)
dpkgs    :: List (ModuleName, Bool)
  , Dependencies -> List Module
dorphs   :: List Module
  , Dependencies -> List Module
dfinsts  :: List Module
  , Dependencies -> List ByteString
dplugins :: List ModuleName
  } deriving ((forall x. Dependencies -> Rep Dependencies x)
-> (forall x. Rep Dependencies x -> Dependencies)
-> Generic Dependencies
forall x. Rep Dependencies x -> Dependencies
forall x. Dependencies -> Rep Dependencies x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Dependencies -> Rep Dependencies x
from :: forall x. Dependencies -> Rep Dependencies x
$cto :: forall x. Rep Dependencies x -> Dependencies
to :: forall x. Rep Dependencies x -> Dependencies
Generic, Int -> Dependencies -> ShowS
[Dependencies] -> ShowS
Dependencies -> String
(Int -> Dependencies -> ShowS)
-> (Dependencies -> String)
-> ([Dependencies] -> ShowS)
-> Show Dependencies
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Dependencies -> ShowS
showsPrec :: Int -> Dependencies -> ShowS
$cshow :: Dependencies -> String
show :: Dependencies -> String
$cshowList :: [Dependencies] -> ShowS
showList :: [Dependencies] -> ShowS
Show)

instance NFData Dependencies

data Interface = Interface
  { Interface -> Dependencies
deps  :: Dependencies
  , Interface -> List Usage
usage :: List Usage
  } deriving ((forall x. Interface -> Rep Interface x)
-> (forall x. Rep Interface x -> Interface) -> Generic Interface
forall x. Rep Interface x -> Interface
forall x. Interface -> Rep Interface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Interface -> Rep Interface x
from :: forall x. Interface -> Rep Interface x
$cto :: forall x. Rep Interface x -> Interface
to :: forall x. Rep Interface x -> Interface
Generic, Int -> Interface -> ShowS
[Interface] -> ShowS
Interface -> String
(Int -> Interface -> ShowS)
-> (Interface -> String)
-> ([Interface] -> ShowS)
-> Show Interface
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Interface -> ShowS
showsPrec :: Int -> Interface -> ShowS
$cshow :: Interface -> String
show :: Interface -> String
$cshowList :: [Interface] -> ShowS
showList :: [Interface] -> ShowS
Show)

instance NFData Interface

-- | Read a block prefixed with its length

withBlockPrefix :: Get a -> Get a
withBlockPrefix :: forall b. Get b -> Get b
withBlockPrefix Get a
f = Get Word32
getPtr Get Word32 -> Get a -> Get a
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get a
f

getBool :: Get Bool
getBool :: StateT IfaceGetState Get Bool
getBool = Int -> Bool
forall a. Enum a => Int -> a
toEnum (Int -> Bool) -> (Word8 -> Int) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Bool) -> Get Word8 -> StateT IfaceGetState Get Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8

getString :: Get String
getString :: Get String
getString = (Word32 -> Char) -> [Word32] -> String
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Char
chr (Int -> Char) -> (Word32 -> Int) -> Word32 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) ([Word32] -> String)
-> (List Word32 -> [Word32]) -> List Word32 -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List Word32 -> [Word32]
forall a. List a -> [a]
unList (List Word32 -> String)
-> StateT IfaceGetState Get (List Word32) -> Get String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32 -> StateT IfaceGetState Get (List Word32)
forall a. Get a -> Get (List a)
getList Get Word32
getWord32be

getMaybe :: Get a -> Get (Maybe a)
getMaybe :: forall a. Get a -> Get (Maybe a)
getMaybe Get a
f = StateT IfaceGetState Get (Maybe a)
-> StateT IfaceGetState Get (Maybe a)
-> Bool
-> StateT IfaceGetState Get (Maybe a)
forall a. a -> a -> Bool -> a
bool (Maybe a -> StateT IfaceGetState Get (Maybe a)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing) (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Get a -> StateT IfaceGetState Get (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get a
f) (Bool -> StateT IfaceGetState Get (Maybe a))
-> StateT IfaceGetState Get Bool
-> StateT IfaceGetState Get (Maybe a)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< StateT IfaceGetState Get Bool
getBool

getList :: Get a -> Get (List a)
getList :: forall a. Get a -> Get (List a)
getList Get a
f = do
  Bool
use_uleb <- (IfaceGetState -> Bool) -> StateT IfaceGetState Get Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets IfaceGetState -> Bool
useLEB128
  if Bool
use_uleb
    then do
      Int64
l <- (Get Int64
forall a. (Integral a, FiniteBits a) => Get a
getSLEB128 :: Get Int64)
      [a] -> List a
forall a. [a] -> List a
List ([a] -> List a) -> StateT IfaceGetState Get [a] -> Get (List a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get a -> StateT IfaceGetState Get [a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
l) Get a
f
    else do
      Word8
i <- Get Word8
getWord8
      Word32
l <-
        if Word8
i Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0xff
          then Get Word32
getWord32be
          else Word32 -> Get Word32
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
i :: Word32)
      [a] -> List a
forall a. [a] -> List a
List ([a] -> List a) -> StateT IfaceGetState Get [a] -> Get (List a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get a -> StateT IfaceGetState Get [a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
l) Get a
f

getTuple :: Get a -> Get b -> Get (a, b)
getTuple :: forall a b. Get a -> Get b -> Get (a, b)
getTuple Get a
f Get b
g = (,) (a -> b -> (a, b))
-> Get a -> StateT IfaceGetState Get (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get a
f StateT IfaceGetState Get (b -> (a, b))
-> Get b -> StateT IfaceGetState Get (a, b)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get b
g

getByteStringSized :: Get ByteString
getByteStringSized :: Get ByteString
getByteStringSized = do
  Int64
size <- Get Int64
getInt64be
  Int -> Get ByteString
getByteString (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
size)

getDictionary :: Int -> Get Dictionary
getDictionary :: Int -> Get Dictionary
getDictionary Int
ptr = do
  Int64
offset <- Get Int64
bytesRead
  Int -> Get ()
skip (Int -> Get ()) -> Int -> Get ()
forall a b. (a -> b) -> a -> b
$ Int
ptr Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
offset
  Int
size <- Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> Get Int64 -> StateT IfaceGetState Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int64
getInt64be
  String -> Get ()
traceGet (String
"Dictionary size: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
size)
  Dictionary
dict <- Vector ByteString -> Dictionary
Dictionary (Vector ByteString -> Dictionary)
-> StateT IfaceGetState Get (Vector ByteString) -> Get Dictionary
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> Get ByteString -> StateT IfaceGetState Get (Vector ByteString)
forall (m :: * -> *) a. Monad m => Int -> m a -> m (Vector a)
V.replicateM Int
size Get ByteString
getByteStringSized
  String -> Get ()
traceGet (String
"Dictionary: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Dictionary -> String
forall a. Show a => a -> String
show Dictionary
dict)
  Dictionary -> Get Dictionary
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return Dictionary
dict

-- | Get a FastString

--

-- FastStrings are stored in a global FastString table and only the index (a

-- Word32be) is stored at the expected position.

getCachedBS :: Dictionary -> Get ByteString
getCachedBS :: Dictionary -> Get ByteString
getCachedBS Dictionary
d = Word32 -> Get ByteString
forall {a} {f :: * -> *}.
(Integral a, MonadFail f, Show a) =>
a -> f ByteString
go (Word32 -> Get ByteString) -> Get Word32 -> Get ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Get Word32 -> Get Word32
forall a. Show a => String -> Get a -> Get a
traceShow String
"Dict index:" Get Word32
getWord32be
 where
  go :: a -> f ByteString
go a
i =
    case Dictionary -> Vector ByteString
unDictionary Dictionary
d Vector ByteString -> Int -> Maybe ByteString
forall a. Vector a -> Int -> Maybe a
V.!? a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i of
      Just ByteString
bs -> ByteString -> f ByteString
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
bs
      Maybe ByteString
Nothing -> String -> f ByteString
forall a. String -> f a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> f ByteString) -> String -> f ByteString
forall a b. (a -> b) -> a -> b
$ String
"Invalid dictionary index: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
i

-- | Get Fingerprint

getFP' :: Get String
getFP' :: Get String
getFP' = do
  Word64
x <- Get Word64
getWord64be
  Word64
y <- Get Word64
getWord64be
  String -> Get String
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x (Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
y String
""))

getFP :: Get ()
getFP :: Get ()
getFP = Get String -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get String
getFP'

getInterface721 :: Dictionary -> Get Interface
getInterface721 :: Dictionary -> Get Interface
getInterface721 Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Int -> Get () -> Get ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
2 Get ()
getFP
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Dependencies -> List Usage -> Interface
Interface (Dependencies -> List Usage -> Interface)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get (List Usage -> Interface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT IfaceGetState Get Dependencies
getDependencies StateT IfaceGetState Get (List Usage -> Interface)
-> StateT IfaceGetState Get (List Usage) -> Get Interface
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT IfaceGetState Get (List Usage)
getUsage
 where
  getModule :: StateT IfaceGetState Get Module
getModule = Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString
-> StateT IfaceGetState Get Module
-> StateT IfaceGetState Get Module
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dictionary -> Get ByteString
getCachedBS Dictionary
d)
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$
    List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies (List (ByteString, Bool)
 -> List (ByteString, Bool)
 -> List Module
 -> List Module
 -> List ByteString
 -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List (ByteString, Bool)
      -> List Module -> List Module -> List ByteString -> Dependencies)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List (ByteString, Bool)
   -> List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List Module -> List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT
     IfaceGetState Get (List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT
  IfaceGetState Get (List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT IfaceGetState Get (List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get (List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List ByteString)
-> StateT IfaceGetState Get Dependencies
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    List ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ByteString] -> List ByteString
forall a. [a] -> List a
List [])
  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
1 ->
             Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (Maybe ())
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get Word8
getWord8 Get Word8 -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Dictionary -> Get ByteString
getCachedBS Dictionary
d) Get ()
getFP) StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

getInterface741 :: Dictionary -> Get Interface
getInterface741 :: Dictionary -> Get Interface
getInterface741 Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Int -> Get () -> Get ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
3 Get ()
getFP
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Dependencies -> List Usage -> Interface
Interface (Dependencies -> List Usage -> Interface)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get (List Usage -> Interface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT IfaceGetState Get Dependencies
getDependencies StateT IfaceGetState Get (List Usage -> Interface)
-> StateT IfaceGetState Get (List Usage) -> Get Interface
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT IfaceGetState Get (List Usage)
getUsage
 where
  getModule :: StateT IfaceGetState Get Module
getModule = Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString
-> StateT IfaceGetState Get Module
-> StateT IfaceGetState Get Module
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dictionary -> Get ByteString
getCachedBS Dictionary
d)
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$
    List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies (List (ByteString, Bool)
 -> List (ByteString, Bool)
 -> List Module
 -> List Module
 -> List ByteString
 -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List (ByteString, Bool)
      -> List Module -> List Module -> List ByteString -> Dependencies)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List (ByteString, Bool)
   -> List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List Module -> List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT
     IfaceGetState Get (List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT
  IfaceGetState Get (List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT IfaceGetState Get (List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get (List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List ByteString)
-> StateT IfaceGetState Get Dependencies
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    List ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ByteString] -> List ByteString
forall a. [a] -> List a
List [])
  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
1 ->
             Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (Maybe ())
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get Word8
getWord8 Get Word8 -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Dictionary -> Get ByteString
getCachedBS Dictionary
d) Get ()
getFP) StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
2 -> Usage -> Maybe Usage
forall a. a -> Maybe a
Just (Usage -> Maybe Usage)
-> (String -> Usage) -> String -> Maybe Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Usage
Usage (String -> Maybe Usage) -> Get String -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
getString Get (Maybe Usage) -> Get Word64 -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get Word64
getWord64be Get (Maybe Usage) -> Get Word64 -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get Word64
getWord64be
        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

getInterface761 :: Dictionary -> Get Interface
getInterface761 :: Dictionary -> Get Interface
getInterface761 Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Int -> Get () -> Get ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
3 Get ()
getFP
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Dependencies -> List Usage -> Interface
Interface (Dependencies -> List Usage -> Interface)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get (List Usage -> Interface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT IfaceGetState Get Dependencies
getDependencies StateT IfaceGetState Get (List Usage -> Interface)
-> StateT IfaceGetState Get (List Usage) -> Get Interface
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT IfaceGetState Get (List Usage)
getUsage
 where
  getModule :: StateT IfaceGetState Get Module
getModule = Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString
-> StateT IfaceGetState Get Module
-> StateT IfaceGetState Get Module
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dictionary -> Get ByteString
getCachedBS Dictionary
d)
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$
    List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies (List (ByteString, Bool)
 -> List (ByteString, Bool)
 -> List Module
 -> List Module
 -> List ByteString
 -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List (ByteString, Bool)
      -> List Module -> List Module -> List ByteString -> Dependencies)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List (ByteString, Bool)
   -> List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List Module -> List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT
     IfaceGetState Get (List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT
  IfaceGetState Get (List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT IfaceGetState Get (List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get (List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List ByteString)
-> StateT IfaceGetState Get Dependencies
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    List ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ByteString] -> List ByteString
forall a. [a] -> List a
List [])
  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
1 ->
             Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (Maybe ())
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get Word8
getWord8 Get Word8 -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Dictionary -> Get ByteString
getCachedBS Dictionary
d) Get ()
getFP) StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
2 -> Usage -> Maybe Usage
forall a. a -> Maybe a
Just (Usage -> Maybe Usage)
-> (String -> Usage) -> String -> Maybe Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Usage
Usage (String -> Maybe Usage) -> Get String -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
getString Get (Maybe Usage) -> Get Word64 -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get Word64
getWord64be Get (Maybe Usage) -> Get Word64 -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get Word64
getWord64be
        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

getInterface781 :: Dictionary -> Get Interface
getInterface781 :: Dictionary -> Get Interface
getInterface781 Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Int -> Get () -> Get ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
3 Get ()
getFP
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Dependencies -> List Usage -> Interface
Interface (Dependencies -> List Usage -> Interface)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get (List Usage -> Interface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT IfaceGetState Get Dependencies
getDependencies StateT IfaceGetState Get (List Usage -> Interface)
-> StateT IfaceGetState Get (List Usage) -> Get Interface
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT IfaceGetState Get (List Usage)
getUsage
 where
  getModule :: StateT IfaceGetState Get Module
getModule = Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString
-> StateT IfaceGetState Get Module
-> StateT IfaceGetState Get Module
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dictionary -> Get ByteString
getCachedBS Dictionary
d)
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$
    List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies (List (ByteString, Bool)
 -> List (ByteString, Bool)
 -> List Module
 -> List Module
 -> List ByteString
 -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List (ByteString, Bool)
      -> List Module -> List Module -> List ByteString -> Dependencies)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List (ByteString, Bool)
   -> List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List Module -> List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT
     IfaceGetState Get (List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT
  IfaceGetState Get (List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT IfaceGetState Get (List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get (List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List ByteString)
-> StateT IfaceGetState Get Dependencies
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    List ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ByteString] -> List ByteString
forall a. [a] -> List a
List [])
  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
1 ->
             Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (Maybe ())
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get Word8
getWord8 Get Word8 -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Dictionary -> Get ByteString
getCachedBS Dictionary
d) Get ()
getFP) StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
2 -> Usage -> Maybe Usage
forall a. a -> Maybe a
Just (Usage -> Maybe Usage)
-> (String -> Usage) -> String -> Maybe Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Usage
Usage (String -> Maybe Usage) -> Get String -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
getString Get (Maybe Usage) -> Get () -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get ()
getFP
        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

getInterface801 :: Dictionary -> Get Interface
getInterface801 :: Dictionary -> Get Interface
getInterface801 Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule
  Get Word8 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word8
getWord8
  Int -> Get () -> Get ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
3 Get ()
getFP
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Dependencies -> List Usage -> Interface
Interface (Dependencies -> List Usage -> Interface)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get (List Usage -> Interface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT IfaceGetState Get Dependencies
getDependencies StateT IfaceGetState Get (List Usage -> Interface)
-> StateT IfaceGetState Get (List Usage) -> Get Interface
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT IfaceGetState Get (List Usage)
getUsage
 where
  getModule :: StateT IfaceGetState Get Module
getModule = Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString
-> StateT IfaceGetState Get Module
-> StateT IfaceGetState Get Module
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dictionary -> Get ByteString
getCachedBS Dictionary
d)
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$
    List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies (List (ByteString, Bool)
 -> List (ByteString, Bool)
 -> List Module
 -> List Module
 -> List ByteString
 -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List (ByteString, Bool)
      -> List Module -> List Module -> List ByteString -> Dependencies)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List (ByteString, Bool)
   -> List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List Module -> List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT
     IfaceGetState Get (List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT
  IfaceGetState Get (List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT IfaceGetState Get (List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get (List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List ByteString)
-> StateT IfaceGetState Get Dependencies
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    List ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ByteString] -> List ByteString
forall a. [a] -> List a
List [])
  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
1 ->
             Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (Maybe ())
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get Word8
getWord8 Get Word8 -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Dictionary -> Get ByteString
getCachedBS Dictionary
d) Get ()
getFP) StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
2 -> Usage -> Maybe Usage
forall a. a -> Maybe a
Just (Usage -> Maybe Usage)
-> (String -> Usage) -> String -> Maybe Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Usage
Usage (String -> Maybe Usage) -> Get String -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
getString Get (Maybe Usage) -> Get () -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get ()
getFP
        Word8
3 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get () -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

getInterface821 :: Dictionary -> Get Interface
getInterface821 :: Dictionary -> Get Interface
getInterface821 Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule
  StateT IfaceGetState Get (Maybe Module) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (Maybe Module) -> Get ())
-> StateT IfaceGetState Get (Maybe Module) -> Get ()
forall a b. (a -> b) -> a -> b
$ StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (Maybe Module)
forall a. Get a -> Get (Maybe a)
getMaybe StateT IfaceGetState Get Module
getModule
  Get Word8 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word8
getWord8
  Int -> Get () -> Get ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
3 Get ()
getFP
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Dependencies -> List Usage -> Interface
Interface (Dependencies -> List Usage -> Interface)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get (List Usage -> Interface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT IfaceGetState Get Dependencies
getDependencies StateT IfaceGetState Get (List Usage -> Interface)
-> StateT IfaceGetState Get (List Usage) -> Get Interface
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT IfaceGetState Get (List Usage)
getUsage
 where
  getModule :: StateT IfaceGetState Get Module
getModule = do
    Word8
idType <- Get Word8
getWord8
    case Word8
idType of
      Word8
0 -> Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Get ByteString -> Get ()) -> Get ByteString -> Get ()
forall a b. (a -> b) -> a -> b
$ Dictionary -> Get ByteString
getCachedBS Dictionary
d
      Word8
_ ->
          StateT IfaceGetState Get (List (ByteString, Module)) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (List (ByteString, Module)) -> Get ())
-> StateT IfaceGetState Get (List (ByteString, Module)) -> Get ()
forall a b. (a -> b) -> a -> b
$
          Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString
-> StateT IfaceGetState Get (List (ByteString, Module))
-> StateT IfaceGetState Get (List (ByteString, Module))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get (ByteString, Module)
-> StateT IfaceGetState Get (List (ByteString, Module))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Module -> Get (ByteString, Module)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Module
getModule)
    ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dictionary -> Get ByteString
getCachedBS Dictionary
d
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$
    List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies (List (ByteString, Bool)
 -> List (ByteString, Bool)
 -> List Module
 -> List Module
 -> List ByteString
 -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List (ByteString, Bool)
      -> List Module -> List Module -> List ByteString -> Dependencies)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List (ByteString, Bool)
   -> List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List Module -> List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT
     IfaceGetState Get (List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT
  IfaceGetState Get (List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT IfaceGetState Get (List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get (List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List ByteString)
-> StateT IfaceGetState Get Dependencies
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    List ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ByteString] -> List ByteString
forall a. [a] -> List a
List [])
  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
1 ->
             Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (Maybe ())
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get Word8
getWord8 Get Word8 -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Dictionary -> Get ByteString
getCachedBS Dictionary
d) Get ()
getFP) StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
2 -> Usage -> Maybe Usage
forall a. a -> Maybe a
Just (Usage -> Maybe Usage)
-> (String -> Usage) -> String -> Maybe Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Usage
Usage (String -> Maybe Usage) -> Get String -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
getString Get (Maybe Usage) -> Get () -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get ()
getFP
        Word8
3 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get () -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

getInterface841 :: Dictionary -> Get Interface
getInterface841 :: Dictionary -> Get Interface
getInterface841 Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule
  StateT IfaceGetState Get (Maybe Module) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (Maybe Module) -> Get ())
-> StateT IfaceGetState Get (Maybe Module) -> Get ()
forall a b. (a -> b) -> a -> b
$ StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (Maybe Module)
forall a. Get a -> Get (Maybe a)
getMaybe StateT IfaceGetState Get Module
getModule
  Get Word8 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word8
getWord8
  Int -> Get () -> Get ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
5 Get ()
getFP
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Dependencies -> List Usage -> Interface
Interface (Dependencies -> List Usage -> Interface)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get (List Usage -> Interface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT IfaceGetState Get Dependencies
getDependencies StateT IfaceGetState Get (List Usage -> Interface)
-> StateT IfaceGetState Get (List Usage) -> Get Interface
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT IfaceGetState Get (List Usage)
getUsage
 where
  getModule :: StateT IfaceGetState Get Module
getModule = do
    Word8
idType <- Get Word8
getWord8
    case Word8
idType of
      Word8
0 -> Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Get ByteString -> Get ()) -> Get ByteString -> Get ()
forall a b. (a -> b) -> a -> b
$ Dictionary -> Get ByteString
getCachedBS Dictionary
d
      Word8
_ ->
          StateT IfaceGetState Get (List (ByteString, Module)) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (List (ByteString, Module)) -> Get ())
-> StateT IfaceGetState Get (List (ByteString, Module)) -> Get ()
forall a b. (a -> b) -> a -> b
$
          Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString
-> StateT IfaceGetState Get (List (ByteString, Module))
-> StateT IfaceGetState Get (List (ByteString, Module))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get (ByteString, Module)
-> StateT IfaceGetState Get (List (ByteString, Module))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Module -> Get (ByteString, Module)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Module
getModule)
    ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dictionary -> Get ByteString
getCachedBS Dictionary
d
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$
    List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies (List (ByteString, Bool)
 -> List (ByteString, Bool)
 -> List Module
 -> List Module
 -> List ByteString
 -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List (ByteString, Bool)
      -> List Module -> List Module -> List ByteString -> Dependencies)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List (ByteString, Bool)
   -> List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List Module -> List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT
     IfaceGetState Get (List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT
  IfaceGetState Get (List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT IfaceGetState Get (List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get (List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List ByteString)
-> StateT IfaceGetState Get Dependencies
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    List ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([ByteString] -> List ByteString
forall a. [a] -> List a
List [])
  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
1 ->
             Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (Maybe ())
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get Word8
getWord8 Get Word8 -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Dictionary -> Get ByteString
getCachedBS Dictionary
d) Get ()
getFP) StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
2 -> Usage -> Maybe Usage
forall a. a -> Maybe a
Just (Usage -> Maybe Usage)
-> (String -> Usage) -> String -> Maybe Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Usage
Usage (String -> Maybe Usage) -> Get String -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
getString Get (Maybe Usage) -> Get () -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get ()
getFP
        Word8
3 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get () -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

getInterface861 :: Dictionary -> Get Interface
getInterface861 :: Dictionary -> Get Interface
getInterface861 Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule
  StateT IfaceGetState Get (Maybe Module) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (Maybe Module) -> Get ())
-> StateT IfaceGetState Get (Maybe Module) -> Get ()
forall a b. (a -> b) -> a -> b
$ StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (Maybe Module)
forall a. Get a -> Get (Maybe a)
getMaybe StateT IfaceGetState Get Module
getModule
  Get Word8 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word8
getWord8
  Int -> Get () -> Get ()
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
6 Get ()
getFP
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool
  Dependencies -> List Usage -> Interface
Interface (Dependencies -> List Usage -> Interface)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get (List Usage -> Interface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT IfaceGetState Get Dependencies
getDependencies StateT IfaceGetState Get (List Usage -> Interface)
-> StateT IfaceGetState Get (List Usage) -> Get Interface
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT IfaceGetState Get (List Usage)
getUsage
 where
  getModule :: StateT IfaceGetState Get Module
getModule = do
    Word8
idType <- Get Word8
getWord8
    case Word8
idType of
      Word8
0 -> Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Get ByteString -> Get ()) -> Get ByteString -> Get ()
forall a b. (a -> b) -> a -> b
$ Dictionary -> Get ByteString
getCachedBS Dictionary
d
      Word8
_ ->
           StateT IfaceGetState Get (List (ByteString, Module)) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (List (ByteString, Module)) -> Get ())
-> StateT IfaceGetState Get (List (ByteString, Module)) -> Get ()
forall a b. (a -> b) -> a -> b
$
           Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString
-> StateT IfaceGetState Get (List (ByteString, Module))
-> StateT IfaceGetState Get (List (ByteString, Module))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get (ByteString, Module)
-> StateT IfaceGetState Get (List (ByteString, Module))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Module -> Get (ByteString, Module)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Module
getModule)
    ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dictionary -> Get ByteString
getCachedBS Dictionary
d
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$
    List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies (List (ByteString, Bool)
 -> List (ByteString, Bool)
 -> List Module
 -> List Module
 -> List ByteString
 -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List (ByteString, Bool)
      -> List Module -> List Module -> List ByteString -> Dependencies)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List (ByteString, Bool)
   -> List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT
     IfaceGetState
     Get
     (List Module -> List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Dictionary -> Get ByteString
getCachedBS Dictionary
d) StateT IfaceGetState Get Bool
getBool) StateT
  IfaceGetState
  Get
  (List Module -> List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT
     IfaceGetState Get (List Module -> List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT
  IfaceGetState Get (List Module -> List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List Module)
-> StateT IfaceGetState Get (List ByteString -> Dependencies)
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get (List ByteString -> Dependencies)
-> StateT IfaceGetState Get (List ByteString)
-> StateT IfaceGetState Get Dependencies
forall a b.
StateT IfaceGetState Get (a -> b)
-> StateT IfaceGetState Get a -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
    Get ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. Get a -> Get (List a)
getList (Dictionary -> Get ByteString
getCachedBS Dictionary
d)
  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
1 ->
             Dictionary -> Get ByteString
getCachedBS Dictionary
d Get ByteString -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get ()
-> StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (Maybe ())
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP StateT IfaceGetState Get (Maybe ())
-> StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get Word8
getWord8 Get Word8 -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Dictionary -> Get ByteString
getCachedBS Dictionary
d) Get ()
getFP) StateT IfaceGetState Get (List (ByteString, ()))
-> StateT IfaceGetState Get Bool -> StateT IfaceGetState Get Bool
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             StateT IfaceGetState Get Bool
getBool StateT IfaceGetState Get Bool -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
2 -> Usage -> Maybe Usage
forall a. a -> Maybe a
Just (Usage -> Maybe Usage)
-> (String -> Usage) -> String -> Maybe Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Usage
Usage (String -> Maybe Usage) -> Get String -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get String
getString Get (Maybe Usage) -> Get () -> Get (Maybe Usage)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Get ()
getFP
        Word8
3 -> StateT IfaceGetState Get Module
getModule StateT IfaceGetState Get Module -> Get () -> Get ()
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ()
getFP Get () -> Maybe Usage -> Get (Maybe Usage)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Maybe Usage
forall a. Maybe a
Nothing
        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

getInterfaceRecent :: IfaceVersion -> Dictionary -> Get Interface
getInterfaceRecent :: IfaceVersion -> Dictionary -> Get Interface
getInterfaceRecent IfaceVersion
version Dictionary
d = do
  StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get Module -> Get ())
-> StateT IfaceGetState Get Module -> Get ()
forall a b. (a -> b) -> a -> b
$ String
-> StateT IfaceGetState Get Module
-> StateT IfaceGetState Get Module
forall a. Show a => String -> Get a -> Get a
traceShow String
"Module:" StateT IfaceGetState Get Module
getModule
  StateT IfaceGetState Get (Maybe Module) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (Maybe Module) -> Get ())
-> StateT IfaceGetState Get (Maybe Module) -> Get ()
forall a b. (a -> b) -> a -> b
$ String
-> StateT IfaceGetState Get (Maybe Module)
-> StateT IfaceGetState Get (Maybe Module)
forall a. Show a => String -> Get a -> Get a
traceShow String
"Sig:" (StateT IfaceGetState Get (Maybe Module)
 -> StateT IfaceGetState Get (Maybe Module))
-> StateT IfaceGetState Get (Maybe Module)
-> StateT IfaceGetState Get (Maybe Module)
forall a b. (a -> b) -> a -> b
$ StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (Maybe Module)
forall a. Get a -> Get (Maybe a)
getMaybe StateT IfaceGetState Get Module
getModule
  Get Word8 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word8
getWord8 -- hsc_src

  Get ()
getFP         -- iface_hash

  Get ()
getFP         -- mod_hash

  Get ()
getFP         -- flag_hash

  Get ()
getFP         -- opt_hash

  Get ()
getFP         -- hpc_hash

  Get ()
getFP         -- plugin_hash

  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool  -- orphan

  StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool  -- hasFamInsts

  Dependencies
ddeps  <- String
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a. Show a => String -> Get a -> Get a
traceShow String
"Dependencies:" StateT IfaceGetState Get Dependencies
getDependencies
  List Usage
dusage <- String
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a. Show a => String -> Get a -> Get a
traceShow String
"Usage:"        StateT IfaceGetState Get (List Usage)
getUsage
  Interface -> Get Interface
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Dependencies -> List Usage -> Interface
Interface Dependencies
ddeps List Usage
dusage)
 where
  since :: IfaceVersion -> f () -> f ()
since IfaceVersion
v = Bool -> f () -> f ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (IfaceVersion
version IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
v)

  getFastString :: Get ByteString
getFastString = Dictionary -> Get ByteString
getCachedBS Dictionary
d

  getModule :: StateT IfaceGetState Get Module
getModule = do
    Word8
idType <- String -> Get Word8 -> Get Word8
forall a. Show a => String -> Get a -> Get a
traceShow String
"Unit type:" Get Word8
getWord8
    case Word8
idType of
      Word8
0 -> Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ByteString
getFastString
      Word8
1 ->
           StateT IfaceGetState Get (List (ByteString, Module)) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (List (ByteString, Module)) -> Get ())
-> StateT IfaceGetState Get (List (ByteString, Module)) -> Get ()
forall a b. (a -> b) -> a -> b
$
           Get ByteString
getFastString Get ByteString
-> StateT IfaceGetState Get (List (ByteString, Module))
-> StateT IfaceGetState Get (List (ByteString, Module))
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get (ByteString, Module)
-> StateT IfaceGetState Get (List (ByteString, Module))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Module -> Get (ByteString, Module)
forall a b. Get a -> Get b -> Get (a, b)
getTuple Get ByteString
getFastString StateT IfaceGetState Get Module
getModule)
      Word8
_ -> String -> Get ()
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get ()) -> String -> Get ()
forall a b. (a -> b) -> a -> b
$ String
"Invalid unit type: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
idType
    ByteString -> Module
Module (ByteString -> Module)
-> Get ByteString -> StateT IfaceGetState Get Module
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
getFastString
  getDependencies :: StateT IfaceGetState Get Dependencies
getDependencies =
    StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get Dependencies
 -> StateT IfaceGetState Get Dependencies)
-> StateT IfaceGetState Get Dependencies
-> StateT IfaceGetState Get Dependencies
forall a b. (a -> b) -> a -> b
$ do
      if IfaceVersion
version IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
V9041
        then do
          -- warning: transitive dependencies are no longer stored,

          -- only direct imports!

          -- Modules are now prefixed with their UnitId (should have been

          -- ModuleWithIsBoot...)

          List (ByteString, Bool)
direct_mods <- String
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Show a => String -> Get a -> Get a
traceShow String
"direct_mods:" (StateT IfaceGetState Get (List (ByteString, Bool))
 -> StateT IfaceGetState Get (List (ByteString, Bool)))
-> StateT IfaceGetState Get (List (ByteString, Bool))
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a b. (a -> b) -> a -> b
$
            Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
getFastString Get ByteString -> Get (ByteString, Bool) -> Get (ByteString, Bool)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple Get ByteString
getFastString StateT IfaceGetState Get Bool
getBool)
          List ByteString
direct_pkgs <- Get ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. Get a -> Get (List a)
getList Get ByteString
getFastString

          -- plugin packages are now stored separately

          List ByteString
plugin_pkgs <- Get ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. Get a -> Get (List a)
getList Get ByteString
getFastString
          let all_pkgs :: [ByteString]
all_pkgs = List ByteString -> [ByteString]
forall a. List a -> [a]
unList List ByteString
plugin_pkgs [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ List ByteString -> [ByteString]
forall a. List a -> [a]
unList List ByteString
direct_pkgs

          -- instead of a trust bool for each unit, we have an additional

          -- list of trusted units (transitive)

          List ByteString
trusted_pkgs <- Get ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. Get a -> Get (List a)
getList Get ByteString
getFastString
          let trusted :: ByteString -> Bool
trusted ByteString
u = ByteString
u ByteString -> [ByteString] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` List ByteString -> [ByteString]
forall a. List a -> [a]
unList List ByteString
trusted_pkgs
              all_pkgs_trust :: List (ByteString, Bool)
all_pkgs_trust = [(ByteString, Bool)] -> List (ByteString, Bool)
forall a. [a] -> List a
List ([ByteString] -> [Bool] -> [(ByteString, Bool)]
forall a b. [a] -> [b] -> [(a, b)]
zip [ByteString]
all_pkgs ((ByteString -> Bool) -> [ByteString] -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> Bool
trusted [ByteString]
all_pkgs))

          -- these are new

          List Module
_sig_mods  <- StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule
          List (ByteString, Bool)
_boot_mods <- Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
getFastString Get ByteString -> Get (ByteString, Bool) -> Get (ByteString, Bool)
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple Get ByteString
getFastString StateT IfaceGetState Get Bool
getBool)

          List Module
dep_orphs  <- StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule
          List Module
dep_finsts <- StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule

          -- plugin names are no longer stored here

          let dep_plgins :: List a
dep_plgins = [a] -> List a
forall a. [a] -> List a
List []

          Dependencies -> StateT IfaceGetState Get Dependencies
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies List (ByteString, Bool)
direct_mods List (ByteString, Bool)
all_pkgs_trust List Module
dep_orphs List Module
dep_finsts List ByteString
forall {a}. List a
dep_plgins)
        else do
          List (ByteString, Bool)
dep_mods   <- Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple Get ByteString
getFastString StateT IfaceGetState Get Bool
getBool)
          List (ByteString, Bool)
dep_pkgs   <- Get (ByteString, Bool)
-> StateT IfaceGetState Get (List (ByteString, Bool))
forall a. Get a -> Get (List a)
getList (Get ByteString
-> StateT IfaceGetState Get Bool -> Get (ByteString, Bool)
forall a b. Get a -> Get b -> Get (a, b)
getTuple Get ByteString
getFastString StateT IfaceGetState Get Bool
getBool)
          List Module
dep_orphs  <- StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule
          List Module
dep_finsts <- StateT IfaceGetState Get Module
-> StateT IfaceGetState Get (List Module)
forall a. Get a -> Get (List a)
getList StateT IfaceGetState Get Module
getModule
          List ByteString
dep_plgins <- Get ByteString -> StateT IfaceGetState Get (List ByteString)
forall a. Get a -> Get (List a)
getList Get ByteString
getFastString
          Dependencies -> StateT IfaceGetState Get Dependencies
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (List (ByteString, Bool)
-> List (ByteString, Bool)
-> List Module
-> List Module
-> List ByteString
-> Dependencies
Dependencies List (ByteString, Bool)
dep_mods List (ByteString, Bool)
dep_pkgs List Module
dep_orphs List Module
dep_finsts List ByteString
dep_plgins)

  getUsage :: StateT IfaceGetState Get (List Usage)
getUsage = StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall b. Get b -> Get b
withBlockPrefix (StateT IfaceGetState Get (List Usage)
 -> StateT IfaceGetState Get (List Usage))
-> StateT IfaceGetState Get (List Usage)
-> StateT IfaceGetState Get (List Usage)
forall a b. (a -> b) -> a -> b
$ [Usage] -> List Usage
forall a. [a] -> List a
List ([Usage] -> List Usage)
-> (List (Maybe Usage) -> [Usage])
-> List (Maybe Usage)
-> List Usage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Usage] -> [Usage]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Usage] -> [Usage])
-> (List (Maybe Usage) -> [Maybe Usage])
-> List (Maybe Usage)
-> [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List (Maybe Usage) -> [Maybe Usage]
forall a. List a -> [a]
unList (List (Maybe Usage) -> List Usage)
-> StateT IfaceGetState Get (List (Maybe Usage))
-> StateT IfaceGetState Get (List Usage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Maybe Usage) -> StateT IfaceGetState Get (List (Maybe Usage))
forall a. Get a -> Get (List a)
getList Get (Maybe Usage)
go
   where
    -- this must follow the `Binary Usage` instance in GHC

    -- (in GHC.Unit.Module.Deps, at least in GHC 9.4.5)

    go :: Get (Maybe Usage)
    go :: Get (Maybe Usage)
go = do
      Word8
usageType <- String -> Get Word8 -> Get Word8
forall a. Show a => String -> Get a -> Get a
traceShow String
"Usage type:" Get Word8
getWord8
      case Word8
usageType of
        Word8
0 -> do
          StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (String
-> StateT IfaceGetState Get Module
-> StateT IfaceGetState Get Module
forall a. Show a => String -> Get a -> Get a
traceShow String
"Module:" StateT IfaceGetState Get Module
getModule) -- usg_mod

          Get () -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ()
getFP                           -- usg_mod_hash

          StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool                         -- usg_safe

          Maybe Usage -> Get (Maybe Usage)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Usage
forall a. Maybe a
Nothing

        Word8
1 -> do
          Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (String -> Get ByteString -> Get ByteString
forall a. Show a => String -> Get a -> Get a
traceShow String
"Home module:" Get ByteString
getFastString)   -- usg_mod_name

          IfaceVersion -> Get () -> Get ()
forall {f :: * -> *}. Applicative f => IfaceVersion -> f () -> f ()
since IfaceVersion
V9045 (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$ Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ByteString
getFastString                -- usg_unit_id

          Get () -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ()
getFP                                      -- usg_mod_hash

          StateT IfaceGetState Get (Maybe ()) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Get () -> StateT IfaceGetState Get (Maybe ())
forall a. Get a -> Get (Maybe a)
getMaybe Get ()
getFP)                           -- usg_exports

          StateT IfaceGetState Get (List (ByteString, ())) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get (List (ByteString, ()))
getEntitiesList                            -- usg_entities

          StateT IfaceGetState Get Bool -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Bool
getBool                                    -- usg_safe

          Maybe Usage -> Get (Maybe Usage)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Usage
forall a. Maybe a
Nothing

        Word8
2 -> do
          -- usg_file_path

          String
file_path  <- String -> Get String -> Get String
forall a. Show a => String -> Get a -> Get a
traceShow String
"File:" (Get String -> Get String) -> Get String -> Get String
forall a b. (a -> b) -> a -> b
$ if IfaceVersion
version IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
V9081
            then Text -> String
Text.unpack (Text -> String) -> (ByteString -> Text) -> ByteString -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf8 (ByteString -> String) -> Get ByteString -> Get String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString
getFastString
            else Get String
getString
          Get String -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Get String -> Get ()) -> Get String -> Get ()
forall a b. (a -> b) -> a -> b
$ String -> Get String -> Get String
forall a. Show a => String -> Get a -> Get a
traceShow String
"FP:" Get String
getFP'                     -- usg_file_hash

          IfaceVersion -> Get () -> Get ()
forall {f :: * -> *}. Applicative f => IfaceVersion -> f () -> f ()
since IfaceVersion
V9041 (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$ StateT IfaceGetState Get (Maybe String) -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (StateT IfaceGetState Get (Maybe String) -> Get ())
-> StateT IfaceGetState Get (Maybe String) -> Get ()
forall a b. (a -> b) -> a -> b
$ String
-> StateT IfaceGetState Get (Maybe String)
-> StateT IfaceGetState Get (Maybe String)
forall a. Show a => String -> Get a -> Get a
traceShow String
"File label:" (Get String -> StateT IfaceGetState Get (Maybe String)
forall a. Get a -> Get (Maybe a)
getMaybe Get String
getString)-- usg_file_label

          Maybe Usage -> Get (Maybe Usage)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Usage -> Maybe Usage
forall a. a -> Maybe a
Just (String -> Usage
Usage String
file_path))

        Word8
3 -> do
          StateT IfaceGetState Get Module -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void StateT IfaceGetState Get Module
getModule -- usg_mod

          Get () -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ()
getFP     -- usg_mod_hash

          Maybe Usage -> Get (Maybe Usage)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Usage
forall a. Maybe a
Nothing

        Word8
4 | IfaceVersion
version IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
V9041 -> do -- UsageHomeModuleInterface

          Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ByteString
getFastString                  -- usg_mod_name

          IfaceVersion -> Get () -> Get ()
forall {f :: * -> *}. Applicative f => IfaceVersion -> f () -> f ()
since IfaceVersion
V9045 (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$ Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ByteString
getFastString    -- usg_unit_id

          Get () -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ()
getFP                          -- usg_iface_hash

          Maybe Usage -> Get (Maybe Usage)
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Usage
forall a. Maybe a
Nothing

        Word8
_ -> String -> Get (Maybe Usage)
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get (Maybe Usage)) -> String -> Get (Maybe Usage)
forall a b. (a -> b) -> a -> b
$ String
"Invalid usageType: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
usageType

  getEntitiesList :: Get (List (ByteString, ()))
  getEntitiesList :: StateT IfaceGetState Get (List (ByteString, ()))
getEntitiesList = Get (ByteString, ())
-> StateT IfaceGetState Get (List (ByteString, ()))
forall a. Get a -> Get (List a)
getList (Get ByteString -> Get () -> Get (ByteString, ())
forall a b. Get a -> Get b -> Get (a, b)
getTuple (Get ()
getNameSpace Get () -> Get ByteString -> Get ByteString
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Get ByteString
getFastString) Get ()
getFP)

  -- See `instance Binary NameSpace` in module GHC.Types.Name.Occurrence. We

  -- discard the information.

  getNameSpace :: Get ()
  getNameSpace :: Get ()
getNameSpace = if IfaceVersion
version IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
V9081
    then do
      Word8
nameSpaceType <- Get Word8
getWord8
      case Word8
nameSpaceType of
        Word8
0 -> () -> Get ()
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        Word8
1 -> () -> Get ()
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        Word8
2 -> () -> Get ()
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        Word8
3 -> () -> Get ()
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        -- Unlike the original, we test that the byte we have obtained is

        -- valid.

        Word8
4 -> do
          Get ByteString -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ByteString
getFastString
        Word8
_ -> String -> Get ()
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get ()) -> String -> Get ()
forall a b. (a -> b) -> a -> b
$ String
"Invalid NameSpace type: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
nameSpaceType
    else Get Word8 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word8
getWord8

getInterface :: Get Interface
getInterface :: Get Interface
getInterface = do
  let enableLEB128 :: Get ()
enableLEB128 = (IfaceGetState -> IfaceGetState) -> Get ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\IfaceGetState
c -> IfaceGetState
c { useLEB128 = True})
      -- read a relative bin pointer

      getRelPtr :: Get Word32
getRelPtr = do
        Int64
c <- Get Int64
bytesRead
        Word32
p <- Get Word32
getPtr
        Word32 -> Get Word32
forall a. a -> StateT IfaceGetState Get a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
c Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
p)

  Word32
magic <- Get Word32 -> Get Word32
forall b. Get b -> Get b
lookAhead Get Word32
getWord32be Get Word32 -> (Word32 -> Get Word32) -> Get Word32
forall a b.
StateT IfaceGetState Get a
-> (a -> StateT IfaceGetState Get b) -> StateT IfaceGetState Get b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    -- normal magic

    Word32
0x1face      -> Get Word32
getWord32be
    Word32
0x1face64    -> Get Word32
getWord32be
    Word32
m            -> do
      -- GHC 8.10 mistakenly encoded header fields with LEB128

      -- so it gets special treatment

      Get Word32 -> Get Word32
forall b. Get b -> Get b
lookAhead (Get ()
enableLEB128 Get () -> Get Word32 -> Get Word32
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Get Word32
getWord32be) Get Word32 -> (Word32 -> Get Word32) -> Get Word32
forall a b.
StateT IfaceGetState Get a
-> (a -> StateT IfaceGetState Get b) -> StateT IfaceGetState Get b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Word32
0x1face      -> Get ()
enableLEB128 Get () -> Get Word32 -> Get Word32
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Get Word32
getWord32be
        Word32
0x1face64    -> Get ()
enableLEB128 Get () -> Get Word32 -> Get Word32
forall a b.
StateT IfaceGetState Get a
-> StateT IfaceGetState Get b -> StateT IfaceGetState Get b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Get Word32
getWord32be
        Word32
_            -> String -> Get Word32
forall a. String -> StateT IfaceGetState Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get Word32) -> String -> Get Word32
forall a b. (a -> b) -> a -> b
$ String
"Invalid magic: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word32 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word32
m String
""

  String -> Get ()
traceGet (String
"Magic: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word32 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word32
magic String
"")

  -- empty field (removed in 9.0...)

  case Word32
magic of
    Word32
0x1face      -> do
      Word32
e <- Get Word32 -> Get Word32
forall b. Get b -> Get b
lookAhead Get Word32
getWord32be
      if Word32
e Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
== Word32
0
        then Get Word32 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word32
getWord32be
        else Get ()
enableLEB128 -- > 9.0

    Word32
0x1face64    -> do
      Word64
e <- Get Word64 -> Get Word64
forall b. Get b -> Get b
lookAhead Get Word64
getWord64be
      if Word64
e Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== Word64
0
        then Get Word64 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word64
getWord64be
        else Get ()
enableLEB128 -- > 9.0

    Word32
_            -> () -> Get ()
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

  -- ghc version

  String
version <- Get String
getString
  String -> Get ()
traceGet (String
"Version: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
version)

  let !ifaceVersion :: IfaceVersion
ifaceVersion
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"9120" = IfaceVersion
V9120
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"9081" = IfaceVersion
V9081
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"9045" = IfaceVersion
V9045
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"9041" = IfaceVersion
V9041
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"9001" = IfaceVersion
V9001
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"8101" = IfaceVersion
V8101
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"8061" = IfaceVersion
V8061
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"8041" = IfaceVersion
V8041
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"8021" = IfaceVersion
V8021
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"8001" = IfaceVersion
V8001
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"7081" = IfaceVersion
V7081
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"7061" = IfaceVersion
V7061
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"7041" = IfaceVersion
V7041
        | String
version String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"7021" = IfaceVersion
V7021
        | Bool
otherwise         = String -> IfaceVersion
forall a. HasCallStack => String -> a
error (String -> IfaceVersion) -> String -> IfaceVersion
forall a b. (a -> b) -> a -> b
$ String
"Unsupported version: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
version

  -- way

  String
way <- Get String
getString
  String -> Get ()
traceGet (String
"Ways: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
way)

  -- source hash (GHC >= 9.4)

  Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (IfaceVersion
ifaceVersion IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
V9041) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$ Get () -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get ()
getFP

  -- extensible fields (GHC >= 9.0)

  Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (IfaceVersion
ifaceVersion IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
V9001) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$ Get Word32 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word32
getPtr

  -- dict_ptr

  Word32
dictPtr <- if IfaceVersion
ifaceVersion IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
V9120 -- 9.12 uses relative pointers

    then Get Word32
getRelPtr
    else Get Word32
getPtr
  String -> Get ()
traceGet (String
"Dict ptr: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word32 -> String
forall a. Show a => a -> String
show Word32
dictPtr)

  -- dict

  Dictionary
dict <- Get Dictionary -> Get Dictionary
forall b. Get b -> Get b
lookAhead (Get Dictionary -> Get Dictionary)
-> Get Dictionary -> Get Dictionary
forall a b. (a -> b) -> a -> b
$ Int -> Get Dictionary
getDictionary (Int -> Get Dictionary) -> Int -> Get Dictionary
forall a b. (a -> b) -> a -> b
$ Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
dictPtr

  -- symtable_ptr

  Get Word32 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word32
getPtr

  -- IfaceType table

  Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (IfaceVersion
ifaceVersion IfaceVersion -> IfaceVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= IfaceVersion
V9120) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$ Get Word32 -> Get ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void Get Word32
getPtr

  case IfaceVersion
ifaceVersion of
    IfaceVersion
V9120 -> IfaceVersion -> Dictionary -> Get Interface
getInterfaceRecent IfaceVersion
ifaceVersion Dictionary
dict
    IfaceVersion
V9081 -> IfaceVersion -> Dictionary -> Get Interface
getInterfaceRecent IfaceVersion
ifaceVersion Dictionary
dict
    IfaceVersion
V9045 -> IfaceVersion -> Dictionary -> Get Interface
getInterfaceRecent IfaceVersion
ifaceVersion Dictionary
dict
    IfaceVersion
V9041 -> IfaceVersion -> Dictionary -> Get Interface
getInterfaceRecent IfaceVersion
ifaceVersion Dictionary
dict
    IfaceVersion
V9001 -> IfaceVersion -> Dictionary -> Get Interface
getInterfaceRecent IfaceVersion
ifaceVersion Dictionary
dict
    IfaceVersion
V8101 -> IfaceVersion -> Dictionary -> Get Interface
getInterfaceRecent IfaceVersion
ifaceVersion Dictionary
dict
    IfaceVersion
V8061 -> Dictionary -> Get Interface
getInterface861 Dictionary
dict
    IfaceVersion
V8041 -> Dictionary -> Get Interface
getInterface841 Dictionary
dict
    IfaceVersion
V8021 -> Dictionary -> Get Interface
getInterface821 Dictionary
dict
    IfaceVersion
V8001 -> Dictionary -> Get Interface
getInterface801 Dictionary
dict
    IfaceVersion
V7081 -> Dictionary -> Get Interface
getInterface781 Dictionary
dict
    IfaceVersion
V7061 -> Dictionary -> Get Interface
getInterface761 Dictionary
dict
    IfaceVersion
V7041 -> Dictionary -> Get Interface
getInterface741 Dictionary
dict
    IfaceVersion
V7021 -> Dictionary -> Get Interface
getInterface721 Dictionary
dict

fromFile :: FilePath -> IO (Either String Interface)
fromFile :: String -> IO (Either String Interface)
fromFile String
fp = String
-> IOMode
-> (Handle -> IO (Either String Interface))
-> IO (Either String Interface)
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
fp IOMode
ReadMode Handle -> IO (Either String Interface)
forall {f :: * -> *}.
MonadIO f =>
Handle -> f (Either String Interface)
go
 where
  go :: Handle -> f (Either String Interface)
go Handle
h =
    let feed :: Decoder b -> f (Either String b)
feed (G.Done ByteString
_ Int64
_ b
iface) = Either String b -> f (Either String b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String b -> f (Either String b))
-> Either String b -> f (Either String b)
forall a b. (a -> b) -> a -> b
$ b -> Either String b
forall a b. b -> Either a b
Right b
iface
        feed (G.Fail ByteString
_ Int64
_ String
msg) = Either String b -> f (Either String b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String b -> f (Either String b))
-> Either String b -> f (Either String b)
forall a b. (a -> b) -> a -> b
$ String -> Either String b
forall a b. a -> Either a b
Left String
msg
        feed (G.Partial Maybe ByteString -> Decoder b
k) = do
          ByteString
chunk <- Handle -> Int -> f ByteString
forall (m :: * -> *). MonadIO m => Handle -> Int -> m ByteString
hGetSome Handle
h Int
defaultChunkSize
          Decoder b -> f (Either String b)
feed (Decoder b -> f (Either String b))
-> Decoder b -> f (Either String b)
forall a b. (a -> b) -> a -> b
$ Maybe ByteString -> Decoder b
k (Maybe ByteString -> Decoder b) -> Maybe ByteString -> Decoder b
forall a b. (a -> b) -> a -> b
$ if ByteString -> Bool
B.null ByteString
chunk then Maybe ByteString
forall a. Maybe a
Nothing else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
chunk
    in  Decoder Interface -> f (Either String Interface)
forall {f :: * -> *} {b}.
MonadIO f =>
Decoder b -> f (Either String b)
feed (Decoder Interface -> f (Either String Interface))
-> Decoder Interface -> f (Either String Interface)
forall a b. (a -> b) -> a -> b
$ Get Interface -> Decoder Interface
forall a. Get a -> Decoder a
runGetIncremental Get Interface
getInterface


getULEB128 :: forall a. (Integral a, FiniteBits a) => Get a
getULEB128 :: forall a. (Integral a, FiniteBits a) => Get a
getULEB128 =
  Int -> a -> Get a
go Int
0 a
0
 where
  go :: Int -> a -> Get a
  go :: Int -> a -> Get a
go Int
shift a
w = do
    Word8
b <- Get Word8
getWord8
    let !hasMore :: Bool
hasMore = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
b Int
7
        !val :: a
val = a
w a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a -> Int -> a
forall a. Bits a => a -> Int -> a
clearBit (Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b) Int
7 a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
shift) :: a
    if Bool
hasMore
      then do
        Int -> a -> Get a
go (Int
shiftInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
7) a
val
      else
        a -> Get a
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Get a) -> a -> Get a
forall a b. (a -> b) -> a -> b
$! a
val

getSLEB128 :: forall a. (Integral a, FiniteBits a) => Get a
getSLEB128 :: forall a. (Integral a, FiniteBits a) => Get a
getSLEB128 = do
  (a
val,Int
shift,Bool
signed) <- Int -> a -> Get (a, Int, Bool)
go Int
0 a
0
  if Bool
signed Bool -> Bool -> Bool
&& (Int
shift Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< a -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize a
val )
    then a -> Get a
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Get a) -> a -> Get a
forall a b. (a -> b) -> a -> b
$! ((a -> a
forall a. Bits a => a -> a
complement a
0 a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
shift) a -> a -> a
forall a. Bits a => a -> a -> a
.|. a
val)
    else a -> Get a
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return a
val
 where
  go :: Int -> a -> Get (a,Int,Bool)
  go :: Int -> a -> Get (a, Int, Bool)
go Int
shift a
val = do
    Word8
byte <- Get Word8
getWord8
    let !byteVal :: a
byteVal = Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
clearBit Word8
byte Int
7) :: a
        !val' :: a
val' = a
val a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
byteVal a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
shift)
        !more :: Bool
more = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
byte Int
7
        !shift' :: Int
shift' = Int
shiftInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
7
    if Bool
more
      then Int -> a -> Get (a, Int, Bool)
go Int
shift' a
val'
      else do
        let !signed :: Bool
signed = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
byte Int
6
        (a, Int, Bool) -> Get (a, Int, Bool)
forall a. a -> StateT IfaceGetState Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
val',Int
shift',Bool
signed)