{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Bytes.Put
  ( MonadPut(..)
  , runPutL
  , runPutS
  ) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
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.Put as B
import Data.ByteString as Strict
import Data.ByteString.Lazy as Lazy
import qualified Data.Serialize.Put as S
import Data.Word
class (Applicative m, Monad m) => MonadPut m where
  
  putWord8 :: Word8 -> m ()
#ifndef HLINT
  default putWord8 :: (m ~ t n, MonadTrans t, MonadPut n) => Word8 -> m ()
  putWord8 = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word8 -> n ()) -> Word8 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> n ()
forall (m :: * -> *). MonadPut m => Word8 -> m ()
putWord8
  {-# INLINE putWord8 #-}
#endif
  
  
  
  putByteString     :: Strict.ByteString -> m ()
#ifndef HLINT
  default putByteString :: (m ~ t n, MonadTrans t, MonadPut n) => Strict.ByteString -> m ()
  putByteString = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (ByteString -> n ()) -> ByteString -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> n ()
forall (m :: * -> *). MonadPut m => ByteString -> m ()
putByteString
  {-# INLINE putByteString #-}
#endif
  
  
  
  putLazyByteString :: Lazy.ByteString -> m ()
#ifndef HLINT
  default putLazyByteString :: (m ~ t n, MonadTrans t, MonadPut n) => Lazy.ByteString -> m ()
  putLazyByteString = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (ByteString -> n ()) -> ByteString -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> n ()
forall (m :: * -> *). MonadPut m => ByteString -> m ()
putLazyByteString
  {-# INLINE putLazyByteString #-}
#endif
  
  
  
  
  flush :: m ()
#ifndef HLINT
  default flush :: (m ~ t n, MonadTrans t, MonadPut n) => m ()
  flush = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift n ()
forall (m :: * -> *). MonadPut m => m ()
flush
  {-# INLINE flush #-}
#endif
  
  putWord16le   :: Word16 -> m ()
#ifndef HLINT
  default putWord16le :: (m ~ t n, MonadTrans t, MonadPut n) => Word16 -> m ()
  putWord16le = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word16 -> n ()) -> Word16 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> n ()
forall (m :: * -> *). MonadPut m => Word16 -> m ()
putWord16le
  {-# INLINE putWord16le #-}
#endif
  
  putWord16be   :: Word16 -> m ()
#ifndef HLINT
  default putWord16be :: (m ~ t n, MonadTrans t, MonadPut n) => Word16 -> m ()
  putWord16be = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word16 -> n ()) -> Word16 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> n ()
forall (m :: * -> *). MonadPut m => Word16 -> m ()
putWord16be
  {-# INLINE putWord16be #-}
#endif
  
  
  putWord16host :: Word16 -> m ()
#ifndef HLINT
  default putWord16host :: (m ~ t n, MonadTrans t, MonadPut n) => Word16 -> m ()
  putWord16host = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word16 -> n ()) -> Word16 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> n ()
forall (m :: * -> *). MonadPut m => Word16 -> m ()
putWord16host
  {-# INLINE putWord16host #-}
#endif
  
  putWord32le   :: Word32 -> m ()
#ifndef HLINT
  default putWord32le :: (m ~ t n, MonadTrans t, MonadPut n) => Word32 -> m ()
  putWord32le = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word32 -> n ()) -> Word32 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> n ()
forall (m :: * -> *). MonadPut m => Word32 -> m ()
putWord32le
  {-# INLINE putWord32le #-}
#endif
  
  putWord32be   :: Word32 -> m ()
#ifndef HLINT
  default putWord32be :: (m ~ t n, MonadTrans t, MonadPut n) => Word32 -> m ()
  putWord32be = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word32 -> n ()) -> Word32 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> n ()
forall (m :: * -> *). MonadPut m => Word32 -> m ()
putWord32be
  {-# INLINE putWord32be #-}
#endif
  
  
  putWord32host :: Word32 -> m ()
#ifndef HLINT
  default putWord32host :: (m ~ t n, MonadTrans t, MonadPut n) => Word32 -> m ()
  putWord32host = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word32 -> n ()) -> Word32 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> n ()
forall (m :: * -> *). MonadPut m => Word32 -> m ()
putWord32host
  {-# INLINE putWord32host #-}
#endif
  
  putWord64le   :: Word64 -> m ()
#ifndef HLINT
  default putWord64le :: (m ~ t n, MonadTrans t, MonadPut n) => Word64 -> m ()
  putWord64le = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word64 -> n ()) -> Word64 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> n ()
forall (m :: * -> *). MonadPut m => Word64 -> m ()
putWord64le
  {-# INLINE putWord64le #-}
#endif
  
  putWord64be   :: Word64 -> m ()
#ifndef HLINT
  default putWord64be :: (m ~ t n, MonadTrans t, MonadPut n) => Word64 -> m ()
  putWord64be = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word64 -> n ()) -> Word64 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> n ()
forall (m :: * -> *). MonadPut m => Word64 -> m ()
putWord64be
  {-# INLINE putWord64be #-}
#endif
  
  
  putWord64host :: Word64 -> m ()
#ifndef HLINT
  default putWord64host :: (m ~ t n, MonadTrans t, MonadPut n) => Word64 -> m ()
  putWord64host = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word64 -> n ()) -> Word64 -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> n ()
forall (m :: * -> *). MonadPut m => Word64 -> m ()
putWord64host
  {-# INLINE putWord64host #-}
#endif
  
  
  
  
  
  putWordhost :: Word -> m ()
#ifndef HLINT
  default putWordhost :: (m ~ t n, MonadTrans t, MonadPut n) => Word -> m ()
  putWordhost = n () -> t n ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (n () -> t n ()) -> (Word -> n ()) -> Word -> t n ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> n ()
forall (m :: * -> *). MonadPut m => Word -> m ()
putWordhost
  {-# INLINE putWordhost #-}
#endif
instance MonadPut B.PutM where
  putWord8 :: Word8 -> PutM ()
putWord8 = Word8 -> PutM ()
B.putWord8
  {-# INLINE putWord8 #-}
  putByteString :: ByteString -> PutM ()
putByteString = ByteString -> PutM ()
B.putByteString
  {-# INLINE putByteString #-}
  putLazyByteString :: ByteString -> PutM ()
putLazyByteString = ByteString -> PutM ()
B.putLazyByteString
  {-# INLINE putLazyByteString #-}
  flush :: PutM ()
flush = PutM ()
B.flush
  {-# INLINE flush #-}
  putWord16le :: Word16 -> PutM ()
putWord16le   = Word16 -> PutM ()
B.putWord16le
  {-# INLINE putWord16le #-}
  putWord16be :: Word16 -> PutM ()
putWord16be   = Word16 -> PutM ()
B.putWord16be
  {-# INLINE putWord16be #-}
  putWord16host :: Word16 -> PutM ()
putWord16host = Word16 -> PutM ()
B.putWord16host
  {-# INLINE putWord16host #-}
  putWord32le :: Word32 -> PutM ()
putWord32le   = Word32 -> PutM ()
B.putWord32le
  {-# INLINE putWord32le #-}
  putWord32be :: Word32 -> PutM ()
putWord32be   = Word32 -> PutM ()
B.putWord32be
  {-# INLINE putWord32be #-}
  putWord32host :: Word32 -> PutM ()
putWord32host = Word32 -> PutM ()
B.putWord32host
  {-# INLINE putWord32host #-}
  putWord64le :: Word64 -> PutM ()
putWord64le   = Word64 -> PutM ()
B.putWord64le
  {-# INLINE putWord64le #-}
  putWord64be :: Word64 -> PutM ()
putWord64be   = Word64 -> PutM ()
B.putWord64be
  {-# INLINE putWord64be #-}
  putWord64host :: Word64 -> PutM ()
putWord64host = Word64 -> PutM ()
B.putWord64host
  {-# INLINE putWord64host #-}
  putWordhost :: Word -> PutM ()
putWordhost   = Word -> PutM ()
B.putWordhost
  {-# INLINE putWordhost #-}
instance MonadPut S.PutM where
  putWord8 :: Word8 -> PutM ()
putWord8 = Word8 -> PutM ()
S.putWord8
  {-# INLINE putWord8 #-}
  putByteString :: ByteString -> PutM ()
putByteString = ByteString -> PutM ()
S.putByteString
  {-# INLINE putByteString #-}
  putLazyByteString :: ByteString -> PutM ()
putLazyByteString = ByteString -> PutM ()
S.putLazyByteString
  {-# INLINE putLazyByteString #-}
  flush :: PutM ()
flush = PutM ()
S.flush
  {-# INLINE flush #-}
  putWord16le :: Word16 -> PutM ()
putWord16le   = Word16 -> PutM ()
S.putWord16le
  {-# INLINE putWord16le #-}
  putWord16be :: Word16 -> PutM ()
putWord16be   = Word16 -> PutM ()
S.putWord16be
  {-# INLINE putWord16be #-}
  putWord16host :: Word16 -> PutM ()
putWord16host = Word16 -> PutM ()
S.putWord16host
  {-# INLINE putWord16host #-}
  putWord32le :: Word32 -> PutM ()
putWord32le   = Word32 -> PutM ()
S.putWord32le
  {-# INLINE putWord32le #-}
  putWord32be :: Word32 -> PutM ()
putWord32be   = Word32 -> PutM ()
S.putWord32be
  {-# INLINE putWord32be #-}
  putWord32host :: Word32 -> PutM ()
putWord32host = Word32 -> PutM ()
S.putWord32host
  {-# INLINE putWord32host #-}
  putWord64le :: Word64 -> PutM ()
putWord64le   = Word64 -> PutM ()
S.putWord64le
  {-# INLINE putWord64le #-}
  putWord64be :: Word64 -> PutM ()
putWord64be   = Word64 -> PutM ()
S.putWord64be
  {-# INLINE putWord64be #-}
  putWord64host :: Word64 -> PutM ()
putWord64host = Word64 -> PutM ()
S.putWord64host
  {-# INLINE putWord64host #-}
  putWordhost :: Word -> PutM ()
putWordhost   = Word -> PutM ()
S.putWordhost
  {-# INLINE putWordhost #-}
instance MonadPut m => MonadPut (Lazy.StateT s m)
instance MonadPut m => MonadPut (Strict.StateT s m)
instance MonadPut m => MonadPut (ReaderT e m)
instance (MonadPut m, Monoid w) => MonadPut (Lazy.WriterT w m)
instance (MonadPut m, Monoid w) => MonadPut (Strict.WriterT w m)
instance (MonadPut m, Monoid w) => MonadPut (Lazy.RWST r w s m)
instance (MonadPut m, Monoid w) => MonadPut (Strict.RWST r w s m)
instance (MonadPut m) => MonadPut (ExceptT e m) where
runPutL :: B.Put -> Lazy.ByteString
runPutL :: PutM () -> ByteString
runPutL = PutM () -> ByteString
B.runPut
runPutS :: S.Put -> Strict.ByteString
runPutS :: PutM () -> ByteString
runPutS = PutM () -> ByteString
S.runPut