{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Data.DynamicState.Serializable (
DynamicState(..),
getDyn,
putDyn
) where
import Data.Binary
import Data.HashMap.Strict as M
import Data.ConcreteTypeRep
import Data.Typeable
import Data.ByteString.Lazy(ByteString)
import Control.Monad
data Dynamic
= forall a. (Typeable a, Binary a) => Dynamic !a
| Serial !ByteString
fromDynamic :: forall a. (Typeable a, Binary a) => Dynamic -> Maybe (a,Bool)
fromDynamic (Dynamic b) = (,False) <$> cast b
#if __GLASGOW_HASKELL__ < 708
fromDynamic (Serial bs) = (,True) <$> (Just $ decode bs)
#else
fromDynamic (Serial bs) = let b = either (const Nothing) (\(_,_,a) -> Just a) $ decodeOrFail bs in (,True) <$> b
#endif
instance Binary Dynamic where
put = put . toSerialRep where
toSerialRep (Dynamic a) = encode a
toSerialRep (Serial bs) = bs
get = Serial <$> get
newtype DynamicState = DynamicState { unDynamicState :: M.HashMap ConcreteTypeRep Dynamic }
deriving (Typeable)
#if __GLASGOW_HASKELL__ >= 804
instance Semigroup DynamicState where
(<>) = mappend
#endif
instance Monoid DynamicState where
mappend (DynamicState a) (DynamicState b) = DynamicState (mappend a b)
mempty = DynamicState mempty
getDyn :: forall m a. (Typeable a, Binary a, Monad m) => m DynamicState -> (DynamicState -> m ()) -> m (Maybe a)
getDyn get' put' = do
let ty = cTypeOf (undefined::a)
dvs <- liftM unDynamicState get'
case M.lookup ty dvs >>= fromDynamic of
Just (val,new) -> (when new $ put' $ DynamicState $ M.insert ty (Dynamic val) dvs) >> return (Just val)
Nothing -> return Nothing
putDyn :: forall m a. (Typeable a, Binary a, Monad m) => m DynamicState -> (DynamicState -> m ()) -> a -> m ()
putDyn get' put' v = do
dvs <- liftM unDynamicState get'
put' $ DynamicState (M.insert (cTypeOf (undefined :: a)) (Dynamic v) dvs)
instance Binary DynamicState where
put (DynamicState ds) = put (M.toList ds)
get = DynamicState . M.fromList <$> get