{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE UnboxedTuples #-}

{-# OPTIONS_GHC -O2 -funbox-strict-fields #-}
-- We always optimise this, otherwise performance of a non-optimised
-- compiler is severely affected

--
-- (c) The University of Glasgow 2002-2006
--
-- Binary I/O library, with special tweaks for GHC
--
-- Based on the nhc98 Binary library, which is copyright
-- (c) Malcolm Wallace and Colin Runciman, University of York, 1998.
-- Under the terms of the license for that software, we must tell you
-- where you can obtain the original version of the Binary library, namely
--     http://www.cs.york.ac.uk/fp/nhc98/

module GHC.Utils.Binary
  ( {-type-}  Bin,
    {-class-} Binary(..),
    {-type-}  BinHandle,
    SymbolTable, Dictionary,

   BinData(..), dataHandle, handleData,

   openBinMem,
--   closeBin,

   seekBin,
   tellBin,
   castBin,
   withBinBuffer,

   writeBinMem,
   readBinMem,

   putAt, getAt,

   -- * For writing instances
   putByte,
   getByte,

   -- * Variable length encodings
   putULEB128,
   getULEB128,
   putSLEB128,
   getSLEB128,

   -- * Fixed length encoding
   FixedLengthEncoding(..),

   -- * Lazy Binary I/O
   lazyGet,
   lazyPut,

   -- * User data
   UserData(..), getUserData, setUserData,
   newReadState, newWriteState,
   putDictionary, getDictionary, putFS,
  ) where

#include "HsVersions.h"

import GHC.Prelude

import {-# SOURCE #-} GHC.Types.Name (Name)
import GHC.Data.FastString
import GHC.Utils.Panic.Plain
import GHC.Types.Unique.FM
import GHC.Data.FastMutInt
import GHC.Utils.Fingerprint
import GHC.Types.Basic
import GHC.Types.SrcLoc

import Control.DeepSeq
import Foreign
import Data.Array
import Data.ByteString (ByteString)
import qualified Data.ByteString.Internal as BS
import qualified Data.ByteString.Unsafe   as BS
import Data.IORef
import Data.Char                ( ord, chr )
import Data.Time
import Data.List (unfoldr)
import Type.Reflection
import Type.Reflection.Unsafe
import Data.Kind (Type)
import GHC.Exts (TYPE, RuntimeRep(..), VecCount(..), VecElem(..))
import Control.Monad            ( when, (<$!>), unless )
import System.IO as IO
import System.IO.Unsafe         ( unsafeInterleaveIO )
import System.IO.Error          ( mkIOError, eofErrorType )
import GHC.Real                 ( Ratio(..) )
import GHC.Serialized
#if MIN_VERSION_base(4,15,0)
import GHC.ForeignPtr           ( unsafeWithForeignPtr )
#endif

type BinArray = ForeignPtr Word8

#if !MIN_VERSION_base(4,15,0)
unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr = withForeignPtr
#endif

---------------------------------------------------------------
-- BinData
---------------------------------------------------------------

data BinData = BinData Int BinArray

instance NFData BinData where
  rnf :: BinData -> ()
rnf (BinData Int
sz BinArray
_) = Int -> ()
forall a. NFData a => a -> ()
rnf Int
sz

instance Binary BinData where
  put_ :: BinHandle -> BinData -> IO ()
put_ BinHandle
bh (BinData Int
sz BinArray
dat) = do
    BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
sz
    BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
putPrim BinHandle
bh Int
sz ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dest ->
      BinArray -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr BinArray
dat ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
orig ->
        Ptr Word8 -> Ptr Word8 -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr Word8
dest Ptr Word8
orig Int
sz
  --
  get :: BinHandle -> IO BinData
get BinHandle
bh = do
    Int
sz <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    BinArray
dat <- Int -> IO BinArray
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
sz
    BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
forall a. BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim BinHandle
bh Int
sz ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
orig ->
      BinArray -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr BinArray
dat ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dest ->
        Ptr Word8 -> Ptr Word8 -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr Word8
dest Ptr Word8
orig Int
sz
    BinData -> IO BinData
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> BinArray -> BinData
BinData Int
sz BinArray
dat)

dataHandle :: BinData -> IO BinHandle
dataHandle :: BinData -> IO BinHandle
dataHandle (BinData Int
size BinArray
bin) = do
  FastMutInt
ixr <- IO FastMutInt
newFastMutInt
  FastMutInt
szr <- IO FastMutInt
newFastMutInt
  FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
ixr Int
0
  FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
szr Int
size
  IORef BinArray
binr <- BinArray -> IO (IORef BinArray)
forall a. a -> IO (IORef a)
newIORef BinArray
bin
  BinHandle -> IO BinHandle
forall (m :: * -> *) a. Monad m => a -> m a
return (UserData -> FastMutInt -> FastMutInt -> IORef BinArray -> BinHandle
BinMem UserData
forall a. a
noUserData FastMutInt
ixr FastMutInt
szr IORef BinArray
binr)

handleData :: BinHandle -> IO BinData
handleData :: BinHandle -> IO BinData
handleData (BinMem UserData
_ FastMutInt
ixr FastMutInt
_ IORef BinArray
binr) = Int -> BinArray -> BinData
BinData (Int -> BinArray -> BinData) -> IO Int -> IO (BinArray -> BinData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FastMutInt -> IO Int
readFastMutInt FastMutInt
ixr IO (BinArray -> BinData) -> IO BinArray -> IO BinData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IORef BinArray -> IO BinArray
forall a. IORef a -> IO a
readIORef IORef BinArray
binr

---------------------------------------------------------------
-- BinHandle
---------------------------------------------------------------

data BinHandle
  = BinMem {                     -- binary data stored in an unboxed array
     BinHandle -> UserData
bh_usr :: UserData,         -- sigh, need parameterized modules :-)
     BinHandle -> FastMutInt
_off_r :: !FastMutInt,      -- the current offset
     BinHandle -> FastMutInt
_sz_r  :: !FastMutInt,      -- size of the array (cached)
     BinHandle -> IORef BinArray
_arr_r :: !(IORef BinArray) -- the array (bounds: (0,size-1))
    }
        -- XXX: should really store a "high water mark" for dumping out
        -- the binary data to a file.

getUserData :: BinHandle -> UserData
getUserData :: BinHandle -> UserData
getUserData BinHandle
bh = BinHandle -> UserData
bh_usr BinHandle
bh

setUserData :: BinHandle -> UserData -> BinHandle
setUserData :: BinHandle -> UserData -> BinHandle
setUserData BinHandle
bh UserData
us = BinHandle
bh { bh_usr :: UserData
bh_usr = UserData
us }

-- | Get access to the underlying buffer.
--
-- It is quite important that no references to the 'ByteString' leak out of the
-- continuation lest terrible things happen.
withBinBuffer :: BinHandle -> (ByteString -> IO a) -> IO a
withBinBuffer :: forall a. BinHandle -> (ByteString -> IO a) -> IO a
withBinBuffer (BinMem UserData
_ FastMutInt
ix_r FastMutInt
_ IORef BinArray
arr_r) ByteString -> IO a
action = do
  BinArray
arr <- IORef BinArray -> IO BinArray
forall a. IORef a -> IO a
readIORef IORef BinArray
arr_r
  Int
ix <- FastMutInt -> IO Int
readFastMutInt FastMutInt
ix_r
  BinArray -> (Ptr Word8 -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr BinArray
arr ((Ptr Word8 -> IO a) -> IO a) -> (Ptr Word8 -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr ->
    CStringLen -> IO ByteString
BS.unsafePackCStringLen (Ptr Word8 -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
ptr, Int
ix) IO ByteString -> (ByteString -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> IO a
action


---------------------------------------------------------------
-- Bin
---------------------------------------------------------------

newtype Bin a = BinPtr Int
  deriving (Bin a -> Bin a -> Bool
(Bin a -> Bin a -> Bool) -> (Bin a -> Bin a -> Bool) -> Eq (Bin a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (a :: k). Bin a -> Bin a -> Bool
/= :: Bin a -> Bin a -> Bool
$c/= :: forall k (a :: k). Bin a -> Bin a -> Bool
== :: Bin a -> Bin a -> Bool
$c== :: forall k (a :: k). Bin a -> Bin a -> Bool
Eq, Eq (Bin a)
Eq (Bin a)
-> (Bin a -> Bin a -> Ordering)
-> (Bin a -> Bin a -> Bool)
-> (Bin a -> Bin a -> Bool)
-> (Bin a -> Bin a -> Bool)
-> (Bin a -> Bin a -> Bool)
-> (Bin a -> Bin a -> Bin a)
-> (Bin a -> Bin a -> Bin a)
-> Ord (Bin a)
Bin a -> Bin a -> Bool
Bin a -> Bin a -> Ordering
Bin a -> Bin a -> Bin a
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
forall k (a :: k). Eq (Bin a)
forall k (a :: k). Bin a -> Bin a -> Bool
forall k (a :: k). Bin a -> Bin a -> Ordering
forall k (a :: k). Bin a -> Bin a -> Bin a
min :: Bin a -> Bin a -> Bin a
$cmin :: forall k (a :: k). Bin a -> Bin a -> Bin a
max :: Bin a -> Bin a -> Bin a
$cmax :: forall k (a :: k). Bin a -> Bin a -> Bin a
>= :: Bin a -> Bin a -> Bool
$c>= :: forall k (a :: k). Bin a -> Bin a -> Bool
> :: Bin a -> Bin a -> Bool
$c> :: forall k (a :: k). Bin a -> Bin a -> Bool
<= :: Bin a -> Bin a -> Bool
$c<= :: forall k (a :: k). Bin a -> Bin a -> Bool
< :: Bin a -> Bin a -> Bool
$c< :: forall k (a :: k). Bin a -> Bin a -> Bool
compare :: Bin a -> Bin a -> Ordering
$ccompare :: forall k (a :: k). Bin a -> Bin a -> Ordering
Ord, Int -> Bin a -> ShowS
[Bin a] -> ShowS
Bin a -> String
(Int -> Bin a -> ShowS)
-> (Bin a -> String) -> ([Bin a] -> ShowS) -> Show (Bin a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (a :: k). Int -> Bin a -> ShowS
forall k (a :: k). [Bin a] -> ShowS
forall k (a :: k). Bin a -> String
showList :: [Bin a] -> ShowS
$cshowList :: forall k (a :: k). [Bin a] -> ShowS
show :: Bin a -> String
$cshow :: forall k (a :: k). Bin a -> String
showsPrec :: Int -> Bin a -> ShowS
$cshowsPrec :: forall k (a :: k). Int -> Bin a -> ShowS
Show, Bin a
Bin a -> Bin a -> Bounded (Bin a)
forall a. a -> a -> Bounded a
forall k (a :: k). Bin a
maxBound :: Bin a
$cmaxBound :: forall k (a :: k). Bin a
minBound :: Bin a
$cminBound :: forall k (a :: k). Bin a
Bounded)

castBin :: Bin a -> Bin b
castBin :: forall {k} {k} (a :: k) (b :: k). Bin a -> Bin b
castBin (BinPtr Int
i) = Int -> Bin b
forall {k} (a :: k). Int -> Bin a
BinPtr Int
i

---------------------------------------------------------------
-- class Binary
---------------------------------------------------------------

-- | Do not rely on instance sizes for general types,
-- we use variable length encoding for many of them.
class Binary a where
    put_   :: BinHandle -> a -> IO ()
    put    :: BinHandle -> a -> IO (Bin a)
    get    :: BinHandle -> IO a

    -- define one of put_, put.  Use of put_ is recommended because it
    -- is more likely that tail-calls can kick in, and we rarely need the
    -- position return value.
    put_ BinHandle
bh a
a = do Bin a
_ <- BinHandle -> a -> IO (Bin a)
forall a. Binary a => BinHandle -> a -> IO (Bin a)
put BinHandle
bh a
a; () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    put BinHandle
bh a
a  = do Bin a
p <- BinHandle -> IO (Bin a)
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh; BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a; Bin a -> IO (Bin a)
forall (m :: * -> *) a. Monad m => a -> m a
return Bin a
p

putAt  :: Binary a => BinHandle -> Bin a -> a -> IO ()
putAt :: forall a. Binary a => BinHandle -> Bin a -> a -> IO ()
putAt BinHandle
bh Bin a
p a
x = do BinHandle -> Bin a -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin a
p; BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
x; () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

getAt  :: Binary a => BinHandle -> Bin a -> IO a
getAt :: forall a. Binary a => BinHandle -> Bin a -> IO a
getAt BinHandle
bh Bin a
p = do BinHandle -> Bin a -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin a
p; BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh

openBinMem :: Int -> IO BinHandle
openBinMem :: Int -> IO BinHandle
openBinMem Int
size
 | Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = String -> IO BinHandle
forall a. HasCallStack => String -> a
error String
"Data.Binary.openBinMem: size must be >= 0"
 | Bool
otherwise = do
   BinArray
arr <- Int -> IO BinArray
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
size
   IORef BinArray
arr_r <- BinArray -> IO (IORef BinArray)
forall a. a -> IO (IORef a)
newIORef BinArray
arr
   FastMutInt
ix_r <- IO FastMutInt
newFastMutInt
   FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
ix_r Int
0
   FastMutInt
sz_r <- IO FastMutInt
newFastMutInt
   FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
sz_r Int
size
   BinHandle -> IO BinHandle
forall (m :: * -> *) a. Monad m => a -> m a
return (UserData -> FastMutInt -> FastMutInt -> IORef BinArray -> BinHandle
BinMem UserData
forall a. a
noUserData FastMutInt
ix_r FastMutInt
sz_r IORef BinArray
arr_r)

tellBin :: BinHandle -> IO (Bin a)
tellBin :: forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin (BinMem UserData
_ FastMutInt
r FastMutInt
_ IORef BinArray
_) = do Int
ix <- FastMutInt -> IO Int
readFastMutInt FastMutInt
r; Bin a -> IO (Bin a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Bin a
forall {k} (a :: k). Int -> Bin a
BinPtr Int
ix)

seekBin :: BinHandle -> Bin a -> IO ()
seekBin :: forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin h :: BinHandle
h@(BinMem UserData
_ FastMutInt
ix_r FastMutInt
sz_r IORef BinArray
_) (BinPtr !Int
p) = do
  Int
sz <- FastMutInt -> IO Int
readFastMutInt FastMutInt
sz_r
  if (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
sz)
        then do BinHandle -> Int -> IO ()
expandBin BinHandle
h Int
p; FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
ix_r Int
p
        else FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
ix_r Int
p

writeBinMem :: BinHandle -> FilePath -> IO ()
writeBinMem :: BinHandle -> String -> IO ()
writeBinMem (BinMem UserData
_ FastMutInt
ix_r FastMutInt
_ IORef BinArray
arr_r) String
fn = do
  Handle
h <- String -> IOMode -> IO Handle
openBinaryFile String
fn IOMode
WriteMode
  BinArray
arr <- IORef BinArray -> IO BinArray
forall a. IORef a -> IO a
readIORef IORef BinArray
arr_r
  Int
ix  <- FastMutInt -> IO Int
readFastMutInt FastMutInt
ix_r
  BinArray -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr BinArray
arr ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Handle -> Ptr Word8 -> Int -> IO ()
forall a. Handle -> Ptr a -> Int -> IO ()
hPutBuf Handle
h Ptr Word8
p Int
ix
  Handle -> IO ()
hClose Handle
h

readBinMem :: FilePath -> IO BinHandle
-- Return a BinHandle with a totally undefined State
readBinMem :: String -> IO BinHandle
readBinMem String
filename = do
  Handle
h <- String -> IOMode -> IO Handle
openBinaryFile String
filename IOMode
ReadMode
  Integer
filesize' <- Handle -> IO Integer
hFileSize Handle
h
  let filesize :: Int
filesize = Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
filesize'
  BinArray
arr <- Int -> IO BinArray
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
filesize
  Int
count <- BinArray -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr BinArray
arr ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Handle -> Ptr Word8 -> Int -> IO Int
forall a. Handle -> Ptr a -> Int -> IO Int
hGetBuf Handle
h Ptr Word8
p Int
filesize
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
count Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
filesize) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
       String -> IO ()
forall a. HasCallStack => String -> a
error (String
"Binary.readBinMem: only read " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
count String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" bytes")
  Handle -> IO ()
hClose Handle
h
  IORef BinArray
arr_r <- BinArray -> IO (IORef BinArray)
forall a. a -> IO (IORef a)
newIORef BinArray
arr
  FastMutInt
ix_r <- IO FastMutInt
newFastMutInt
  FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
ix_r Int
0
  FastMutInt
sz_r <- IO FastMutInt
newFastMutInt
  FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
sz_r Int
filesize
  BinHandle -> IO BinHandle
forall (m :: * -> *) a. Monad m => a -> m a
return (UserData -> FastMutInt -> FastMutInt -> IORef BinArray -> BinHandle
BinMem UserData
forall a. a
noUserData FastMutInt
ix_r FastMutInt
sz_r IORef BinArray
arr_r)

-- expand the size of the array to include a specified offset
expandBin :: BinHandle -> Int -> IO ()
expandBin :: BinHandle -> Int -> IO ()
expandBin (BinMem UserData
_ FastMutInt
_ FastMutInt
sz_r IORef BinArray
arr_r) !Int
off = do
   !Int
sz <- FastMutInt -> IO Int
readFastMutInt FastMutInt
sz_r
   let !sz' :: Int
sz' = Int -> Int
getSize Int
sz
   BinArray
arr <- IORef BinArray -> IO BinArray
forall a. IORef a -> IO a
readIORef IORef BinArray
arr_r
   BinArray
arr' <- Int -> IO BinArray
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
sz'
   BinArray -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr BinArray
arr ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
old ->
     BinArray -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr BinArray
arr' ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
new ->
       Ptr Word8 -> Ptr Word8 -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr Word8
new Ptr Word8
old Int
sz
   FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
sz_r Int
sz'
   IORef BinArray -> BinArray -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef BinArray
arr_r BinArray
arr'
   where
    getSize :: Int -> Int
    getSize :: Int -> Int
getSize !Int
sz
      | Int
sz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
off
      = Int
sz
      | Bool
otherwise
      = Int -> Int
getSize (Int
sz Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2)

-- -----------------------------------------------------------------------------
-- Low-level reading/writing of bytes

-- | Takes a size and action writing up to @size@ bytes.
--   After the action has run advance the index to the buffer
--   by size bytes.
putPrim :: BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
putPrim :: BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
putPrim h :: BinHandle
h@(BinMem UserData
_ FastMutInt
ix_r FastMutInt
sz_r IORef BinArray
arr_r) Int
size Ptr Word8 -> IO ()
f = do
  Int
ix <- FastMutInt -> IO Int
readFastMutInt FastMutInt
ix_r
  Int
sz <- FastMutInt -> IO Int
readFastMutInt FastMutInt
sz_r
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
sz) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    BinHandle -> Int -> IO ()
expandBin BinHandle
h (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
size)
  BinArray
arr <- IORef BinArray -> IO BinArray
forall a. IORef a -> IO a
readIORef IORef BinArray
arr_r
  BinArray -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr BinArray
arr ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
op -> Ptr Word8 -> IO ()
f (Ptr Word8
op Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
ix)
  FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
ix_r (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
size)

-- -- | Similar to putPrim but advances the index by the actual number of
-- -- bytes written.
-- putPrimMax :: BinHandle -> Int -> (Ptr Word8 -> IO Int) -> IO ()
-- putPrimMax h@(BinMem _ ix_r sz_r arr_r) size f = do
--   ix <- readFastMutInt ix_r
--   sz <- readFastMutInt sz_r
--   when (ix + size > sz) $
--     expandBin h (ix + size)
--   arr <- readIORef arr_r
--   written <- withForeignPtr arr $ \op -> f (op `plusPtr` ix)
--   writeFastMutInt ix_r (ix + written)

getPrim :: BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim :: forall a. BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim (BinMem UserData
_ FastMutInt
ix_r FastMutInt
sz_r IORef BinArray
arr_r) Int
size Ptr Word8 -> IO a
f = do
  Int
ix <- FastMutInt -> IO Int
readFastMutInt FastMutInt
ix_r
  Int
sz <- FastMutInt -> IO Int
readFastMutInt FastMutInt
sz_r
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
size Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
sz) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      IOError -> IO ()
forall a. IOError -> IO a
ioError (IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
eofErrorType String
"Data.Binary.getPrim" Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing)
  BinArray
arr <- IORef BinArray -> IO BinArray
forall a. IORef a -> IO a
readIORef IORef BinArray
arr_r
  a
w <- BinArray -> (Ptr Word8 -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr BinArray
arr ((Ptr Word8 -> IO a) -> IO a) -> (Ptr Word8 -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> IO a
f (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
ix)
    -- This is safe WRT #17760 as we we guarantee that the above line doesn't
    -- diverge
  FastMutInt -> Int -> IO ()
writeFastMutInt FastMutInt
ix_r (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
size)
  a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
w

putWord8 :: BinHandle -> Word8 -> IO ()
putWord8 :: BinHandle -> Word8 -> IO ()
putWord8 BinHandle
h !Word8
w = BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
putPrim BinHandle
h Int
1 (\Ptr Word8
op -> Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
op Word8
w)

getWord8 :: BinHandle -> IO Word8
getWord8 :: BinHandle -> IO Word8
getWord8 BinHandle
h = BinHandle -> Int -> (Ptr Word8 -> IO Word8) -> IO Word8
forall a. BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim BinHandle
h Int
1 Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek

putWord16 :: BinHandle -> Word16 -> IO ()
putWord16 :: BinHandle -> Word16 -> IO ()
putWord16 BinHandle
h Word16
w = BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
putPrim BinHandle
h Int
2 (\Ptr Word8
op -> do
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
0 (Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16
w Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
`shiftR` Int
8))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
1 (Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16
w Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.&. Word16
0xFF))
  )

getWord16 :: BinHandle -> IO Word16
getWord16 :: BinHandle -> IO Word16
getWord16 BinHandle
h = BinHandle -> Int -> (Ptr Word8 -> IO Word16) -> IO Word16
forall a. BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim BinHandle
h Int
2 (\Ptr Word8
op -> do
  Word16
w0 <- Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word16) -> IO Word8 -> IO Word16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
0
  Word16
w1 <- Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word16) -> IO Word8 -> IO Word16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
1
  Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return (Word16 -> IO Word16) -> Word16 -> IO Word16
forall a b. (a -> b) -> a -> b
$! Word16
w0 Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
`shiftL` Int
8 Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|. Word16
w1
  )

putWord32 :: BinHandle -> Word32 -> IO ()
putWord32 :: BinHandle -> Word32 -> IO ()
putWord32 BinHandle
h Word32
w = BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
putPrim BinHandle
h Int
4 (\Ptr Word8
op -> do
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
0 (Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
w Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` Int
24))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
1 (Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word32
w Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` Int
16) Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
0xFF))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
2 (Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word32
w Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` Int
8) Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
0xFF))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
3 (Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
w Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
0xFF))
  )

getWord32 :: BinHandle -> IO Word32
getWord32 :: BinHandle -> IO Word32
getWord32 BinHandle
h = BinHandle -> Int -> (Ptr Word8 -> IO Word32) -> IO Word32
forall a. BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim BinHandle
h Int
4 (\Ptr Word8
op -> do
  Word32
w0 <- Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word32) -> IO Word8 -> IO Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
0
  Word32
w1 <- Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word32) -> IO Word8 -> IO Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
1
  Word32
w2 <- Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word32) -> IO Word8 -> IO Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
2
  Word32
w3 <- Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word32) -> IO Word8 -> IO Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
3

  Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32 -> IO Word32) -> Word32 -> IO Word32
forall a b. (a -> b) -> a -> b
$! (Word32
w0 Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` Int
24) Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|.
            (Word32
w1 Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` Int
16) Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|.
            (Word32
w2 Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` Int
8)  Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|.
            Word32
w3
  )

