{-# LANGUAGE CPP #-}
module Codec.Picture.InternalHelper ( runGet
                                    , runGetStrict
                                    , decode
                                    , getRemainingBytes
                                    , getRemainingLazyBytes ) where

import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import Data.Binary( Binary( get ) )
import Data.Binary.Get( Get
                      , getRemainingLazyByteString
                      )
import qualified Data.Binary.Get as G

#if MIN_VERSION_binary(0,6,4)
#else
import Control.Applicative( (<$>) )
import qualified Control.Exception as E
-- I feel so dirty. :(
import System.IO.Unsafe( unsafePerformIO )
#endif

decode :: (Binary a) => B.ByteString -> Either String a
decode :: ByteString -> Either String a
decode = Get a -> ByteString -> Either String a
forall a. Get a -> ByteString -> Either String a
runGetStrict Get a
forall t. Binary t => Get t
get

runGet :: Get a -> L.ByteString -> Either String a
#if MIN_VERSION_binary(0,6,4)
runGet :: Get a -> ByteString -> Either String a
runGet Get a
act = Either (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
-> Either String a
forall a b a a b b. Either (a, b, a) (a, b, b) -> Either a b
unpack (Either
   (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
 -> Either String a)
-> (ByteString
    -> Either
         (ByteString, ByteOffset, String) (ByteString, ByteOffset, a))
-> ByteString
-> Either String a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Get a
-> ByteString
-> Either
     (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
forall a.
Get a
-> ByteString
-> Either
     (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
G.runGetOrFail Get a
act
    where unpack :: Either (a, b, a) (a, b, b) -> Either a b
unpack (Left (a
_, b
_, a
str)) = a -> Either a b
forall a b. a -> Either a b
Left a
str
          unpack (Right (a
_, b
_, b
element)) = b -> Either a b
forall a b. b -> Either a b
Right b
element
#else
runGet act str = unsafePerformIO $ E.catch
    (Right <$> E.evaluate (G.runGet act str))
    (\msg -> return . Left $ show (msg :: E.SomeException))
#endif

runGetStrict :: Get a -> B.ByteString -> Either String a
runGetStrict :: Get a -> ByteString -> Either String a
runGetStrict Get a
act ByteString
buffer = Get a -> ByteString -> Either String a
forall a. Get a -> ByteString -> Either String a
runGet Get a
act (ByteString -> Either String a) -> ByteString -> Either String a
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
L.fromChunks [ByteString
buffer]

getRemainingBytes :: Get B.ByteString
getRemainingBytes :: Get ByteString
getRemainingBytes = do
    ByteString
rest <- Get ByteString
getRemainingLazyByteString 
    ByteString -> Get ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Get ByteString) -> ByteString -> Get ByteString
forall a b. (a -> b) -> a -> b
$ case ByteString -> [ByteString]
L.toChunks ByteString
rest of
        [] -> ByteString
B.empty
        [ByteString
a] -> ByteString
a
        [ByteString]
lst -> [ByteString] -> ByteString
B.concat [ByteString]
lst

getRemainingLazyBytes :: Get L.ByteString
getRemainingLazyBytes :: Get ByteString
getRemainingLazyBytes = Get ByteString
getRemainingLazyByteString