module Data.Bytes.Get
  ( MonadGet(..)
  , runGetL
  , runGetS
  ) where
import Control.Applicative
import Control.Monad.Reader
import Control.Monad.Trans.Except as Except
import Control.Monad.RWS.Lazy as Lazy
import Control.Monad.RWS.Strict as Strict
import Control.Monad.State.Lazy as Lazy
import Control.Monad.State.Strict as Strict
import Control.Monad.Writer.Lazy as Lazy
import Control.Monad.Writer.Strict as Strict
import qualified Data.Binary.Get as B
import qualified Data.ByteString.Lazy as Lazy
import qualified Data.ByteString as Strict
import Data.Int
import qualified Data.Serialize.Get as S
import Data.Word
class (Integral (Remaining m), Monad m, Applicative m) => MonadGet m where
  
  type Remaining m :: *
  
  type Bytes m :: *
  
  skip :: Int -> m ()
#ifndef HLINT
  default skip :: (MonadTrans t, MonadGet n, m ~ t n) => Int -> m ()
  skip = lift . skip
#endif
  
  
  ensure :: Int -> m Strict.ByteString
#ifndef HLINT
  default ensure :: (MonadTrans t, MonadGet n, m ~ t n) => Int -> m Strict.ByteString
  ensure = lift . ensure
#endif
  
  
  lookAhead :: m a -> m a
  
  
  lookAheadM :: m (Maybe a) -> m (Maybe a)
  
  
  lookAheadE :: m (Either a b) -> m (Either a b)
  
  getBytes :: Int -> m Strict.ByteString
#ifndef HLINT
  default getBytes :: (MonadTrans t, MonadGet n, m ~ t n) => Int -> m Strict.ByteString
  getBytes = lift . getBytes
#endif
  
  
  
  remaining :: m (Remaining m)
#ifndef HLINT
  default remaining :: (MonadTrans t, MonadGet n, m ~ t n) => m (Remaining n)
  remaining = lift remaining
#endif
  
  
  isEmpty :: m Bool
#ifndef HLINT
  default isEmpty :: (MonadTrans t, MonadGet n, m ~ t n) => m Bool
  isEmpty = lift isEmpty
#endif
  
  getWord8 :: m Word8
#ifndef HLINT
  default getWord8 :: (MonadTrans t, MonadGet n, m ~ t n) => m Word8
  getWord8 = lift getWord8
#endif
  
  
  getByteString :: Int -> m Strict.ByteString
#ifndef HLINT
  default getByteString :: (MonadTrans t, MonadGet n, m ~ t n) => Int -> m Strict.ByteString
  getByteString = lift . getByteString
#endif
  
  
  getLazyByteString :: Int64 -> m Lazy.ByteString
#ifndef HLINT
  default getLazyByteString :: (MonadTrans t, MonadGet n, m ~ t n) => Int64 -> m Lazy.ByteString
  getLazyByteString = lift . getLazyByteString
#endif
  
  getWord16be   :: m Word16
#ifndef HLINT
  default getWord16be :: (MonadTrans t, MonadGet n, m ~ t n) => m Word16
  getWord16be = lift getWord16be
#endif
  
  getWord16le   :: m Word16
#ifndef HLINT
  default getWord16le :: (MonadTrans t, MonadGet n, m ~ t n) => m Word16
  getWord16le = lift getWord16le
#endif
  
  getWord16host :: m Word16
#ifndef HLINT
  default getWord16host :: (MonadTrans t, MonadGet n, m ~ t n) => m Word16
  getWord16host = lift getWord16host
#endif
  
  getWord32be   :: m Word32
#ifndef HLINT
  default getWord32be :: (MonadTrans t, MonadGet n, m ~ t n) => m Word32
  getWord32be = lift getWord32be
#endif
  
  getWord32le   :: m Word32
#ifndef HLINT
  default getWord32le :: (MonadTrans t, MonadGet n, m ~ t n) => m Word32
  getWord32le = lift getWord32le
#endif
  
  getWord32host :: m Word32
#ifndef HLINT
  default getWord32host :: (MonadTrans t, MonadGet n, m ~ t n) => m Word32
  getWord32host = lift getWord32host
#endif
  
  getWord64be   :: m Word64
#ifndef HLINT
  default getWord64be :: (MonadTrans t, MonadGet n, m ~ t n) => m Word64
  getWord64be = lift getWord64be
#endif
  
  getWord64le   :: m Word64
#ifndef HLINT
  default getWord64le :: (MonadTrans t, MonadGet n, m ~ t n) => m Word64
  getWord64le = lift getWord64le
#endif
  
  getWord64host :: m Word64