putWord64 :: BinHandle -> Word64 -> IO ()
putWord64 :: BinHandle -> Word64 -> IO ()
putWord64 BinHandle
h Word64
w = BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
putPrim BinHandle
h Int
8 (\Ptr Word8
op -> do
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
0 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
56))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
1 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
48) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xFF))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
2 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
40) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xFF))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
3 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
32) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xFF))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
4 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
24) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xFF))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
5 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
16) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xFF))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
6 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
8) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xFF))
  Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
op Int
7 (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
w Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0xFF))
  )

getWord64 :: BinHandle -> IO Word64
getWord64 :: BinHandle -> IO Word64
getWord64 BinHandle
h = BinHandle -> Int -> (Ptr Word8 -> IO Word64) -> IO Word64
forall a. BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim BinHandle
h Int
8 (\Ptr Word8
op -> do
  Word64
w0 <- Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word64) -> IO Word8 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
0
  Word64
w1 <- Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word64) -> IO Word8 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
1
  Word64
w2 <- Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word64) -> IO Word8 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
2
  Word64
w3 <- Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word64) -> IO Word8 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
3
  Word64
w4 <- Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word64) -> IO Word8 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
4
  Word64
w5 <- Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word64) -> IO Word8 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
5
  Word64
w6 <- Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word64) -> IO Word8 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
6
  Word64
w7 <- Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word64) -> IO Word8 -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
op Int
7

  Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return (Word64 -> IO Word64) -> Word64 -> IO Word64
forall a b. (a -> b) -> a -> b
$! (Word64
w0 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
56) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
            (Word64
w1 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
48) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
            (Word64
w2 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
40) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
            (Word64
w3 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
32) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
            (Word64
w4 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
24) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
            (Word64
w5 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
16) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
            (Word64
w6 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
8)  Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
            Word64
w7
  )

putByte :: BinHandle -> Word8 -> IO ()
putByte :: BinHandle -> Word8 -> IO ()
putByte BinHandle
bh !Word8
w = BinHandle -> Word8 -> IO ()
putWord8 BinHandle
bh Word8
w

getByte :: BinHandle -> IO Word8
getByte :: BinHandle -> IO Word8
getByte BinHandle
h = BinHandle -> IO Word8
getWord8 BinHandle
h

-- -----------------------------------------------------------------------------
-- Encode numbers in LEB128 encoding.
-- Requires one byte of space per 7 bits of data.
--
-- There are signed and unsigned variants.
-- Do NOT use the unsigned one for signed values, at worst it will
-- result in wrong results, at best it will lead to bad performance
-- when coercing negative values to an unsigned type.
--
-- We mark them as SPECIALIZE as it's extremely critical that they get specialized
-- to their specific types.
--
-- TODO: Each use of putByte performs a bounds check,
--       we should use putPrimMax here. However it's quite hard to return
--       the number of bytes written into putPrimMax without allocating an
--       Int for it, while the code below does not allocate at all.
--       So we eat the cost of the bounds check instead of increasing allocations
--       for now.

