{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 707
{-# LANGUAGE StandaloneDeriving, DeriveDataTypeable, Safe #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Control.Comonad.Trans.Store
(
Store, store, runStore
, StoreT(..), runStoreT
, pos
, seek, seeks
, peek, peeks
, experiment
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Control.Comonad
import Control.Comonad.Hoist.Class
import Control.Comonad.Trans.Class
import Data.Functor.Identity
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
#ifdef __GLASGOW_HASKELL__
import Data.Typeable
#if __GLASGOW_HASKELL__ >= 707
deriving instance Typeable StoreT
#else
instance (Typeable s, Typeable1 w) => Typeable1 (StoreT s w) where
typeOf1 dswa = mkTyConApp storeTTyCon [typeOf (s dswa), typeOf1 (w dswa)]
where
s :: StoreT s w a -> s
s = undefined
w :: StoreT s w a -> w a
w = undefined
instance (Typeable s, Typeable1 w, Typeable a) => Typeable (StoreT s w a) where
typeOf = typeOfDefault
storeTTyCon :: TyCon
#if __GLASGOW_HASKELL__ < 704
storeTTyCon = mkTyCon "Control.Comonad.Trans.Store.StoreT"
#else
storeTTyCon = mkTyCon3 "comonad-transformers" "Control.Comonad.Trans.Store" "StoreT"
#endif
{-# NOINLINE storeTTyCon #-}
#endif
#endif
type Store s = StoreT s Identity
store :: (s -> a) -> s -> Store s a
store f s = StoreT (Identity f) s
runStore :: Store s a -> (s -> a, s)
runStore (StoreT (Identity f) s) = (f, s)
data StoreT s w a = StoreT (w (s -> a)) s
runStoreT :: StoreT s w a -> (w (s -> a), s)
runStoreT (StoreT wf s) = (wf, s)
instance Functor w => Functor (StoreT s w) where
fmap f (StoreT wf s) = StoreT (fmap (f .) wf) s
instance (ComonadApply w, Semigroup s) => ComonadApply (StoreT s w) where
StoreT ff m <@> StoreT fa n = StoreT ((<*>) <$> ff <@> fa) (m <> n)
instance (Applicative w, Monoid s) => Applicative (StoreT s w) where
pure a = StoreT (pure (const a)) mempty
StoreT ff m <*> StoreT fa n = StoreT ((<*>) <$> ff <*> fa) (mappend m n)
instance Comonad w => Comonad (StoreT s w) where
duplicate (StoreT wf s) = StoreT (extend StoreT wf) s
extend f (StoreT wf s) = StoreT (extend (\wf' s' -> f (StoreT wf' s')) wf) s
extract (StoreT wf s) = extract wf s
instance ComonadTrans (StoreT s) where
lower (StoreT f s) = fmap ($ s) f
instance ComonadHoist (StoreT s) where
cohoist l (StoreT f s) = StoreT (l f) s
pos :: StoreT s w a -> s
pos (StoreT _ s) = s
seek :: s -> StoreT s w a -> StoreT s w a
seek s ~(StoreT f _) = StoreT f s
seeks :: (s -> s) -> StoreT s w a -> StoreT s w a
seeks f ~(StoreT g s) = StoreT g (f s)
peek :: Comonad w => s -> StoreT s w a -> a
peek s (StoreT g _) = extract g s
peeks :: Comonad w => (s -> s) -> StoreT s w a -> a
peeks f ~(StoreT g s) = extract g (f s)
experiment :: (Comonad w, Functor f) => (s -> f s) -> StoreT s w a -> f a
experiment f (StoreT wf s) = extract wf <$> f s