#ifndef HLINT
  default getWord64host :: (MonadTrans t, MonadGet n, m ~ t n) => m Word64
  getWord64host = lift getWord64host
#endif
  
  
  
  getWordhost :: m Word
#ifndef HLINT
  default getWordhost :: (MonadTrans t, MonadGet n, m ~ t n) => m Word
  getWordhost = lift getWordhost
#endif
instance MonadGet B.Get where
  type Remaining B.Get = Int64
  type Bytes B.Get = Lazy.ByteString
  skip = B.skip
  
  lookAhead = B.lookAhead
  
  lookAheadM = B.lookAheadM
  
  lookAheadE = B.lookAheadE
  
  ensure n = do
    bs <- lookAhead $ getByteString n
    unless (Strict.length bs >= n) $ fail "ensure: Required more bytes"
    return bs
  
  getBytes = B.getByteString
  
  remaining = B.remaining
  
  isEmpty = B.isEmpty
  
  getWord8 = B.getWord8
  
  getByteString = B.getByteString
  
  getLazyByteString = B.getLazyByteString
  
  getWord16be   = B.getWord16be
  
  getWord16le   = B.getWord16le
  
  getWord16host = B.getWord16host
  
  getWord32be   = B.getWord32be
  
  getWord32le   = B.getWord32le
  
  getWord32host = B.getWord32host
  
  getWord64be   = B.getWord64be
  
  getWord64le   = B.getWord64le
  
  getWord64host = B.getWord64host
  
  getWordhost   = B.getWordhost
  
instance MonadGet S.Get where
  type Remaining S.Get = Int
  type Bytes S.Get = Strict.ByteString
  skip = S.skip
  
  lookAhead = S.lookAhead
  
  lookAheadM = S.lookAheadM
  
  lookAheadE = S.lookAheadE
  
  getBytes = S.getBytes
  
  ensure = S.ensure
  
  remaining = S.remaining
  
  isEmpty = S.isEmpty
  
  getWord8 = S.getWord8
  
  getByteString = S.getByteString
  
  getLazyByteString = S.getLazyByteString
  
  getWord16be   = S.getWord16be
  
  getWord16le   = S.getWord16le
  
  getWord16host = S.getWord16host
  
  getWord32be   = S.getWord32be
  
  getWord32le   = S.getWord32le
  
  getWord32host = S.getWord32host
  
  getWord64be   = S.getWord64be
  
  getWord64le   = S.getWord64le
  
  getWord64host = S.getWord64host
  
  getWordhost   = S.getWordhost
  
instance MonadGet m => MonadGet (Lazy.StateT s m) where
  type Remaining (Lazy.StateT s m) = Remaining m
  type Bytes (Lazy.StateT s m) = Bytes m
  lookAhead (Lazy.StateT m) = Lazy.StateT (lookAhead . m)
  
  lookAheadM (Lazy.StateT m) = Lazy.StateT (liftM factor . lookAheadE . liftM distribute . m)
    where
    distribute (Nothing, s') = Left (Nothing, s')
    distribute (Just a, s') = Right (Just a, s')
    factor = either id id
  
  lookAheadE (Lazy.StateT m) = Lazy.StateT (liftM factor . lookAheadE . liftM distribute . m)
    where
    distribute (Left a, s') = Left (Left a, s')
    distribute (Right b, s') = Right (Right b, s')
    factor = either id id
  
instance MonadGet m => MonadGet (Strict.StateT s m) where
  type Remaining (Strict.StateT s m) = Remaining m
  type Bytes (Strict.StateT s m) = Bytes m
  lookAhead (Strict.StateT m) = Strict.StateT (lookAhead . m)
  
  lookAheadM (Strict.StateT m) = Strict.StateT (liftM factor . lookAheadE . liftM distribute . m)
    where
    distribute (Nothing, s') = Left (Nothing, s')
    distribute (Just a, s') = Right (Just a, s')
    factor = either id id
  
  lookAheadE (Strict.StateT m) = Strict.StateT (liftM factor . lookAheadE . liftM distribute . m)
    where
    distribute (Left a, s') = Left (Left a, s')
    distribute (Right b, s') = Right (Right b, s')
    factor = either id id
  
instance MonadGet m => MonadGet (ReaderT e m) where
  type Remaining (ReaderT e m) = Remaining m
  type Bytes (ReaderT e m) = Bytes m
  lookAhead (ReaderT m) = ReaderT (lookAhead . m)
  
  lookAheadM (ReaderT m) = ReaderT (lookAheadM . m)
  
  lookAheadE (ReaderT m) = ReaderT (lookAheadE . m)
  
