[Haskell-cafe] When using functional dependencies to combine...
Daniel Fischer
daniel.is.fischer at web.de
Thu Dec 18 20:20:47 EST 2008
Am Freitag, 19. Dezember 2008 00:17 schrieb Martijn van Steenbergen:
> Good evening everyone,
>
> My program reads:
> > module Boom where
> >
> > import Control.Monad.State
> >
> > type SucParser s = StateT [s] []
> >
> > newtype WithUnit s a = WithUnit (SucParser s (a, ()))
> >
> > foo :: SucParser s [s]
> > foo = get
> >
> > bar :: WithUnit s [s]
> > bar = WithUnit get
>
> The compiler complains:
>
> Boom.hs:13:0:
> Couldn't match expected type `([s], ())'
> against inferred type `[s]'
> When using functional dependencies to combine
> MonadState s (StateT s m),
> arising from the instance declaration at <no location info>
> MonadState ([s], ()) (StateT [s] []),
> arising from a use of `get' at Boom.hs:13:15-17
> When generalising the type(s) for `bar'
>
> I'm wondering if I'm making a silly mistake or if there's something less
> trivial going on here. Could someone please explain the error and give a
> hint on how to fix it?
class MonadState s m | m -> s where
get :: m s ...
For SucParser,
get :: StateT [s] [] [s].
To wrap it in WithUnit, it would need type
StateT [s] [] (([s],()),[s])
Easy fix:
bar :: WithUnit s [s]
bar = WithUnit $ do
s <- get
return (s,())
Better define
liftUnit :: SucParser s a -> WithUnit s a
liftUnit m = WithUnit $ do
a <- m
return (a,())
and
bar = liftUnit get
Or make WithUnit more general (working with arbitrary monads) and give it a
MonadTrans instance.
>
> Thanks much. :-)
>
> Martijn.
More information about the Haskell-Cafe
mailing list