{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 711
{-# LANGUAGE PatternSynonyms #-}
#endif

#ifndef MIN_VERSION_binary
#define MIN_VERSION_binary(x, y, z) 0
#endif

module Distribution.Compat.Binary
       ( decodeOrFailIO
       , decodeFileOrFail'
#if __GLASGOW_HASKELL__ >= 708 || MIN_VERSION_binary(0,7,0)
       , module Data.Binary
#else
       , Binary(..)
       , decode, encode, encodeFile
#endif
       ) where

import Control.Exception (ErrorCall (..), catch, evaluate)
import Data.ByteString.Lazy (ByteString)

#if __GLASGOW_HASKELL__ >= 708 || MIN_VERSION_binary(0,7,0)

import Data.Binary

-- | Lazily reconstruct a value previously written to a file.
decodeFileOrFail' :: Binary a => FilePath -> IO (Either String a)
decodeFileOrFail' :: FilePath -> IO (Either FilePath a)
decodeFileOrFail' FilePath
f = ((ByteOffset, FilePath) -> Either FilePath a)
-> (a -> Either FilePath a)
-> Either (ByteOffset, FilePath) a
-> Either FilePath a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (FilePath -> Either FilePath a
forall a b. a -> Either a b
Left (FilePath -> Either FilePath a)
-> ((ByteOffset, FilePath) -> FilePath)
-> (ByteOffset, FilePath)
-> Either FilePath a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteOffset, FilePath) -> FilePath
forall a b. (a, b) -> b
snd) a -> Either FilePath a
forall a b. b -> Either a b
Right (Either (ByteOffset, FilePath) a -> Either FilePath a)
-> IO (Either (ByteOffset, FilePath) a) -> IO (Either FilePath a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` FilePath -> IO (Either (ByteOffset, FilePath) a)
forall a.
Binary a =>
FilePath -> IO (Either (ByteOffset, FilePath) a)
decodeFileOrFail FilePath
f

#else

import Data.Binary.Get
import Data.Binary.Put
import qualified Data.ByteString.Lazy as BSL

import Distribution.Compat.Binary.Class
import Distribution.Compat.Binary.Generic ()

-- | Decode a value from a lazy ByteString, reconstructing the
-- original structure.
--
decode :: Binary a => ByteString -> a
decode = runGet get

-- | Encode a value using binary serialisation to a lazy ByteString.
--
encode :: Binary a => a -> ByteString
encode = runPut . put
{-# INLINE encode #-}

-- | Lazily reconstruct a value previously written to a file.
decodeFileOrFail' :: Binary a => FilePath -> IO (Either String a)
decodeFileOrFail' f = decodeOrFailIO =<< BSL.readFile f

-- | Lazily serialise a value to a file
encodeFile :: Binary a => FilePath -> a -> IO ()
encodeFile f = BSL.writeFile f . encode

#endif

decodeOrFailIO :: Binary a => ByteString -> IO (Either String a)
decodeOrFailIO :: ByteString -> IO (Either FilePath a)
decodeOrFailIO ByteString
bs =
    IO (Either FilePath a)
-> (ErrorCall -> IO (Either FilePath a)) -> IO (Either FilePath a)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch (a -> IO a
forall a. a -> IO a
evaluate (ByteString -> a
forall a. Binary a => ByteString -> a
decode ByteString
bs) IO a -> (a -> IO (Either FilePath a)) -> IO (Either FilePath a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Either FilePath a -> IO (Either FilePath a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either FilePath a -> IO (Either FilePath a))
-> (a -> Either FilePath a) -> a -> IO (Either FilePath a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Either FilePath a
forall a b. b -> Either a b
Right) ErrorCall -> IO (Either FilePath a)
forall (m :: * -> *) b.
Monad m =>
ErrorCall -> m (Either FilePath b)
handler
  where
#if MIN_VERSION_base(4,9,0)
    handler :: ErrorCall -> m (Either FilePath b)
handler (ErrorCallWithLocation FilePath
str FilePath
_) = Either FilePath b -> m (Either FilePath b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either FilePath b -> m (Either FilePath b))
-> Either FilePath b -> m (Either FilePath b)
forall a b. (a -> b) -> a -> b
$ FilePath -> Either FilePath b
forall a b. a -> Either a b
Left FilePath
str
#else
    handler (ErrorCall str) = return $ Left str
#endif