instance (MonadGet m, Monoid w) => MonadGet (Lazy.WriterT w m) where
  type Remaining (Lazy.WriterT w m) = Remaining m
  type Bytes (Lazy.WriterT w m) = Bytes m
  lookAhead (Lazy.WriterT m) = Lazy.WriterT (lookAhead m)
  
  lookAheadM (Lazy.WriterT m) = Lazy.WriterT (liftM factor $ lookAheadE $ liftM distribute m)
    where
    distribute (Nothing, s') = Left (Nothing, s')
    distribute (Just a, s') = Right (Just a, s')
    factor = either id id
  
  lookAheadE (Lazy.WriterT m) = Lazy.WriterT (liftM factor $ lookAheadE $ liftM distribute m)
    where
    distribute (Left a, s') = Left (Left a, s')
    distribute (Right b, s') = Right (Right b, s')
    factor = either id id
  
instance (MonadGet m, Monoid w) => MonadGet (Strict.WriterT w m) where
  type Remaining (Strict.WriterT w m) = Remaining m
  type Bytes (Strict.WriterT w m) = Bytes m
  lookAhead (Strict.WriterT m) = Strict.WriterT (lookAhead m)
  
  lookAheadM (Strict.WriterT m) = Strict.WriterT (liftM factor $ lookAheadE $ liftM distribute m)
    where
    distribute (Nothing, s') = Left (Nothing, s')
    distribute (Just a, s') = Right (Just a, s')
    factor = either id id
  
  lookAheadE (Strict.WriterT m) = Strict.WriterT (liftM factor $ lookAheadE $ liftM distribute m)
    where
    distribute (Left a, s') = Left (Left a, s')
    distribute (Right b, s') = Right (Right b, s')
    factor = either id id
  
instance (MonadGet m, Monoid w) => MonadGet (Strict.RWST r w s m) where
  type Remaining (Strict.RWST r w s m) = Remaining m
  type Bytes (Strict.RWST r w s m) = Bytes m
  lookAhead (Strict.RWST m) = Strict.RWST $ \r s -> lookAhead (m r s)
  
  lookAheadM (Strict.RWST m) = Strict.RWST (\r s -> liftM factor $ lookAheadE $ liftM distribute $ m r s )
    where
    distribute (Nothing, s',w') = Left (Nothing, s', w')
    distribute (Just a, s',w') = Right (Just a, s', w')
    factor = either id id
  
  lookAheadE (Strict.RWST m) = Strict.RWST (\r s -> liftM factor $ lookAheadE $ liftM distribute $ m r s)
    where
    distribute (Left a, s', w') = Left (Left a, s', w')
    distribute (Right b, s', w') = Right (Right b, s', w')
    factor = either id id
  
instance (MonadGet m, Monoid w) => MonadGet (Lazy.RWST r w s m) where
  type Remaining (Lazy.RWST r w s m) = Remaining m
  type Bytes (Lazy.RWST r w s m) = Bytes m
  lookAhead (Lazy.RWST m) = Lazy.RWST $ \r s -> lookAhead (m r s)
  
  lookAheadM (Lazy.RWST m) = Lazy.RWST (\r s -> liftM factor $ lookAheadE $ liftM distribute $ m r s )
    where
    distribute (Nothing, s',w') = Left (Nothing, s', w')
    distribute (Just a, s',w') = Right (Just a, s', w')
    factor = either id id
  
  lookAheadE (Lazy.RWST m) = Lazy.RWST (\r s -> liftM factor $ lookAheadE $ liftM distribute $ m r s)
    where
    distribute (Left a, s', w') = Left (Left a, s', w')
    distribute (Right b, s', w') = Right (Right b, s', w')
    factor = either id id
  
instance MonadGet m => MonadGet (ExceptT e m) where
  type Remaining (ExceptT e m) = Remaining m
  type Bytes (ExceptT e m) = Bytes m
  lookAhead = mapExceptT lookAhead
  
  lookAheadM (ExceptT m) = ExceptT (liftM factor $ lookAheadE $ liftM distribute m)
    where
    distribute (Left e) = (Left (Left e))
    distribute (Right j) = (Right (Right j))
    factor = either id id
  
  lookAheadE (ExceptT m) = ExceptT (liftM factor $ lookAheadE $ liftM distribute m)
    where
    distribute (Left e) = (Left (Left e))
    distribute (Right a) = (Right (Right a))
    factor = either id id
  
runGetL :: B.Get a -> Lazy.ByteString -> a
runGetL = B.runGet
runGetS :: S.Get a -> Strict.ByteString -> Either String a
runGetS = S.runGet