{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE TypeFamilies         #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-- | Module with binary instances for data types defined in fixed
--   vector
module Data.Vector.Fixed.Instances.Binary where

import           Data.Vector.Fixed             (Arity)
import qualified Data.Vector.Fixed           as F
import qualified Data.Vector.Fixed.Boxed     as B
import qualified Data.Vector.Fixed.Unboxed   as U
import qualified Data.Vector.Fixed.Primitive as P
import qualified Data.Vector.Fixed.Storable  as S
import           Data.Binary                   (Binary(..))


instance (Arity n, Binary a) => Binary (B.Vec n a) where
  put :: Vec n a -> Put
put = (a -> Put) -> Vec n a -> Put
forall (v :: * -> *) a (f :: * -> *) b.
(Vector v a, Applicative f) =>
(a -> f b) -> v a -> f ()
F.mapM_ a -> Put
forall t. Binary t => t -> Put
put
  get :: Get (Vec n a)
get = Get a -> Get (Vec n a)
forall (v :: * -> *) a (f :: * -> *).
(Vector v a, Applicative f) =>
f a -> f (v a)
F.replicateM Get a
forall t. Binary t => Get t
get

instance (Arity n, P.Prim a, Binary a) => Binary (P.Vec n a) where
  put :: Vec n a -> Put
put = (a -> Put) -> Vec n a -> Put
forall (v :: * -> *) a (f :: * -> *) b.
(Vector v a, Applicative f) =>
(a -> f b) -> v a -> f ()
F.mapM_ a -> Put
forall t. Binary t => t -> Put
put
  get :: Get (Vec n a)
get = Get a -> Get (Vec n a)
forall (v :: * -> *) a (f :: * -> *).
(Vector v a, Applicative f) =>
f a -> f (v a)
F.replicateM Get a
forall t. Binary t => Get t
get

instance (Arity n, S.Storable a, Binary a) => Binary (S.Vec n a) where
  put :: Vec n a -> Put
put = (a -> Put) -> Vec n a -> Put
forall (v :: * -> *) a (f :: * -> *) b.
(Vector v a, Applicative f) =>
(a -> f b) -> v a -> f ()
F.mapM_ a -> Put
forall t. Binary t => t -> Put
put
  get :: Get (Vec n a)
get = Get a -> Get (Vec n a)
forall (v :: * -> *) a (f :: * -> *).
(Vector v a, Applicative f) =>
f a -> f (v a)
F.replicateM Get a
forall t. Binary t => Get t
get

instance (U.Unbox n a, Binary a) => Binary (U.Vec n a) where
  put :: Vec n a -> Put
put = (a -> Put) -> Vec n a -> Put
forall (v :: * -> *) a (f :: * -> *) b.
(Vector v a, Applicative f) =>
(a -> f b) -> v a -> f ()
F.mapM_ a -> Put
forall t. Binary t => t -> Put
put
  get :: Get (Vec n a)
get = Get a -> Get (Vec n a)
forall (v :: * -> *) a (f :: * -> *).
(Vector v a, Applicative f) =>
f a -> f (v a)
F.replicateM Get a
forall t. Binary t => Get t
get

instance (Arity n, Binary a) => Binary (F.VecList n a) where
  put :: VecList n a -> Put
put = (a -> Put) -> VecList n a -> Put
forall (v :: * -> *) a (f :: * -> *) b.
(Vector v a, Applicative f) =>
(a -> f b) -> v a -> f ()
F.mapM_ a -> Put
forall t. Binary t => t -> Put
put
  get :: Get (VecList n a)
get = Get a -> Get (VecList n a)
forall (v :: * -> *) a (f :: * -> *).
(Vector v a, Applicative f) =>
f a -> f (v a)
F.replicateM Get a
forall t. Binary t => Get t
get

instance (Binary a) => Binary (F.Only a) where
  put :: Only a -> Put
put (F.Only a
a) = a -> Put
forall t. Binary t => t -> Put
put a
a
  get :: Get (Only a)
get = a -> Only a
forall a. a -> Only a
F.Only (a -> Only a) -> Get a -> Get (Only a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Get a
forall t. Binary t => Get t
get

instance Binary (F.Empty a) where
  put :: Empty a -> Put
put Empty a
_ = () -> Put
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  get :: Get (Empty a)
get = Empty a -> Get (Empty a)
forall (m :: * -> *) a. Monad m => a -> m a
return Empty a
forall k (a :: k). Empty a
F.Empty