-- Unsigned numbers
{-# SPECIALISE putULEB128 :: BinHandle -> Word -> IO () #-}
{-# SPECIALISE putULEB128 :: BinHandle -> Word64 -> IO () #-}
{-# SPECIALISE putULEB128 :: BinHandle -> Word32 -> IO () #-}
{-# SPECIALISE putULEB128 :: BinHandle -> Word16 -> IO () #-}
{-# SPECIALISE putULEB128 :: BinHandle -> Int -> IO () #-}
{-# SPECIALISE putULEB128 :: BinHandle -> Int64 -> IO () #-}
{-# SPECIALISE putULEB128 :: BinHandle -> Int32 -> IO () #-}
{-# SPECIALISE putULEB128 :: BinHandle -> Int16 -> IO () #-}
putULEB128 :: forall a. (Integral a, FiniteBits a) => BinHandle -> a -> IO ()
putULEB128 :: forall a. (Integral a, FiniteBits a) => BinHandle -> a -> IO ()
putULEB128 BinHandle
bh a
w =
#if defined(DEBUG)
    (if w < 0 then panic "putULEB128: Signed number" else id) $
#endif
    a -> IO ()
go a
w
  where
    go :: a -> IO ()
    go :: a -> IO ()
go a
w
      | a
w a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= (a
127 :: a)
      = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
w :: Word8)
      | Bool
otherwise = do
        -- bit 7 (8th bit) indicates more to come.
        let !byte :: Word8
byte = Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
setBit (a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
w) Int
7 :: Word8
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
byte
        a -> IO ()
go (a
w a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
7)

{-# SPECIALISE getULEB128 :: BinHandle -> IO Word #-}
{-# SPECIALISE getULEB128 :: BinHandle -> IO Word64 #-}
{-# SPECIALISE getULEB128 :: BinHandle -> IO Word32 #-}
{-# SPECIALISE getULEB128 :: BinHandle -> IO Word16 #-}
{-# SPECIALISE getULEB128 :: BinHandle -> IO Int #-}
{-# SPECIALISE getULEB128 :: BinHandle -> IO Int64 #-}
{-# SPECIALISE getULEB128 :: BinHandle -> IO Int32 #-}
{-# SPECIALISE getULEB128 :: BinHandle -> IO Int16 #-}
getULEB128 :: forall a. (Integral a, FiniteBits a) => BinHandle -> IO a
getULEB128 :: forall a. (Integral a, FiniteBits a) => BinHandle -> IO a
getULEB128 BinHandle
bh =
    Int -> a -> IO a
go Int
0 a
0
  where
    go :: Int -> a -> IO a
    go :: Int -> a -> IO a
go Int
shift a
w = do
        Word8
b <- BinHandle -> IO Word8
getByte BinHandle
bh
        let !hasMore :: Bool
hasMore = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
b Int
7
        let !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 -> IO a
go (Int
shiftInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
7) a
val
            else
                a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> IO a) -> a -> IO a
forall a b. (a -> b) -> a -> b
$! a
val

-- Signed numbers
{-# SPECIALISE putSLEB128 :: BinHandle -> Word -> IO () #-}
{-# SPECIALISE putSLEB128 :: BinHandle -> Word64 -> IO () #-}
{-# SPECIALISE putSLEB128 :: BinHandle -> Word32 -> IO () #-}
{-# SPECIALISE putSLEB128 :: BinHandle -> Word16 -> IO () #-}
{-# SPECIALISE putSLEB128 :: BinHandle -> Int -> IO () #-}
{-# SPECIALISE putSLEB128 :: BinHandle -> Int64 -> IO () #-}
{-# SPECIALISE putSLEB128 :: BinHandle -> Int32 -> IO () #-}
{-# SPECIALISE putSLEB128 :: BinHandle -> Int16 -> IO () #-}
putSLEB128 :: forall a. (Integral a, Bits a) => BinHandle -> a -> IO ()
putSLEB128 :: forall a. (Integral a, Bits a) => BinHandle -> a -> IO ()
putSLEB128 BinHandle
bh a
initial = a -> IO ()
go a
initial
  where
    go :: a -> IO ()
    go :: a -> IO ()
go a
val = do
        let !byte :: Word8
byte = a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Int -> a
forall a. Bits a => a -> Int -> a
clearBit a
val Int
7) :: Word8
        let !val' :: a
val' = a
val a -> Int -> a
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
7
        let !signBit :: Bool
signBit = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
byte Int
6
        let !done :: Bool
done =
                -- Unsigned value, val' == 0 and last value can
                -- be discriminated from a negative number.
                ((a
val' a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
signBit) Bool -> Bool -> Bool
||
                -- Signed value,
                 (a
val' a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== -a
1 Bool -> Bool -> Bool
&& Bool
signBit))

        let !byte' :: Word8
byte' = if Bool
done then Word8
byte else Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
setBit Word8
byte Int
7
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
byte'

        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
done (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ a -> IO ()
go a
val'

{-# SPECIALISE getSLEB128 :: BinHandle -> IO Word #-}
{-# SPECIALISE getSLEB128 :: BinHandle -> IO Word64 #-}
{-# SPECIALISE getSLEB128 :: BinHandle -> IO Word32 #-}
{-# SPECIALISE getSLEB128 :: BinHandle -> IO Word16 #-}
{-# SPECIALISE getSLEB128 :: BinHandle -> IO Int #-}
{-# SPECIALISE getSLEB128 :: BinHandle -> IO Int64 #-}
{-# SPECIALISE getSLEB128 :: BinHandle -> IO Int32 #-}
{-# SPECIALISE getSLEB128 :: BinHandle -> IO Int16 #-}
getSLEB128 :: forall a. (Show a, Integral a, FiniteBits a) => BinHandle -> IO a
getSLEB128 :: forall a. (Show a, Integral a, FiniteBits a) => BinHandle -> IO a
getSLEB128 BinHandle
bh = do
    (a
val,Int
shift,Bool
signed) <- Int -> a -> IO (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 -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> IO a) -> a -> IO 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 -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
val
    where
        go :: Int -> a -> IO (a,Int,Bool)
        go :: Int -> a -> IO (a, Int, Bool)
go Int
shift a
val = do
            Word8
byte <- BinHandle -> IO Word8
getByte BinHandle
bh
            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
            let !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)
            let !more :: Bool
more = Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
byte Int
7
            let !shift' :: Int
shift' = Int
shiftInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
7
            if Bool
more
                then Int -> a -> IO (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) -> IO (a, Int, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
val',Int
shift',Bool
signed)

-- -----------------------------------------------------------------------------
-- Fixed length encoding instances

-- Sometimes words are used to represent a certain bit pattern instead
-- of a number. Using FixedLengthEncoding we will write the pattern as
-- is to the interface file without the variable length encoding we usually
-- apply.

-- | Encode the argument in it's full length. This is different from many default
-- binary instances which make no guarantee about the actual encoding and
-- might do things use variable length encoding.
newtype FixedLengthEncoding a = FixedLengthEncoding { forall a. FixedLengthEncoding a -> a
unFixedLength :: a }

instance Binary (FixedLengthEncoding Word8) where
  put_ :: BinHandle -> FixedLengthEncoding Word8 -> IO ()
put_ BinHandle
h (FixedLengthEncoding Word8
x) = BinHandle -> Word8 -> IO ()
putByte BinHandle
h Word8
x
  get :: BinHandle -> IO (FixedLengthEncoding Word8)
get BinHandle
h = Word8 -> FixedLengthEncoding Word8
forall a. a -> FixedLengthEncoding a
FixedLengthEncoding (Word8 -> FixedLengthEncoding Word8)
-> IO Word8 -> IO (FixedLengthEncoding Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Word8
getByte BinHandle
h

instance Binary (FixedLengthEncoding Word16) where
  put_ :: BinHandle -> FixedLengthEncoding Word16 -> IO ()
put_ BinHandle
h (FixedLengthEncoding Word16
x) = BinHandle -> Word16 -> IO ()
putWord16 BinHandle
h Word16
x
  get :: BinHandle -> IO (FixedLengthEncoding Word16)
get BinHandle
h = Word16 -> FixedLengthEncoding Word16
forall a. a -> FixedLengthEncoding a
FixedLengthEncoding (Word16 -> FixedLengthEncoding Word16)
-> IO Word16 -> IO (FixedLengthEncoding Word16)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Word16
getWord16 BinHandle
h

instance Binary (FixedLengthEncoding Word32) where
  put_ :: BinHandle -> FixedLengthEncoding Word32 -> IO ()
put_ BinHandle
h (FixedLengthEncoding Word32
x) = BinHandle -> Word32 -> IO ()
putWord32 BinHandle
h Word32
x
  get :: BinHandle -> IO (FixedLengthEncoding Word32)
get BinHandle
h = Word32 -> FixedLengthEncoding Word32
forall a. a -> FixedLengthEncoding a
FixedLengthEncoding (Word32 -> FixedLengthEncoding Word32)
-> IO Word32 -> IO (FixedLengthEncoding Word32)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Word32
getWord32 BinHandle
h

instance Binary (FixedLengthEncoding Word64) where
  put_ :: BinHandle -> FixedLengthEncoding Word64 -> IO ()
put_ BinHandle
h (FixedLengthEncoding Word64
x) = BinHandle -> Word64 -> IO ()
putWord64 BinHandle
h Word64
x
  get :: BinHandle -> IO (FixedLengthEncoding Word64)
get BinHandle
h = Word64 -> FixedLengthEncoding Word64
forall a. a -> FixedLengthEncoding a
FixedLengthEncoding (Word64 -> FixedLengthEncoding Word64)
-> IO Word64 -> IO (FixedLengthEncoding Word64)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Word64
getWord64 BinHandle
h

-- -----------------------------------------------------------------------------
-- Primitive Word writes

instance Binary Word8 where
  put_ :: BinHandle -> Word8 -> IO ()
put_ BinHandle
bh !Word8
w = BinHandle -> Word8 -> IO ()
putWord8 BinHandle
bh Word8
w
  get :: BinHandle -> IO Word8
get  = BinHandle -> IO Word8
getWord8

instance Binary Word16 where
  put_ :: BinHandle -> Word16 -> IO ()
put_ = BinHandle -> Word16 -> IO ()
forall a. (Integral a, FiniteBits a) => BinHandle -> a -> IO ()
putULEB128
  get :: BinHandle -> IO Word16
get  = BinHandle -> IO Word16
forall a. (Integral a, FiniteBits a) => BinHandle -> IO a
getULEB128

instance Binary Word32 where
  put_ :: BinHandle -> Word32 -> IO ()
put_ = BinHandle -> Word32 -> IO ()
forall a. (Integral a, FiniteBits a) => BinHandle -> a -> IO ()
putULEB128
  get :: BinHandle -> IO Word32
get  = BinHandle -> IO Word32
forall a. (Integral a, FiniteBits a) => BinHandle -> IO a
getULEB128

instance Binary Word64 where
  put_ :: BinHandle -> Word64 -> IO ()
put_ = BinHandle -> Word64 -> IO ()
forall a. (Integral a, FiniteBits a) => BinHandle -> a -> IO ()
putULEB128
  get :: BinHandle -> IO Word64
get = BinHandle -> IO Word64
forall a. (Integral a, FiniteBits a) => BinHandle -> IO a
getULEB128

-- -----------------------------------------------------------------------------
-- Primitive Int writes

instance Binary Int8 where
  put_ :: BinHandle -> Int8 -> IO ()
put_ BinHandle
h Int8
w = BinHandle -> Word8 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
h (Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int8
w :: Word8)
  get :: BinHandle -> IO Int8
get BinHandle
h    = do Word8
w <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
get BinHandle
h; Int8 -> IO Int8
forall (m :: * -> *) a. Monad m => a -> m a
return (Int8 -> IO Int8) -> Int8 -> IO Int8
forall a b. (a -> b) -> a -> b
$! (Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
w::Word8))

instance Binary Int16 where
  put_ :: BinHandle -> Int16 -> IO ()
put_ = BinHandle -> Int16 -> IO ()
forall a. (Integral a, Bits a) => BinHandle -> a -> IO ()
putSLEB128
  get :: BinHandle -> IO Int16
get = BinHandle -> IO Int16
forall a. (Show a, Integral a, FiniteBits a) => BinHandle -> IO a
getSLEB128

instance Binary Int32 where
  put_ :: BinHandle -> Int32 -> IO ()
put_ = BinHandle -> Int32 -> IO ()
forall a. (Integral a, Bits a) => BinHandle -> a -> IO ()
putSLEB128
  get :: BinHandle -> IO Int32
get = BinHandle -> IO Int32
forall a. (Show a, Integral a, FiniteBits a) => BinHandle -> IO a
getSLEB128

instance Binary Int64 where
  put_ :: BinHandle -> Int64 -> IO ()
put_ BinHandle
h Int64
w = BinHandle -> Int64 -> IO ()
forall a. (Integral a, Bits a) => BinHandle -> a -> IO ()
putSLEB128 BinHandle
h Int64
w
  get :: BinHandle -> IO Int64
get BinHandle
h    = BinHandle -> IO Int64
forall a. (Show a, Integral a, FiniteBits a) => BinHandle -> IO a
getSLEB128 BinHandle
h

-- -----------------------------------------------------------------------------
-- Instances for standard types

instance Binary () where
    put_ :: BinHandle -> () -> IO ()
put_ BinHandle
_ () = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    get :: BinHandle -> IO ()
get  BinHandle
_    = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

instance Binary Bool where
    put_ :: BinHandle -> Bool -> IO ()
put_ BinHandle
bh Bool
b = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Bool -> Int
forall a. Enum a => a -> Int
fromEnum Bool
b))
    get :: BinHandle -> IO Bool
get  BinHandle
bh   = do Word8
x <- BinHandle -> IO Word8
getWord8 BinHandle
bh; Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$! (Int -> Bool
forall a. Enum a => Int -> a
toEnum (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
x))

instance Binary Char where
    put_ :: BinHandle -> Char -> IO ()
put_  BinHandle
bh Char
c = BinHandle -> Word32 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
c) :: Word32)
    get :: BinHandle -> IO Char
get  BinHandle
bh   = do Word32
x <- BinHandle -> IO Word32
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh; Char -> IO Char
forall (m :: * -> *) a. Monad m => a -> m a
return (Char -> IO Char) -> Char -> IO Char
forall a b. (a -> b) -> a -> b
$! (Int -> Char
chr (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
x :: Word32)))

instance Binary Int where
    put_ :: BinHandle -> Int -> IO ()
put_ BinHandle
bh Int
i = BinHandle -> Int64 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i :: Int64)
    get :: BinHandle -> IO Int
get  BinHandle
bh = do
        Int64
x <- BinHandle -> IO Int64
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$! (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64
x :: Int64))

instance Binary a => Binary [a] where
    put_ :: BinHandle -> [a] -> IO ()
put_ BinHandle
bh [a]
l = do
        let len :: Int
len = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l
        BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
len
        (a -> IO ()) -> [a] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh) [a]
l
    get :: BinHandle -> IO [a]
get BinHandle
bh = do
        Int
len <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh :: IO Int -- Int is variable length encoded so only
                                -- one byte for small lists.
        let loop :: Int -> IO [a]
loop Int
0 = [a] -> IO [a]
forall (m :: * -> *) a. Monad m => a -> m a
return []
            loop Int
n = do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh; [a]
as <- Int -> IO [a]
loop (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1); [a] -> IO [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
as)
        Int -> IO [a]
loop Int
len

instance (Ix a, Binary a, Binary b) => Binary (Array a b) where
    put_ :: BinHandle -> Array a b -> IO ()
put_ BinHandle
bh Array a b
arr = do
        BinHandle -> (a, a) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ((a, a) -> IO ()) -> (a, a) -> IO ()
forall a b. (a -> b) -> a -> b
$ Array a b -> (a, a)
forall i e. Array i e -> (i, i)
bounds Array a b
arr
        BinHandle -> [b] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ([b] -> IO ()) -> [b] -> IO ()
forall a b. (a -> b) -> a -> b
$ Array a b -> [b]
forall i e. Array i e -> [e]
elems Array a b
arr
    get :: BinHandle -> IO (Array a b)
get BinHandle
bh = do
        (a, a)
bounds <- BinHandle -> IO (a, a)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        [b]
xs <- BinHandle -> IO [b]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Array a b -> IO (Array a b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Array a b -> IO (Array a b)) -> Array a b -> IO (Array a b)
forall a b. (a -> b) -> a -> b
$ (a, a) -> [b] -> Array a b
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (a, a)
bounds [b]
xs

instance (Binary a, Binary b) => Binary (a,b) where
    put_ :: BinHandle -> (a, b) -> IO ()
put_ BinHandle
bh (a
a,b
b) = do BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a; BinHandle -> b -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh b
b
    get :: BinHandle -> IO (a, b)
get BinHandle
bh        = do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                       b
b <- BinHandle -> IO b
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                       (a, b) -> IO (a, b)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b)

instance (Binary a, Binary b, Binary c) => Binary (a,b,c) where
    put_ :: BinHandle -> (a, b, c) -> IO ()
put_ BinHandle
bh (a
a,b
b,c
c) = do BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a; BinHandle -> b -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh b
b; BinHandle -> c -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh c
c
    get :: BinHandle -> IO (a, b, c)
get BinHandle
bh          = do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                         b
b <- BinHandle -> IO b
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                         c
c <- BinHandle -> IO c
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                         (a, b, c) -> IO (a, b, c)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c)

instance (Binary a, Binary b, Binary c, Binary d) => Binary (a,b,c,d) where
    put_ :: BinHandle -> (a, b, c, d) -> IO ()
put_ BinHandle
bh (a
a,b
b,c
c,d
d) = do BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a; BinHandle -> b -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh b
b; BinHandle -> c -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh c
c; BinHandle -> d -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh d
d
    get :: BinHandle -> IO (a, b, c, d)
get BinHandle
bh            = do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                           b
b <- BinHandle -> IO b
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                           c
c <- BinHandle -> IO c
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                           d
d <- BinHandle -> IO d
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                           (a, b, c, d) -> IO (a, b, c, d)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c,d
d)

instance (Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a,b,c,d, e) where
    put_ :: BinHandle -> (a, b, c, d, e) -> IO ()
put_ BinHandle
bh (a
a,b
b,c
c,d
d, e
e) = do BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a; BinHandle -> b -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh b
b; BinHandle -> c -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh c
c; BinHandle -> d -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh d
d; BinHandle -> e -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh e
e;
    get :: BinHandle -> IO (a, b, c, d, e)
get BinHandle
bh               = do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                              b
b <- BinHandle -> IO b
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                              c
c <- BinHandle -> IO c
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                              d
d <- BinHandle -> IO d
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                              e
e <- BinHandle -> IO e
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                              (a, b, c, d, e) -> IO (a, b, c, d, e)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c,d
d,e
e)

instance (Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a,b,c,d, e, f) where
    put_ :: BinHandle -> (a, b, c, d, e, f) -> IO ()
put_ BinHandle
bh (a
a,b
b,c
c,d
d, e
e, f
f) = do BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a; BinHandle -> b -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh b
b; BinHandle -> c -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh c
c; BinHandle -> d -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh d
d; BinHandle -> e -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh e
e; BinHandle -> f -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh f
f;
    get :: BinHandle -> IO (a, b, c, d, e, f)
get BinHandle
bh                  = do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 b
b <- BinHandle -> IO b
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 c
c <- BinHandle -> IO c
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 d
d <- BinHandle -> IO d
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 e
e <- BinHandle -> IO e
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 f
f <- BinHandle -> IO f
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 (a, b, c, d, e, f) -> IO (a, b, c, d, e, f)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c,d
d,e
e,f
f)

instance (Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a,b,c,d,e,f,g) where
    put_ :: BinHandle -> (a, b, c, d, e, f, g) -> IO ()
put_ BinHandle
bh (a
a,b
b,c
c,d
d,e
e,f
f,g
g) = do BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a; BinHandle -> b -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh b
b; BinHandle -> c -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh c
c; BinHandle -> d -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh d
d; BinHandle -> e -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh e
e; BinHandle -> f -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh f
f; BinHandle -> g -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh g
g
    get :: BinHandle -> IO (a, b, c, d, e, f, g)
get BinHandle
bh                  = do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 b
b <- BinHandle -> IO b
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 c
c <- BinHandle -> IO c
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 d
d <- BinHandle -> IO d
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 e
e <- BinHandle -> IO e
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 f
f <- BinHandle -> IO f
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 g
g <- BinHandle -> IO g
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                                 (a, b, c, d, e, f, g) -> IO (a, b, c, d, e, f, g)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a,b
b,c
c,d
d,e
e,f
f,g
g)

instance Binary a => Binary (Maybe a) where
    put_ :: BinHandle -> Maybe a -> IO ()
put_ BinHandle
bh Maybe a
Nothing  = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh (Just a
a) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1; BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a
    get :: BinHandle -> IO (Maybe a)
get BinHandle
bh           = do Word8
h <- BinHandle -> IO Word8
getWord8 BinHandle
bh
                          case Word8
h of
                            Word8
0 -> Maybe a -> IO (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
                            Word8
_ -> do a
x <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh; Maybe a -> IO (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Maybe a
forall a. a -> Maybe a
Just a
x)

instance (Binary a, Binary b) => Binary (Either a b) where
    put_ :: BinHandle -> Either a b -> IO ()
put_ BinHandle
bh (Left  a
a) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0; BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a
    put_ BinHandle
bh (Right b
b) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1; BinHandle -> b -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh b
b
    get :: BinHandle -> IO (Either a b)
get BinHandle
bh            = do Word8
h <- BinHandle -> IO Word8
getWord8 BinHandle
bh
                           case Word8
h of
                             Word8
0 -> do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh ; Either a b -> IO (Either a b)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either a b
forall a b. a -> Either a b
Left a
a)
                             Word8
_ -> do b
b <- BinHandle -> IO b
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh ; Either a b -> IO (Either a b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either a b
forall a b. b -> Either a b
Right b
b)

instance Binary UTCTime where
    put_ :: BinHandle -> UTCTime -> IO ()
put_ BinHandle
bh UTCTime
u = do BinHandle -> Day -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (UTCTime -> Day
utctDay UTCTime
u)
                   BinHandle -> DiffTime -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (UTCTime -> DiffTime
utctDayTime UTCTime
u)
    get :: BinHandle -> IO UTCTime
get BinHandle
bh = do Day
day <- BinHandle -> IO Day
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                DiffTime
dayTime <- BinHandle -> IO DiffTime
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                UTCTime -> IO UTCTime
forall (m :: * -> *) a. Monad m => a -> m a
return (UTCTime -> IO UTCTime) -> UTCTime -> IO UTCTime
forall a b. (a -> b) -> a -> b
$ UTCTime :: Day -> DiffTime -> UTCTime
UTCTime { utctDay :: Day
utctDay = Day
day, utctDayTime :: DiffTime
utctDayTime = DiffTime
dayTime }

instance Binary Day where
    put_ :: BinHandle -> Day -> IO ()
put_ BinHandle
bh Day
d = BinHandle -> Integer -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Day -> Integer
toModifiedJulianDay Day
d)
    get :: BinHandle -> IO Day
get BinHandle
bh = do Integer
i <- BinHandle -> IO Integer
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                Day -> IO Day
forall (m :: * -> *) a. Monad m => a -> m a
return (Day -> IO Day) -> Day -> IO Day
forall a b. (a -> b) -> a -> b
$ ModifiedJulianDay :: Integer -> Day
ModifiedJulianDay { toModifiedJulianDay :: Integer
toModifiedJulianDay = Integer
i }

instance Binary DiffTime where
    put_ :: BinHandle -> DiffTime -> IO ()
put_ BinHandle
bh DiffTime
dt = BinHandle -> Rational -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (DiffTime -> Rational
forall a. Real a => a -> Rational
toRational DiffTime
dt)
    get :: BinHandle -> IO DiffTime
get BinHandle
bh = do Rational
r <- BinHandle -> IO Rational
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                DiffTime -> IO DiffTime
forall (m :: * -> *) a. Monad m => a -> m a
return (DiffTime -> IO DiffTime) -> DiffTime -> IO DiffTime
forall a b. (a -> b) -> a -> b
$ Rational -> DiffTime
forall a. Fractional a => Rational -> a
fromRational Rational
r

{-
Finally - a reasonable portable Integer instance.

We used to encode values in the Int32 range as such,
falling back to a string of all things. In either case
we stored a tag byte to discriminate between the two cases.

This made some sense as it's highly portable but also not very
efficient.

However GHC stores a surprisingly large number off large Integer
values. In the examples looked at between 25% and 50% of Integers
serialized were outside of the Int32 range.

Consider a valie like `2724268014499746065`, some sort of hash
actually generated by GHC.
In the old scheme this was encoded as a list of 19 chars. This
gave a size of 77 Bytes, one for the length of the list and 76
since we encode chars as Word32 as well.

We can easily do better. The new plan is:

* Start with a tag byte
  * 0 => Int64 (LEB128 encoded)
  * 1 => Negative large interger
  * 2 => Positive large integer
* Followed by the value:
  * Int64 is encoded as usual
  * Large integers are encoded as a list of bytes (Word8).
    We use Data.Bits which defines a bit order independent of the representation.
    Values are stored LSB first.

This means our example value `2724268014499746065` is now only 10 bytes large.
* One byte tag
* One byte for the length of the [Word8] list.
* 8 bytes for the actual date.

The new scheme also does not depend in any way on
architecture specific details.

We still use this scheme even with LEB128 available,
as it has less overhead for truly large numbers. (> maxBound :: Int64)

The instance is used for in Binary Integer and Binary Rational in GHC.Types.Literal
-}

instance Binary Integer where
    put_ :: BinHandle -> Integer -> IO ()
put_ BinHandle
bh Integer
i
      | Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
lo64 Bool -> Bool -> Bool
&& Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
hi64 = do
          BinHandle -> Word8 -> IO ()
putWord8 BinHandle
bh Word8
0
          BinHandle -> Int64 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Int64)
      | Bool
otherwise = do
          if Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0
            then BinHandle -> Word8 -> IO ()
putWord8 BinHandle
bh Word8
1
            else BinHandle -> Word8 -> IO ()
putWord8 BinHandle
bh Word8
2
          BinHandle -> [Word8] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Integer -> [Word8]
unroll (Integer -> [Word8]) -> Integer -> [Word8]
forall a b. (a -> b) -> a -> b
$ Integer -> Integer
forall a. Num a => a -> a
abs Integer
i)
      where
        lo64 :: Integer
lo64 = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64
forall a. Bounded a => a
minBound :: Int64)
        hi64 :: Integer
hi64 = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64
forall a. Bounded a => a
maxBound :: Int64)
    get :: BinHandle -> IO Integer
get BinHandle
bh = do
      Word8
int_kind <- BinHandle -> IO Word8
getWord8 BinHandle
bh
      case Word8
int_kind of
        Word8
0 -> Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Integer) -> IO Int64 -> IO Integer
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> (BinHandle -> IO Int64
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh :: IO Int64)
        -- Large integer
        Word8
1 -> Integer -> Integer
forall a. Num a => a -> a
negate (Integer -> Integer) -> IO Integer -> IO Integer
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> IO Integer
getInt
        Word8
2 -> IO Integer
getInt
        Word8
_ -> String -> IO Integer
forall a. String -> a
panic String
"Binary Integer - Invalid byte"
        where
          getInt :: IO Integer
          getInt :: IO Integer
getInt = [Word8] -> Integer
roll ([Word8] -> Integer) -> IO [Word8] -> IO Integer
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> (BinHandle -> IO [Word8]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh :: IO [Word8])

unroll :: Integer -> [Word8]
unroll :: Integer -> [Word8]
unroll = (Integer -> Maybe (Word8, Integer)) -> Integer -> [Word8]
forall b a. (b -> Maybe (a, b)) -> b -> [a]
unfoldr Integer -> Maybe (Word8, Integer)
forall {b} {a}. (Integral b, Num a, Bits b) => b -> Maybe (a, b)
step
  where
    step :: b -> Maybe (a, b)
step b
0 = Maybe (a, b)
forall a. Maybe a
Nothing
    step b
i = (a, b) -> Maybe (a, b)
forall a. a -> Maybe a
Just (b -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral b
i, b
i b -> Int -> b
forall a. Bits a => a -> Int -> a
`shiftR` Int
8)

roll :: [Word8] -> Integer
roll :: [Word8] -> Integer
roll   = (Integer -> Word8 -> Integer) -> Integer -> [Word8] -> Integer
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Integer -> Word8 -> Integer
forall {a} {a}. (Bits a, Integral a, Num a) => a -> a -> a
unstep Integer
0 ([Word8] -> Integer) -> ([Word8] -> [Word8]) -> [Word8] -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> [Word8]
forall a. [a] -> [a]
reverse
  where
    unstep :: a -> a -> a
unstep a
a a
b = a
a a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
8 a -> a -> a
forall a. Bits a => a -> a -> a
.|. a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
b


    {-
    -- This code is currently commented out.
    -- See https://gitlab.haskell.org/ghc/ghc/issues/3379#note_104346 for
    -- discussion.

    put_ bh (S# i#) = do putByte bh 0; put_ bh (I# i#)
    put_ bh (J# s# a#) = do
        putByte bh 1
        put_ bh (I# s#)
        let sz# = sizeofByteArray# a#  -- in *bytes*
        put_ bh (I# sz#)  -- in *bytes*
        putByteArray bh a# sz#

    get bh = do
        b <- getByte bh
        case b of
          0 -> do (I# i#) <- get bh
                  return (S# i#)
          _ -> do (I# s#) <- get bh
                  sz <- get bh
                  (BA a#) <- getByteArray bh sz
                  return (J# s# a#)

putByteArray :: BinHandle -> ByteArray# -> Int# -> IO ()
putByteArray bh a s# = loop 0#
  where loop n#
           | n# ==# s# = return ()
           | otherwise = do
                putByte bh (indexByteArray a n#)
                loop (n# +# 1#)

getByteArray :: BinHandle -> Int -> IO ByteArray
getByteArray bh (I# sz) = do
  (MBA arr) <- newByteArray sz
  let loop n
           | n ==# sz = return ()
           | otherwise = do
                w <- getByte bh
                writeByteArray arr n w
                loop (n +# 1#)
  loop 0#
  freezeByteArray arr
    -}

{-
data ByteArray = BA ByteArray#
data MBA = MBA (MutableByteArray# RealWorld)

newByteArray :: Int# -> IO MBA
newByteArray sz = IO $ \s ->
  case newByteArray# sz s of { (# s, arr #) ->
  (# s, MBA arr #) }

freezeByteArray :: MutableByteArray# RealWorld -> IO ByteArray
freezeByteArray arr = IO $ \s ->
  case unsafeFreezeByteArray# arr s of { (# s, arr #) ->
  (# s, BA arr #) }

writeByteArray :: MutableByteArray# RealWorld -> Int# -> Word8 -> IO ()
writeByteArray arr i (W8# w) = IO $ \s ->
  case writeWord8Array# arr i w s of { s ->
  (# s, () #) }

indexByteArray :: ByteArray# -> Int# -> Word8
indexByteArray a# n# = W8# (indexWord8Array# a# n#)

-}
instance (Binary a) => Binary (Ratio a) where
    put_ :: BinHandle -> Ratio a -> IO ()
put_ BinHandle
bh (a
a :% a
b) = do BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a; BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
b
    get :: BinHandle -> IO (Ratio a)
get BinHandle
bh = do a
a <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh; a
b <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh; Ratio a -> IO (Ratio a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% a
b)

-- Instance uses fixed-width encoding to allow inserting
-- Bin placeholders in the stream.
instance Binary (Bin a) where
  put_ :: BinHandle -> Bin a -> IO ()
put_ BinHandle
bh (BinPtr Int
i) = BinHandle -> Word32 -> IO ()
putWord32 BinHandle
bh (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i :: Word32)
  get :: BinHandle -> IO (Bin a)
get BinHandle
bh = do Word32
i <- BinHandle -> IO Word32
getWord32 BinHandle
bh; Bin a -> IO (Bin a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Bin a
forall {k} (a :: k). Int -> Bin a
BinPtr (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
i :: Word32)))

-- -----------------------------------------------------------------------------
-- Instances for Data.Typeable stuff

instance Binary TyCon where
    put_ :: BinHandle -> TyCon -> IO ()
put_ BinHandle
bh TyCon
tc = do
        BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (TyCon -> String
tyConPackage TyCon
tc)
        BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (TyCon -> String
tyConModule TyCon
tc)
        BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (TyCon -> String
tyConName TyCon
tc)
        BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (TyCon -> Int
tyConKindArgs TyCon
tc)
        BinHandle -> KindRep -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (TyCon -> KindRep
tyConKindRep TyCon
tc)
    get :: BinHandle -> IO TyCon
get BinHandle
bh =
        String -> String -> String -> Int -> KindRep -> TyCon
mkTyCon (String -> String -> String -> Int -> KindRep -> TyCon)
-> IO String -> IO (String -> String -> Int -> KindRep -> TyCon)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (String -> String -> Int -> KindRep -> TyCon)
-> IO String -> IO (String -> Int -> KindRep -> TyCon)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (String -> Int -> KindRep -> TyCon)
-> IO String -> IO (Int -> KindRep -> TyCon)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (Int -> KindRep -> TyCon) -> IO Int -> IO (KindRep -> TyCon)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (KindRep -> TyCon) -> IO KindRep -> IO TyCon
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO KindRep
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh

instance Binary VecCount where
    put_ :: BinHandle -> VecCount -> IO ()
put_ BinHandle
bh = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (Word8 -> IO ()) -> (VecCount -> Word8) -> VecCount -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> (VecCount -> Int) -> VecCount -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VecCount -> Int
forall a. Enum a => a -> Int
fromEnum
    get :: BinHandle -> IO VecCount
get BinHandle
bh = Int -> VecCount
forall a. Enum a => Int -> a
toEnum (Int -> VecCount) -> (Word8 -> Int) -> Word8 -> VecCount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> VecCount) -> IO Word8 -> IO VecCount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Word8
getByte BinHandle
bh

instance Binary VecElem where
    put_ :: BinHandle -> VecElem -> IO ()
put_ BinHandle
bh = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (Word8 -> IO ()) -> (VecElem -> Word8) -> VecElem -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> (VecElem -> Int) -> VecElem -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VecElem -> Int
forall a. Enum a => a -> Int
fromEnum
    get :: BinHandle -> IO VecElem
get BinHandle
bh = Int -> VecElem
forall a. Enum a => Int -> a
toEnum (Int -> VecElem) -> (Word8 -> Int) -> Word8 -> VecElem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> VecElem) -> IO Word8 -> IO VecElem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Word8
getByte BinHandle
bh

instance Binary RuntimeRep where
    put_ :: BinHandle -> RuntimeRep -> IO ()
put_ BinHandle
bh (VecRep VecCount
a VecElem
b)    = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> VecCount -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh VecCount
a IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> VecElem -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh VecElem
b
    put_ BinHandle
bh (TupleRep [RuntimeRep]
reps) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> [RuntimeRep] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [RuntimeRep]
reps
    put_ BinHandle
bh (SumRep [RuntimeRep]
reps)   = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> [RuntimeRep] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [RuntimeRep]
reps
    put_ BinHandle
bh RuntimeRep
LiftedRep       = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
    put_ BinHandle
bh RuntimeRep
UnliftedRep     = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
    put_ BinHandle
bh RuntimeRep
IntRep          = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
    put_ BinHandle
bh RuntimeRep
WordRep         = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
6
    put_ BinHandle
bh RuntimeRep
Int64Rep        = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
7
    put_ BinHandle
bh RuntimeRep
Word64Rep       = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
8
    put_ BinHandle
bh RuntimeRep
AddrRep         = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
9
    put_ BinHandle
bh RuntimeRep
FloatRep        = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
10
    put_ BinHandle
bh RuntimeRep
DoubleRep       = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
11
    put_ BinHandle
bh RuntimeRep
Int8Rep         = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
12
    put_ BinHandle
bh RuntimeRep
Word8Rep        = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
13
    put_ BinHandle
bh RuntimeRep
Int16Rep        = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
14
    put_ BinHandle
bh RuntimeRep
Word16Rep       = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
15
#if __GLASGOW_HASKELL__ >= 809
    put_ BinHandle
bh RuntimeRep
Int32Rep        = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
16
    put_ BinHandle
bh RuntimeRep
Word32Rep       = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
17
#endif

    get :: BinHandle -> IO RuntimeRep
get BinHandle
bh = do
        Word8
tag <- BinHandle -> IO Word8
getByte BinHandle
bh
        case Word8
tag of
          Word8
0  -> VecCount -> VecElem -> RuntimeRep
VecRep (VecCount -> VecElem -> RuntimeRep)
-> IO VecCount -> IO (VecElem -> RuntimeRep)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO VecCount
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (VecElem -> RuntimeRep) -> IO VecElem -> IO RuntimeRep
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO VecElem
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
1  -> [RuntimeRep] -> RuntimeRep
TupleRep ([RuntimeRep] -> RuntimeRep) -> IO [RuntimeRep] -> IO RuntimeRep
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO [RuntimeRep]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
2  -> [RuntimeRep] -> RuntimeRep
SumRep ([RuntimeRep] -> RuntimeRep) -> IO [RuntimeRep] -> IO RuntimeRep
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO [RuntimeRep]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
3  -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
LiftedRep
          Word8
4  -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
UnliftedRep
          Word8
5  -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
IntRep
          Word8
6  -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
WordRep
          Word8
7  -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
Int64Rep
          Word8
8  -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
Word64Rep
          Word8
9  -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
AddrRep
          Word8
10 -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
FloatRep
          Word8
11 -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
DoubleRep
          Word8
12 -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
Int8Rep
          Word8
13 -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
Word8Rep
          Word8
14 -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
Int16Rep
          Word8
15 -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
Word16Rep
#if __GLASGOW_HASKELL__ >= 809
          Word8
16 -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
Int32Rep
          Word8
17 -> RuntimeRep -> IO RuntimeRep
forall (f :: * -> *) a. Applicative f => a -> f a
pure RuntimeRep
Word32Rep
#endif
          Word8
_  -> String -> IO RuntimeRep
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Binary.putRuntimeRep: invalid tag"

instance Binary KindRep where
    put_ :: BinHandle -> KindRep -> IO ()
put_ BinHandle
bh (KindRepTyConApp TyCon
tc [KindRep]
k) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> TyCon -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TyCon
tc IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> [KindRep] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [KindRep]
k
    put_ BinHandle
bh (KindRepVar Int
bndr) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
bndr
    put_ BinHandle
bh (KindRepApp KindRep
a KindRep
b) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> KindRep -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh KindRep
a IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> KindRep -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh KindRep
b
    put_ BinHandle
bh (KindRepFun KindRep
a KindRep
b) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> KindRep -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh KindRep
a IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> KindRep -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh KindRep
b
    put_ BinHandle
bh (KindRepTYPE RuntimeRep
r) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> RuntimeRep -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh RuntimeRep
r
    put_ BinHandle
bh (KindRepTypeLit TypeLitSort
sort String
r) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> TypeLitSort -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TypeLitSort
sort IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh String
r

    get :: BinHandle -> IO KindRep
get BinHandle
bh = do
        Word8
tag <- BinHandle -> IO Word8
getByte BinHandle
bh
        case Word8
tag of
          Word8
0 -> TyCon -> [KindRep] -> KindRep
KindRepTyConApp (TyCon -> [KindRep] -> KindRep)
-> IO TyCon -> IO ([KindRep] -> KindRep)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO TyCon
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO ([KindRep] -> KindRep) -> IO [KindRep] -> IO KindRep
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO [KindRep]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
1 -> Int -> KindRep
KindRepVar (Int -> KindRep) -> IO Int -> IO KindRep
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
2 -> KindRep -> KindRep -> KindRep
KindRepApp (KindRep -> KindRep -> KindRep)
-> IO KindRep -> IO (KindRep -> KindRep)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO KindRep
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (KindRep -> KindRep) -> IO KindRep -> IO KindRep
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO KindRep
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
3 -> KindRep -> KindRep -> KindRep
KindRepFun (KindRep -> KindRep -> KindRep)
-> IO KindRep -> IO (KindRep -> KindRep)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO KindRep
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (KindRep -> KindRep) -> IO KindRep -> IO KindRep
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO KindRep
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
4 -> RuntimeRep -> KindRep
KindRepTYPE (RuntimeRep -> KindRep) -> IO RuntimeRep -> IO KindRep
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO RuntimeRep
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
5 -> TypeLitSort -> String -> KindRep
KindRepTypeLit (TypeLitSort -> String -> KindRep)
-> IO TypeLitSort -> IO (String -> KindRep)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO TypeLitSort
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh IO (String -> KindRep) -> IO String -> IO KindRep
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Word8
_ -> String -> IO KindRep
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Binary.putKindRep: invalid tag"

instance Binary TypeLitSort where
    put_ :: BinHandle -> TypeLitSort -> IO ()
put_ BinHandle
bh TypeLitSort
TypeLitSymbol = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh TypeLitSort
TypeLitNat = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    get :: BinHandle -> IO TypeLitSort
get BinHandle
bh = do
        Word8
tag <- BinHandle -> IO Word8
getByte BinHandle
bh
        case Word8
tag of
          Word8
0 -> TypeLitSort -> IO TypeLitSort
forall (f :: * -> *) a. Applicative f => a -> f a
pure TypeLitSort
TypeLitSymbol
          Word8
1 -> TypeLitSort -> IO TypeLitSort
forall (f :: * -> *) a. Applicative f => a -> f a
pure TypeLitSort
TypeLitNat
          Word8
_ -> String -> IO TypeLitSort
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Binary.putTypeLitSort: invalid tag"

putTypeRep :: BinHandle -> TypeRep a -> IO ()
-- Special handling for TYPE, (->), and RuntimeRep due to recursive kind
-- relations.
-- See Note [Mutually recursive representations of primitive types]
putTypeRep :: forall {k} (a :: k). BinHandle -> TypeRep a -> IO ()
putTypeRep BinHandle
bh TypeRep a
rep
  | Just a :~~: *
HRefl <- TypeRep a
rep TypeRep a -> TypeRep (*) -> Maybe (a :~~: *)
forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
`eqTypeRep` (TypeRep (*)
forall {k} (a :: k). Typeable a => TypeRep a
typeRep :: TypeRep Type)
  = BinHandle -> Word8 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Word8
0 :: Word8)
putTypeRep BinHandle
bh (Con' TyCon
con [SomeTypeRep]
ks) = do
    BinHandle -> Word8 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Word8
1 :: Word8)
    BinHandle -> TyCon -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh TyCon
con
    BinHandle -> [SomeTypeRep] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [SomeTypeRep]
ks
putTypeRep BinHandle
bh (App TypeRep a
f TypeRep b
x) = do
    BinHandle -> Word8 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Word8
2 :: Word8)
    BinHandle -> TypeRep a -> IO ()
forall {k} (a :: k). BinHandle -> TypeRep a -> IO ()
putTypeRep BinHandle
bh TypeRep a
f
    BinHandle -> TypeRep b -> IO ()
forall {k} (a :: k). BinHandle -> TypeRep a -> IO ()
putTypeRep BinHandle
bh TypeRep b
x
putTypeRep BinHandle
bh (Fun TypeRep arg
arg TypeRep res
res) = do
    BinHandle -> Word8 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Word8
3 :: Word8)
    BinHandle -> TypeRep arg -> IO ()
forall {k} (a :: k). BinHandle -> TypeRep a -> IO ()
putTypeRep BinHandle
bh TypeRep arg
arg
    BinHandle -> TypeRep res -> IO ()
forall {k} (a :: k). BinHandle -> TypeRep a -> IO ()
putTypeRep BinHandle
bh TypeRep res
res

getSomeTypeRep :: BinHandle -> IO SomeTypeRep
getSomeTypeRep :: BinHandle -> IO SomeTypeRep
getSomeTypeRep BinHandle
bh = do
    Word8
tag <- BinHandle -> IO Word8
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh :: IO Word8
    case Word8
tag of
        Word8
0 -> SomeTypeRep -> IO SomeTypeRep
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeTypeRep -> IO SomeTypeRep) -> SomeTypeRep -> IO SomeTypeRep
forall a b. (a -> b) -> a -> b
$ TypeRep (*) -> SomeTypeRep
forall k (a :: k). TypeRep a -> SomeTypeRep
SomeTypeRep (TypeRep (*)
forall {k} (a :: k). Typeable a => TypeRep a
typeRep :: TypeRep Type)
        Word8
1 -> do TyCon
con <- BinHandle -> IO TyCon
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh :: IO TyCon
                [SomeTypeRep]
ks <- BinHandle -> IO [SomeTypeRep]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh :: IO [SomeTypeRep]
                SomeTypeRep -> IO SomeTypeRep
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeTypeRep -> IO SomeTypeRep) -> SomeTypeRep -> IO SomeTypeRep
forall a b. (a -> b) -> a -> b
$ TypeRep Any -> SomeTypeRep
forall k (a :: k). TypeRep a -> SomeTypeRep
SomeTypeRep (TypeRep Any -> SomeTypeRep) -> TypeRep Any -> SomeTypeRep
forall a b. (a -> b) -> a -> b
$ TyCon -> [SomeTypeRep] -> TypeRep Any
forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a
mkTrCon TyCon
con [SomeTypeRep]
ks

        Word8
2 -> do SomeTypeRep TypeRep a
f <- BinHandle -> IO SomeTypeRep
getSomeTypeRep BinHandle
bh
                SomeTypeRep TypeRep a
x <- BinHandle -> IO SomeTypeRep
getSomeTypeRep BinHandle
bh
                case TypeRep a -> TypeRep k
forall k (a :: k). TypeRep a -> TypeRep k
typeRepKind TypeRep a
f of
                  Fun TypeRep arg
arg TypeRep res
res ->
                      case TypeRep arg
arg TypeRep arg -> TypeRep k -> Maybe (arg :~~: k)
forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
`eqTypeRep` TypeRep a -> TypeRep k
forall k (a :: k). TypeRep a -> TypeRep k
typeRepKind TypeRep a
x of
                        Just arg :~~: k
HRefl ->
                            case TypeRep res -> TypeRep (TYPE r2)
forall k (a :: k). TypeRep a -> TypeRep k
typeRepKind TypeRep res
res TypeRep (TYPE r2) -> TypeRep (*) -> Maybe (TYPE r2 :~~: *)
forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
`eqTypeRep` (TypeRep (*)
forall {k} (a :: k). Typeable a => TypeRep a
typeRep :: TypeRep Type) of
                              Just TYPE r2 :~~: *
HRefl -> SomeTypeRep -> IO SomeTypeRep
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeTypeRep -> IO SomeTypeRep) -> SomeTypeRep -> IO SomeTypeRep
forall a b. (a -> b) -> a -> b
$ TypeRep (a a) -> SomeTypeRep
forall k (a :: k). TypeRep a -> SomeTypeRep
SomeTypeRep (TypeRep (a a) -> SomeTypeRep) -> TypeRep (a a) -> SomeTypeRep
forall a b. (a -> b) -> a -> b
$ TypeRep a -> TypeRep a -> TypeRep (a a)
forall k1 k2 (a :: k1 -> k2) (b :: k1).
TypeRep a -> TypeRep b -> TypeRep (a b)
mkTrApp TypeRep a
TypeRep a
f TypeRep a
x
                              Maybe (TYPE r2 :~~: *)
_ -> String -> [String] -> IO SomeTypeRep
forall {m :: * -> *} {a}. MonadFail m => String -> [String] -> m a
failure String
"Kind mismatch in type application" []
                        Maybe (arg :~~: k)
_ -> String -> [String] -> IO SomeTypeRep
forall {m :: * -> *} {a}. MonadFail m => String -> [String] -> m a
failure String
"Kind mismatch in type application"
                             [ String
"    Found argument of kind: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep k -> String
forall a. Show a => a -> String
show (TypeRep a -> TypeRep k
forall k (a :: k). TypeRep a -> TypeRep k
typeRepKind TypeRep a
x)
                             , String
"    Where the constructor:  " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep a -> String
forall a. Show a => a -> String
show TypeRep a
f
                             , String
"    Expects kind:           " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep arg -> String
forall a. Show a => a -> String
show TypeRep arg
arg
                             ]
                  TypeRep k
_ -> String -> [String] -> IO SomeTypeRep
forall {m :: * -> *} {a}. MonadFail m => String -> [String] -> m a
failure String
"Applied non-arrow"
                       [ String
"    Applied type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep a -> String
forall a. Show a => a -> String
show TypeRep a
f
                       , String
"    To argument:  " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep a -> String
forall a. Show a => a -> String
show TypeRep a
x
                       ]
        Word8
3 -> do SomeTypeRep TypeRep a
arg <- BinHandle -> IO SomeTypeRep
getSomeTypeRep BinHandle
bh
                SomeTypeRep TypeRep a
res <- BinHandle -> IO SomeTypeRep
getSomeTypeRep BinHandle
bh
                if
                  | App TypeRep a
argkcon TypeRep b
_ <- TypeRep a -> TypeRep k
forall k (a :: k). TypeRep a -> TypeRep k
typeRepKind TypeRep a
arg
                  , App TypeRep a
reskcon TypeRep b
_ <- TypeRep a -> TypeRep k
forall k (a :: k). TypeRep a -> TypeRep k
typeRepKind TypeRep a
res
                  , Just a :~~: TYPE
HRefl <- TypeRep a
argkcon TypeRep a -> TypeRep TYPE -> Maybe (a :~~: TYPE)
forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
`eqTypeRep` TypeRep TYPE
tYPErep
                  , Just a :~~: TYPE
HRefl <- TypeRep a
reskcon TypeRep a -> TypeRep TYPE -> Maybe (a :~~: TYPE)
forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
`eqTypeRep` TypeRep TYPE
tYPErep
                  -> SomeTypeRep -> IO SomeTypeRep
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeTypeRep -> IO SomeTypeRep) -> SomeTypeRep -> IO SomeTypeRep
forall a b. (a -> b) -> a -> b
$ TypeRep (a -> a) -> SomeTypeRep
forall k (a :: k). TypeRep a -> SomeTypeRep
SomeTypeRep (TypeRep (a -> a) -> SomeTypeRep)
-> TypeRep (a -> a) -> SomeTypeRep
forall a b. (a -> b) -> a -> b
$ TypeRep a -> TypeRep a -> TypeRep (a -> a)
forall k (fun :: k) arg res.
(k ~ *, fun ~~ (arg -> res)) =>
TypeRep arg -> TypeRep res -> TypeRep fun
Fun TypeRep a
TypeRep a
arg TypeRep a
TypeRep a
res
                  | Bool
otherwise -> String -> [String] -> IO SomeTypeRep
forall {m :: * -> *} {a}. MonadFail m => String -> [String] -> m a
failure String
"Kind mismatch" []
        Word8
_ -> String -> [String] -> IO SomeTypeRep
forall {m :: * -> *} {a}. MonadFail m => String -> [String] -> m a
failure String
"Invalid SomeTypeRep" []
  where
    tYPErep :: TypeRep TYPE
    tYPErep :: TypeRep TYPE
tYPErep = TypeRep TYPE
forall {k} (a :: k). Typeable a => TypeRep a
typeRep

    failure :: String -> [String] -> m a
failure String
description [String]
info =
        String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [ String
"Binary.getSomeTypeRep: "String -> ShowS
forall a. [a] -> [a] -> [a]
++String
description ]
                      [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"    "String -> ShowS
forall a. [a] -> [a] -> [a]
++) [String]
info

instance Typeable a => Binary (TypeRep (a :: k)) where
    put_ :: BinHandle -> TypeRep a -> IO ()
put_ = BinHandle -> TypeRep a -> IO ()
forall {k} (a :: k). BinHandle -> TypeRep a -> IO ()
putTypeRep
    get :: BinHandle -> IO (TypeRep a)
get BinHandle
bh = do
        SomeTypeRep TypeRep a
rep <- BinHandle -> IO SomeTypeRep
getSomeTypeRep BinHandle
bh
        case TypeRep a
rep TypeRep a -> TypeRep a -> Maybe (a :~~: a)
forall k1 k2 (a :: k1) (b :: k2).
TypeRep a -> TypeRep b -> Maybe (a :~~: b)
`eqTypeRep` TypeRep a
expected of
            Just a :~~: a
HRefl -> TypeRep a -> IO (TypeRep a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure TypeRep a
rep
            Maybe (a :~~: a)
Nothing    -> String -> IO (TypeRep a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO (TypeRep a)) -> String -> IO (TypeRep a)
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines
                               [ String
"Binary: Type mismatch"
                               , String
"    Deserialized type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep a -> String
forall a. Show a => a -> String
show TypeRep a
rep
                               , String
"    Expected type:     " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep a -> String
forall a. Show a => a -> String
show TypeRep a
expected
                               ]
     where expected :: TypeRep a
expected = TypeRep a
forall {k} (a :: k). Typeable a => TypeRep a
typeRep :: TypeRep a

instance Binary SomeTypeRep where
    put_ :: BinHandle -> SomeTypeRep -> IO ()
put_ BinHandle
bh (SomeTypeRep TypeRep a
rep) = BinHandle -> TypeRep a -> IO ()
forall {k} (a :: k). BinHandle -> TypeRep a -> IO ()
putTypeRep BinHandle
bh TypeRep a
rep
    get :: BinHandle -> IO SomeTypeRep
get = BinHandle -> IO SomeTypeRep
getSomeTypeRep

-- -----------------------------------------------------------------------------
-- Lazy reading/writing

lazyPut :: Binary a => BinHandle -> a -> IO ()
lazyPut :: forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh a
a = do
    -- output the obj with a ptr to skip over it:
    Bin (Bin Any)
pre_a <- BinHandle -> IO (Bin (Bin Any))
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
    BinHandle -> Bin (Bin Any) -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Bin (Bin Any)
pre_a       -- save a slot for the ptr
    BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
a           -- dump the object
    Bin Any
q <- BinHandle -> IO (Bin Any)
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh     -- q = ptr to after object
    BinHandle -> Bin (Bin Any) -> Bin Any -> IO ()
forall a. Binary a => BinHandle -> Bin a -> a -> IO ()
putAt BinHandle
bh Bin (Bin Any)
pre_a Bin Any
q    -- fill in slot before a with ptr to q
    BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
q        -- finally carry on writing at q

lazyGet :: Binary a => BinHandle -> IO a
lazyGet :: forall a. Binary a => BinHandle -> IO a
lazyGet BinHandle
bh = do
    Bin Any
p <- BinHandle -> IO (Bin Any)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh -- a BinPtr
    Bin a
p_a <- BinHandle -> IO (Bin a)
forall {k} (a :: k). BinHandle -> IO (Bin a)
tellBin BinHandle
bh
    a
a <- IO a -> IO a
forall a. IO a -> IO a
unsafeInterleaveIO (IO a -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ do
        -- NB: Use a fresh off_r variable in the child thread, for thread
        -- safety.
        FastMutInt
off_r <- IO FastMutInt
newFastMutInt
        BinHandle -> Bin a -> IO a
forall a. Binary a => BinHandle -> Bin a -> IO a
getAt BinHandle
bh { _off_r :: FastMutInt
_off_r = FastMutInt
off_r } Bin a
p_a
    BinHandle -> Bin Any -> IO ()
forall {k} (a :: k). BinHandle -> Bin a -> IO ()
seekBin BinHandle
bh Bin Any
p -- skip over the object for now
    a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a

-- -----------------------------------------------------------------------------
-- UserData
-- -----------------------------------------------------------------------------

-- | Information we keep around during interface file
-- serialization/deserialization. Namely we keep the functions for serializing
-- and deserializing 'Name's and 'FastString's. We do this because we actually
-- use serialization in two distinct settings,
--
-- * When serializing interface files themselves
--
-- * When computing the fingerprint of an IfaceDecl (which we computing by
--   hashing its Binary serialization)
--
-- These two settings have different needs while serializing Names:
--
-- * Names in interface files are serialized via a symbol table (see Note
--   [Symbol table representation of names] in "GHC.Iface.Binary").
--
-- * During fingerprinting a binding Name is serialized as the OccName and a
--   non-binding Name is serialized as the fingerprint of the thing they
--   represent. See Note [Fingerprinting IfaceDecls] for further discussion.
--
data UserData =
   UserData {
        -- for *deserialising* only:
        UserData -> BinHandle -> IO Name
ud_get_name :: BinHandle -> IO Name,
        UserData -> BinHandle -> IO FastString
ud_get_fs   :: BinHandle -> IO FastString,

        -- for *serialising* only:
        UserData -> BinHandle -> Name -> IO ()
ud_put_nonbinding_name :: BinHandle -> Name -> IO (),
        -- ^ serialize a non-binding 'Name' (e.g. a reference to another
        -- binding).
        UserData -> BinHandle -> Name -> IO ()
ud_put_binding_name :: BinHandle -> Name -> IO (),
        -- ^ serialize a binding 'Name' (e.g. the name of an IfaceDecl)
        UserData -> BinHandle -> FastString -> IO ()
ud_put_fs   :: BinHandle -> FastString -> IO ()
   }

newReadState :: (BinHandle -> IO Name)   -- ^ how to deserialize 'Name's
             -> (BinHandle -> IO FastString)
             -> UserData
newReadState :: (BinHandle -> IO Name) -> (BinHandle -> IO FastString) -> UserData
newReadState BinHandle -> IO Name
get_name BinHandle -> IO FastString
get_fs
  = UserData :: (BinHandle -> IO Name)
-> (BinHandle -> IO FastString)
-> (BinHandle -> Name -> IO ())
-> (BinHandle -> Name -> IO ())
-> (BinHandle -> FastString -> IO ())
-> UserData
UserData { ud_get_name :: BinHandle -> IO Name
ud_get_name = BinHandle -> IO Name
get_name,
               ud_get_fs :: BinHandle -> IO FastString
ud_get_fs   = BinHandle -> IO FastString
get_fs,
               ud_put_nonbinding_name :: BinHandle -> Name -> IO ()
ud_put_nonbinding_name = String -> BinHandle -> Name -> IO ()
forall a. String -> a
undef String
"put_nonbinding_name",
               ud_put_binding_name :: BinHandle -> Name -> IO ()
ud_put_binding_name    = String -> BinHandle -> Name -> IO ()
forall a. String -> a
undef String
"put_binding_name",
               ud_put_fs :: BinHandle -> FastString -> IO ()
ud_put_fs   = String -> BinHandle -> FastString -> IO ()
forall a. String -> a
undef String
"put_fs"
             }

newWriteState :: (BinHandle -> Name -> IO ())
                 -- ^ how to serialize non-binding 'Name's
              -> (BinHandle -> Name -> IO ())
                 -- ^ how to serialize binding 'Name's
              -> (BinHandle -> FastString -> IO ())
              -> UserData
newWriteState :: (BinHandle -> Name -> IO ())
-> (BinHandle -> Name -> IO ())
-> (BinHandle -> FastString -> IO ())
-> UserData
newWriteState BinHandle -> Name -> IO ()
put_nonbinding_name BinHandle -> Name -> IO ()
put_binding_name BinHandle -> FastString -> IO ()
put_fs
  = UserData :: (BinHandle -> IO Name)
-> (BinHandle -> IO FastString)
-> (BinHandle -> Name -> IO ())
-> (BinHandle -> Name -> IO ())
-> (BinHandle -> FastString -> IO ())
-> UserData
UserData { ud_get_name :: BinHandle -> IO Name
ud_get_name = String -> BinHandle -> IO Name
forall a. String -> a
undef String
"get_name",
               ud_get_fs :: BinHandle -> IO FastString
ud_get_fs   = String -> BinHandle -> IO FastString
forall a. String -> a
undef String
"get_fs",
               ud_put_nonbinding_name :: BinHandle -> Name -> IO ()
ud_put_nonbinding_name = BinHandle -> Name -> IO ()
put_nonbinding_name,
               ud_put_binding_name :: BinHandle -> Name -> IO ()
ud_put_binding_name    = BinHandle -> Name -> IO ()
put_binding_name,
               ud_put_fs :: BinHandle -> FastString -> IO ()
ud_put_fs   = BinHandle -> FastString -> IO ()
put_fs
             }

noUserData :: a
noUserData :: forall a. a
noUserData = String -> a
forall a. String -> a
undef String
"UserData"

undef :: String -> a
undef :: forall a. String -> a
undef String
s = String -> a
forall a. String -> a
panic (String
"Binary.UserData: no " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s)

---------------------------------------------------------
-- The Dictionary
---------------------------------------------------------

type Dictionary = Array Int FastString -- The dictionary
                                       -- Should be 0-indexed

putDictionary :: BinHandle -> Int -> UniqFM FastString (Int,FastString) -> IO ()
putDictionary :: BinHandle -> Int -> UniqFM FastString (Int, FastString) -> IO ()
putDictionary BinHandle
bh Int
sz UniqFM FastString (Int, FastString)
dict = do
  BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
sz
  (FastString -> IO ()) -> [FastString] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (BinHandle -> FastString -> IO ()
putFS BinHandle
bh) (Array Int FastString -> [FastString]
forall i e. Array i e -> [e]
elems ((Int, Int) -> [(Int, FastString)] -> Array Int FastString
forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e
array (Int
0,Int
szInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (UniqFM FastString (Int, FastString) -> [(Int, FastString)]
forall key elt. UniqFM key elt -> [elt]
nonDetEltsUFM UniqFM FastString (Int, FastString)
dict)))
    -- It's OK to use nonDetEltsUFM here because the elements have indices
    -- that array uses to create order

getDictionary :: BinHandle -> IO Dictionary
getDictionary :: BinHandle -> IO (Array Int FastString)
getDictionary BinHandle
bh = do
  Int
sz <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
  [FastString]
elems <- [IO FastString] -> IO [FastString]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence (Int -> [IO FastString] -> [IO FastString]
forall a. Int -> [a] -> [a]
take Int
sz (IO FastString -> [IO FastString]
forall a. a -> [a]
repeat (BinHandle -> IO FastString
getFS BinHandle
bh)))
  Array Int FastString -> IO (Array Int FastString)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int, Int) -> [FastString] -> Array Int FastString
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
szInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) [FastString]
elems)

---------------------------------------------------------
-- The Symbol Table
---------------------------------------------------------

-- On disk, the symbol table is an array of IfExtName, when
-- reading it in we turn it into a SymbolTable.

type SymbolTable = Array Int Name

---------------------------------------------------------
-- Reading and writing FastStrings
---------------------------------------------------------

putFS :: BinHandle -> FastString -> IO ()
putFS :: BinHandle -> FastString -> IO ()
putFS BinHandle
bh FastString
fs = BinHandle -> ByteString -> IO ()
putBS BinHandle
bh (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ FastString -> ByteString
bytesFS FastString
fs

getFS :: BinHandle -> IO FastString
getFS :: BinHandle -> IO FastString
getFS BinHandle
bh = do
  Int
l  <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh :: IO Int
  BinHandle -> Int -> (Ptr Word8 -> IO FastString) -> IO FastString
forall a. BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim BinHandle
bh Int
l (\Ptr Word8
src -> FastString -> IO FastString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FastString -> IO FastString) -> FastString -> IO FastString
forall a b. (a -> b) -> a -> b
$! Ptr Word8 -> Int -> FastString
mkFastStringBytes Ptr Word8
src Int
l )

putBS :: BinHandle -> ByteString -> IO ()
putBS :: BinHandle -> ByteString -> IO ()
putBS BinHandle
bh ByteString
bs =
  ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.unsafeUseAsCStringLen ByteString
bs ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
l) -> do
    BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
l
    BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
putPrim BinHandle
bh Int
l (\Ptr Word8
op -> Ptr Word8 -> Ptr Word8 -> Int -> IO ()
BS.memcpy Ptr Word8
op (Ptr CChar -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
ptr) Int
l)

getBS :: BinHandle -> IO ByteString
getBS :: BinHandle -> IO ByteString
getBS BinHandle
bh = do
  Int
l <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh :: IO Int
  Int -> (Ptr Word8 -> IO ()) -> IO ByteString
BS.create Int
l ((Ptr Word8 -> IO ()) -> IO ByteString)
-> (Ptr Word8 -> IO ()) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dest -> do
    BinHandle -> Int -> (Ptr Word8 -> IO ()) -> IO ()
forall a. BinHandle -> Int -> (Ptr Word8 -> IO a) -> IO a
getPrim BinHandle
bh Int
l (\Ptr Word8
src -> Ptr Word8 -> Ptr Word8 -> Int -> IO ()
BS.memcpy Ptr Word8
dest Ptr Word8
src Int
l)

instance Binary ByteString where
  put_ :: BinHandle -> ByteString -> IO ()
put_ BinHandle
bh ByteString
f = BinHandle -> ByteString -> IO ()
putBS BinHandle
bh ByteString
f
  get :: BinHandle -> IO ByteString
get BinHandle
bh = BinHandle -> IO ByteString
getBS BinHandle
bh

instance Binary FastString where
  put_ :: BinHandle -> FastString -> IO ()
put_ BinHandle
bh FastString
f =
    case BinHandle -> UserData
getUserData BinHandle
bh of
        UserData { ud_put_fs :: UserData -> BinHandle -> FastString -> IO ()
ud_put_fs = BinHandle -> FastString -> IO ()
put_fs } -> BinHandle -> FastString -> IO ()
put_fs BinHandle
bh FastString
f

  get :: BinHandle -> IO FastString
get BinHandle
bh =
    case BinHandle -> UserData
getUserData BinHandle
bh of
        UserData { ud_get_fs :: UserData -> BinHandle -> IO FastString
ud_get_fs = BinHandle -> IO FastString
get_fs } -> BinHandle -> IO FastString
get_fs BinHandle
bh

-- Here to avoid loop
instance Binary LeftOrRight where
   put_ :: BinHandle -> LeftOrRight -> IO ()
put_ BinHandle
bh LeftOrRight
CLeft  = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
   put_ BinHandle
bh LeftOrRight
CRight = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1

   get :: BinHandle -> IO LeftOrRight
get BinHandle
bh = do { Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
               ; case Word8
h of
                   Word8
0 -> LeftOrRight -> IO LeftOrRight
forall (m :: * -> *) a. Monad m => a -> m a
return LeftOrRight
CLeft
                   Word8
_ -> LeftOrRight -> IO LeftOrRight
forall (m :: * -> *) a. Monad m => a -> m a
return LeftOrRight
CRight }

instance Binary PromotionFlag where
   put_ :: BinHandle -> PromotionFlag -> IO ()
put_ BinHandle
bh PromotionFlag
NotPromoted = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
   put_ BinHandle
bh PromotionFlag
IsPromoted  = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1

   get :: BinHandle -> IO PromotionFlag
get BinHandle
bh = do
       Word8
n <- BinHandle -> IO Word8
getByte BinHandle
bh
       case Word8
n of
         Word8
0 -> PromotionFlag -> IO PromotionFlag
forall (m :: * -> *) a. Monad m => a -> m a
return PromotionFlag
NotPromoted
         Word8
1 -> PromotionFlag -> IO PromotionFlag
forall (m :: * -> *) a. Monad m => a -> m a
return PromotionFlag
IsPromoted
         Word8
_ -> String -> IO PromotionFlag
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Binary(IsPromoted): fail)"

instance Binary Fingerprint where
  put_ :: BinHandle -> Fingerprint -> IO ()
put_ BinHandle
h (Fingerprint Word64
w1 Word64
w2) = do BinHandle -> Word64 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
h Word64
w1; BinHandle -> Word64 -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
h Word64
w2
  get :: BinHandle -> IO Fingerprint
get  BinHandle
h = do Word64
w1 <- BinHandle -> IO Word64
forall a. Binary a => BinHandle -> IO a
get BinHandle
h; Word64
w2 <- BinHandle -> IO Word64
forall a. Binary a => BinHandle -> IO a
get BinHandle
h; Fingerprint -> IO Fingerprint
forall (m :: * -> *) a. Monad m => a -> m a
return (Word64 -> Word64 -> Fingerprint
Fingerprint Word64
w1 Word64
w2)

instance Binary FunctionOrData where
    put_ :: BinHandle -> FunctionOrData -> IO ()
put_ BinHandle
bh FunctionOrData
IsFunction = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh FunctionOrData
IsData     = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    get :: BinHandle -> IO FunctionOrData
get BinHandle
bh = do
        Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
        case Word8
h of
          Word8
0 -> FunctionOrData -> IO FunctionOrData
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionOrData
IsFunction
          Word8
1 -> FunctionOrData -> IO FunctionOrData
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionOrData
IsData
          Word8
_ -> String -> IO FunctionOrData
forall a. String -> a
panic String
"Binary FunctionOrData"

instance Binary TupleSort where
    put_ :: BinHandle -> TupleSort -> IO ()
put_ BinHandle
bh TupleSort
BoxedTuple      = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh TupleSort
UnboxedTuple    = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    put_ BinHandle
bh TupleSort
ConstraintTuple = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
    get :: BinHandle -> IO TupleSort
get BinHandle
bh = do
      Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
      case Word8
h of
        Word8
0 -> do TupleSort -> IO TupleSort
forall (m :: * -> *) a. Monad m => a -> m a
return TupleSort
BoxedTuple
        Word8
1 -> do TupleSort -> IO TupleSort
forall (m :: * -> *) a. Monad m => a -> m a
return TupleSort
UnboxedTuple
        Word8
_ -> do TupleSort -> IO TupleSort
forall (m :: * -> *) a. Monad m => a -> m a
return TupleSort
ConstraintTuple

instance Binary Activation where
    put_ :: BinHandle -> Activation -> IO ()
put_ BinHandle
bh Activation
NeverActive = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh Activation
FinalActive = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    put_ BinHandle
bh Activation
AlwaysActive = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
    put_ BinHandle
bh (ActiveBefore SourceText
src Int
aa) = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
            BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
src
            BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
aa
    put_ BinHandle
bh (ActiveAfter SourceText
src Int
ab) = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
            BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
src
            BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
ab
    get :: BinHandle -> IO Activation
get BinHandle
bh = do
            Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
            case Word8
h of
              Word8
0 -> do Activation -> IO Activation
forall (m :: * -> *) a. Monad m => a -> m a
return Activation
NeverActive
              Word8
1 -> do Activation -> IO Activation
forall (m :: * -> *) a. Monad m => a -> m a
return Activation
FinalActive
              Word8
2 -> do Activation -> IO Activation
forall (m :: * -> *) a. Monad m => a -> m a
return Activation
AlwaysActive
              Word8
3 -> do SourceText
src <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      Int
aa <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      Activation -> IO Activation
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> Int -> Activation
ActiveBefore SourceText
src Int
aa)
              Word8
_ -> do SourceText
src <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      Int
ab <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      Activation -> IO Activation
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> Int -> Activation
ActiveAfter SourceText
src Int
ab)

instance Binary InlinePragma where
    put_ :: BinHandle -> InlinePragma -> IO ()
put_ BinHandle
bh (InlinePragma SourceText
s InlineSpec
a Maybe Int
b Activation
c RuleMatchInfo
d) = do
            BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
            BinHandle -> InlineSpec -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh InlineSpec
a
            BinHandle -> Maybe Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Int
b
            BinHandle -> Activation -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Activation
c
            BinHandle -> RuleMatchInfo -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh RuleMatchInfo
d

    get :: BinHandle -> IO InlinePragma
get BinHandle
bh = do
           SourceText
s <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
           InlineSpec
a <- BinHandle -> IO InlineSpec
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
           Maybe Int
b <- BinHandle -> IO (Maybe Int)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
           Activation
c <- BinHandle -> IO Activation
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
           RuleMatchInfo
d <- BinHandle -> IO RuleMatchInfo
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
           InlinePragma -> IO InlinePragma
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText
-> InlineSpec
-> Maybe Int
-> Activation
-> RuleMatchInfo
-> InlinePragma
InlinePragma SourceText
s InlineSpec
a Maybe Int
b Activation
c RuleMatchInfo
d)

instance Binary RuleMatchInfo where
    put_ :: BinHandle -> RuleMatchInfo -> IO ()
put_ BinHandle
bh RuleMatchInfo
FunLike = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh RuleMatchInfo
ConLike = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    get :: BinHandle -> IO RuleMatchInfo
get BinHandle
bh = do
            Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
            if Word8
h Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
1 then RuleMatchInfo -> IO RuleMatchInfo
forall (m :: * -> *) a. Monad m => a -> m a
return RuleMatchInfo
ConLike
                      else RuleMatchInfo -> IO RuleMatchInfo
forall (m :: * -> *) a. Monad m => a -> m a
return RuleMatchInfo
FunLike

instance Binary InlineSpec where
    put_ :: BinHandle -> InlineSpec -> IO ()
put_ BinHandle
bh InlineSpec
NoUserInline    = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh InlineSpec
Inline          = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    put_ BinHandle
bh InlineSpec
Inlinable       = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
    put_ BinHandle
bh InlineSpec
NoInline        = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3

    get :: BinHandle -> IO InlineSpec
get BinHandle
bh = do Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
                case Word8
h of
                  Word8
0 -> InlineSpec -> IO InlineSpec
forall (m :: * -> *) a. Monad m => a -> m a
return InlineSpec
NoUserInline
                  Word8
1 -> InlineSpec -> IO InlineSpec
forall (m :: * -> *) a. Monad m => a -> m a
return InlineSpec
Inline
                  Word8
2 -> InlineSpec -> IO InlineSpec
forall (m :: * -> *) a. Monad m => a -> m a
return InlineSpec
Inlinable
                  Word8
_ -> InlineSpec -> IO InlineSpec
forall (m :: * -> *) a. Monad m => a -> m a
return InlineSpec
NoInline

instance Binary RecFlag where
    put_ :: BinHandle -> RecFlag -> IO ()
put_ BinHandle
bh RecFlag
Recursive = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh RecFlag
NonRecursive = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    get :: BinHandle -> IO RecFlag
get BinHandle
bh = do
            Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
            case Word8
h of
              Word8
0 -> do RecFlag -> IO RecFlag
forall (m :: * -> *) a. Monad m => a -> m a
return RecFlag
Recursive
              Word8
_ -> do RecFlag -> IO RecFlag
forall (m :: * -> *) a. Monad m => a -> m a
return RecFlag
NonRecursive

instance Binary OverlapMode where
    put_ :: BinHandle -> OverlapMode -> IO ()
put_ BinHandle
bh (NoOverlap    SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
    put_ BinHandle
bh (Overlaps     SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
    put_ BinHandle
bh (Incoherent   SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
    put_ BinHandle
bh (Overlapping  SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
    put_ BinHandle
bh (Overlappable SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
    get :: BinHandle -> IO OverlapMode
get BinHandle
bh = do
        Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
        case Word8
h of
            Word8
0 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
NoOverlap SourceText
s
            Word8
1 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
Overlaps SourceText
s
            Word8
2 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
Incoherent SourceText
s
            Word8
3 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
Overlapping SourceText
s
            Word8
4 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
Overlappable SourceText
s
            Word8
_ -> String -> IO OverlapMode
forall a. String -> a
panic (String
"get OverlapMode" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
h)


instance Binary OverlapFlag where
    put_ :: BinHandle -> OverlapFlag -> IO ()
put_ BinHandle
bh OverlapFlag
flag = do BinHandle -> OverlapMode -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (OverlapFlag -> OverlapMode
overlapMode OverlapFlag
flag)
                      BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (OverlapFlag -> Bool
isSafeOverlap OverlapFlag
flag)
    get :: BinHandle -> IO OverlapFlag
get BinHandle
bh = do
        OverlapMode
h <- BinHandle -> IO OverlapMode
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Bool
b <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        OverlapFlag -> IO OverlapFlag
forall (m :: * -> *) a. Monad m => a -> m a
return OverlapFlag :: OverlapMode -> Bool -> OverlapFlag
OverlapFlag { overlapMode :: OverlapMode
overlapMode = OverlapMode
h, isSafeOverlap :: Bool
isSafeOverlap = Bool
b }

instance Binary FixityDirection where
    put_ :: BinHandle -> FixityDirection -> IO ()
put_ BinHandle
bh FixityDirection
InfixL = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    put_ BinHandle
bh FixityDirection
InfixR = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    put_ BinHandle
bh FixityDirection
InfixN = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
    get :: BinHandle -> IO FixityDirection
get BinHandle
bh = do
            Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
            case Word8
h of
              Word8
0 -> do FixityDirection -> IO FixityDirection
forall (m :: * -> *) a. Monad m => a -> m a
return FixityDirection
InfixL
              Word8
1 -> do FixityDirection -> IO FixityDirection
forall (m :: * -> *) a. Monad m => a -> m a
return FixityDirection
InfixR
              Word8
_ -> do FixityDirection -> IO FixityDirection
forall (m :: * -> *) a. Monad m => a -> m a
return FixityDirection
InfixN

instance Binary Fixity where
    put_ :: BinHandle -> Fixity -> IO ()
put_ BinHandle
bh (Fixity SourceText
src Int
aa FixityDirection
ab) = do
            BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
src
            BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
aa
            BinHandle -> FixityDirection -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh FixityDirection
ab
    get :: BinHandle -> IO Fixity
get BinHandle
bh = do
          SourceText
src <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Int
aa <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          FixityDirection
ab <- BinHandle -> IO FixityDirection
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
          Fixity -> IO Fixity
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> Int -> FixityDirection -> Fixity
Fixity SourceText
src Int
aa FixityDirection
ab)

instance Binary WarningTxt where
    put_ :: BinHandle -> WarningTxt -> IO ()
put_ BinHandle
bh (WarningTxt Located SourceText
s [Located StringLiteral]
w) = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
            BinHandle -> Located SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Located SourceText
s
            BinHandle -> [Located StringLiteral] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Located StringLiteral]
w
    put_ BinHandle
bh (DeprecatedTxt Located SourceText
s [Located StringLiteral]
d) = do
            BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
            BinHandle -> Located SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Located SourceText
s
            BinHandle -> [Located StringLiteral] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Located StringLiteral]
d

    get :: BinHandle -> IO WarningTxt
get BinHandle
bh = do
            Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
            case Word8
h of
              Word8
0 -> do Located SourceText
s <- BinHandle -> IO (Located SourceText)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      [Located StringLiteral]
w <- BinHandle -> IO [Located StringLiteral]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      WarningTxt -> IO WarningTxt
forall (m :: * -> *) a. Monad m => a -> m a
return (Located SourceText -> [Located StringLiteral] -> WarningTxt
WarningTxt Located SourceText
s [Located StringLiteral]
w)
              Word8
_ -> do Located SourceText
s <- BinHandle -> IO (Located SourceText)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      [Located StringLiteral]
d <- BinHandle -> IO [Located StringLiteral]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                      WarningTxt -> IO WarningTxt
forall (m :: * -> *) a. Monad m => a -> m a
return (Located SourceText -> [Located StringLiteral] -> WarningTxt
DeprecatedTxt Located SourceText
s [Located StringLiteral]
d)

instance Binary StringLiteral where
  put_ :: BinHandle -> StringLiteral -> IO ()
put_ BinHandle
bh (StringLiteral SourceText
st FastString
fs) = do
            BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
st
            BinHandle -> FastString -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh FastString
fs
  get :: BinHandle -> IO StringLiteral
get BinHandle
bh = do
            SourceText
st <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            FastString
fs <- BinHandle -> IO FastString
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            StringLiteral -> IO StringLiteral
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> FastString -> StringLiteral
StringLiteral SourceText
st FastString
fs)

instance Binary a => Binary (Located a) where
    put_ :: BinHandle -> Located a -> IO ()
put_ BinHandle
bh (L SrcSpan
l a
x) = do
            BinHandle -> SrcSpan -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SrcSpan
l
            BinHandle -> a -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh a
x

    get :: BinHandle -> IO (Located a)
get BinHandle
bh = do
            SrcSpan
l <- BinHandle -> IO SrcSpan
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            a
x <- BinHandle -> IO a
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Located a -> IO (Located a)
forall (m :: * -> *) a. Monad m => a -> m a
return (SrcSpan -> a -> Located a
forall l e. l -> e -> GenLocated l e
L SrcSpan
l a
x)

instance Binary RealSrcSpan where
  put_ :: BinHandle -> RealSrcSpan -> IO ()
put_ BinHandle
bh RealSrcSpan
ss = do
            BinHandle -> FastString -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (RealSrcSpan -> FastString
srcSpanFile RealSrcSpan
ss)
            BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (RealSrcSpan -> Int
srcSpanStartLine RealSrcSpan
ss)
            BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (RealSrcSpan -> Int
srcSpanStartCol RealSrcSpan
ss)
            BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (RealSrcSpan -> Int
srcSpanEndLine RealSrcSpan
ss)
            BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (RealSrcSpan -> Int
srcSpanEndCol RealSrcSpan
ss)

  get :: BinHandle -> IO RealSrcSpan
get BinHandle
bh = do
            FastString
f <- BinHandle -> IO FastString
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Int
sl <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Int
sc <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Int
el <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            Int
ec <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            RealSrcSpan -> IO RealSrcSpan
forall (m :: * -> *) a. Monad m => a -> m a
return (RealSrcLoc -> RealSrcLoc -> RealSrcSpan
mkRealSrcSpan (FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
f Int
sl Int
sc)
                                  (FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc FastString
f Int
el Int
ec))

instance Binary BufPos where
  put_ :: BinHandle -> BufPos -> IO ()
put_ BinHandle
bh (BufPos Int
i) = BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
i
  get :: BinHandle -> IO BufPos
get BinHandle
bh = Int -> BufPos
BufPos (Int -> BufPos) -> IO Int -> IO BufPos
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh

instance Binary BufSpan where
  put_ :: BinHandle -> BufSpan -> IO ()
put_ BinHandle
bh (BufSpan BufPos
start BufPos
end) = do
    BinHandle -> BufPos -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh BufPos
start
    BinHandle -> BufPos -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh BufPos
end
  get :: BinHandle -> IO BufSpan
get BinHandle
bh = do
    BufPos
start <- BinHandle -> IO BufPos
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    BufPos
end <- BinHandle -> IO BufPos
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
    BufSpan -> IO BufSpan
forall (m :: * -> *) a. Monad m => a -> m a
return (BufPos -> BufPos -> BufSpan
BufSpan BufPos
start BufPos
end)

instance Binary UnhelpfulSpanReason where
  put_ :: BinHandle -> UnhelpfulSpanReason -> IO ()
put_ BinHandle
bh UnhelpfulSpanReason
r = case UnhelpfulSpanReason
r of
    UnhelpfulSpanReason
UnhelpfulNoLocationInfo -> BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
    UnhelpfulSpanReason
UnhelpfulWiredIn        -> BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
    UnhelpfulSpanReason
UnhelpfulInteractive    -> BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
    UnhelpfulSpanReason
UnhelpfulGenerated      -> BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
    UnhelpfulOther FastString
fs       -> BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4 IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> FastString -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh FastString
fs

  get :: BinHandle -> IO UnhelpfulSpanReason
get BinHandle
bh = do
    Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
    case Word8
h of
      Word8
0 -> UnhelpfulSpanReason -> IO UnhelpfulSpanReason
forall (m :: * -> *) a. Monad m => a -> m a
return UnhelpfulSpanReason
UnhelpfulNoLocationInfo
      Word8
1 -> UnhelpfulSpanReason -> IO UnhelpfulSpanReason
forall (m :: * -> *) a. Monad m => a -> m a
return UnhelpfulSpanReason
UnhelpfulWiredIn
      Word8
2 -> UnhelpfulSpanReason -> IO UnhelpfulSpanReason
forall (m :: * -> *) a. Monad m => a -> m a
return UnhelpfulSpanReason
UnhelpfulInteractive
      Word8
3 -> UnhelpfulSpanReason -> IO UnhelpfulSpanReason
forall (m :: * -> *) a. Monad m => a -> m a
return UnhelpfulSpanReason
UnhelpfulGenerated
      Word8
_ -> FastString -> UnhelpfulSpanReason
UnhelpfulOther (FastString -> UnhelpfulSpanReason)
-> IO FastString -> IO UnhelpfulSpanReason
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BinHandle -> IO FastString
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh

instance Binary SrcSpan where
  put_ :: BinHandle -> SrcSpan -> IO ()
put_ BinHandle
bh (RealSrcSpan RealSrcSpan
ss Maybe BufSpan
sb) = do
          BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
          BinHandle -> RealSrcSpan -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh RealSrcSpan
ss
          BinHandle -> Maybe BufSpan -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe BufSpan
sb

  put_ BinHandle
bh (UnhelpfulSpan UnhelpfulSpanReason
s) = do
          BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
          BinHandle -> UnhelpfulSpanReason -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh UnhelpfulSpanReason
s

  get :: BinHandle -> IO SrcSpan
get BinHandle
bh = do
          Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
          case Word8
h of
            Word8
0 -> do RealSrcSpan
ss <- BinHandle -> IO RealSrcSpan
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                    Maybe BufSpan
sb <- BinHandle -> IO (Maybe BufSpan)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                    SrcSpan -> IO SrcSpan
forall (m :: * -> *) a. Monad m => a -> m a
return (RealSrcSpan -> Maybe BufSpan -> SrcSpan
RealSrcSpan RealSrcSpan
ss Maybe BufSpan
sb)
            Word8
_ -> do UnhelpfulSpanReason
s <- BinHandle -> IO UnhelpfulSpanReason
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
                    SrcSpan -> IO SrcSpan
forall (m :: * -> *) a. Monad m => a -> m a
return (UnhelpfulSpanReason -> SrcSpan
UnhelpfulSpan UnhelpfulSpanReason
s)

instance Binary Serialized where
    put_ :: BinHandle -> Serialized -> IO ()
put_ BinHandle
bh (Serialized SomeTypeRep
the_type [Word8]
bytes) = do
        BinHandle -> SomeTypeRep -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SomeTypeRep
the_type
        BinHandle -> [Word8] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Word8]
bytes
    get :: BinHandle -> IO Serialized
get BinHandle
bh = do
        SomeTypeRep
the_type <- BinHandle -> IO SomeTypeRep
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        [Word8]
bytes <- BinHandle -> IO [Word8]
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        Serialized -> IO Serialized
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeTypeRep -> [Word8] -> Serialized
Serialized SomeTypeRep
the_type [Word8]
bytes)

instance Binary SourceText where
  put_ :: BinHandle -> SourceText -> IO ()
put_ BinHandle
bh SourceText
NoSourceText = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
  put_ BinHandle
bh (SourceText String
s) = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
        BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh String
s

  get :: BinHandle -> IO SourceText
get BinHandle
bh = do
    Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
    case Word8
h of
      Word8
0 -> SourceText -> IO SourceText
forall (m :: * -> *) a. Monad m => a -> m a
return SourceText
NoSourceText
      Word8
1 -> do
        String
s <- BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        SourceText -> IO SourceText
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> SourceText
SourceText String
s)
      Word8
_ -> String -> IO SourceText
forall a. String -> a
panic (String -> IO SourceText) -> String -> IO SourceText
forall a b. (a -> b) -> a -> b
$ String
"Binary SourceText:" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
h