{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Copyright   :  (C) 2013-2015 Edward Kmett and Anthony Cowley
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
--
-- Serialization of statically-sized types with the "Data.Binary"
-- library.
------------------------------------------------------------------------------
module Linear.Binary
  ( putLinear
  , getLinear
  ) where

#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Data.Binary
#if __GLASGOW_HASKELL__ < 710
import Data.Foldable (Foldable, traverse_)
import Data.Traversable (Traversable, sequenceA)
#else
import Data.Foldable (traverse_)
#endif

-- | Serialize a linear type.
putLinear :: (Binary a, Foldable t) => t a -> Put
putLinear :: t a -> Put
putLinear = (a -> Put) -> t a -> Put
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ a -> Put
forall t. Binary t => t -> Put
put

-- | Deserialize a linear type.
getLinear :: (Binary a, Applicative t, Traversable t) => Get (t a)
getLinear :: Get (t a)
getLinear = t (Get a) -> Get (t a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (t (Get a) -> Get (t a)) -> t (Get a) -> Get (t a)
forall a b. (a -> b) -> a -> b
$ Get a -> t (Get a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Get a
forall t. Binary t => Get t
get