FunctionalDependencies example:
> {-# LANGUAGE GeneralizedNewtypeDeriving
> , FunctionalDependencies
> , MultiParamTypeClasses #-}
> module Test where
> import Control.Monad.State
> import Control.Monad.Identity
> class (Monad m) => MonadFoo a m | m -> a where
> -- class (Monad m) => MonadFoo a m where
> -- save :: m [a]
> save :: m ()
save has type (MonadFoo a m) => m () . And, although Foo (see below) is an instance of MonadFoo Char, GHC complains that there is No instance for (MonadFoo a Foo) arising from a use of 'save', if functional dependencies isn't used (see commented out code above).
One way to get around is to make save :: m [a] and explicitly annotate each usage of save with :: Foo String (see commented out code of action).
But, using functional dependencies, one can say that m uniquely identifies a. So, GHC will instantiate a with Char on Foo's save, since Foo is an instance of MonadFoo Char.
> restore :: m [a]
> push :: a -> m ()
> newtype FooT m a = FooT {
> runFooT :: (StateT (String, Int) m) a
> } deriving (Monad, Functor, MonadState (String, Int))
> instance (Monad m) => MonadFoo Char (FooT m) where
> save = do
> (current, _) <- get
> put (current, 0)
> -- return current
> restore = do
> (current, n) <- get
> put (drop n current, 0)
> return $ take n current
> push x = do
> (current, n) <- get
> put (x : current, n + 1)
> newtype Foo a = Foo {
> runFoo :: FooT Identity a
> } deriving (Monad, Functor
> , MonadState (String, Int), MonadFoo Char)
> action :: Foo String
> action = do
> push 'a'
> save
> -- save :: Foo String
> push 'b'
> push 'c'
> restore
> test = runIdentity $ runStateT (runFooT (runFoo action)) ("", 0)
No comments:
Post a Comment