#5595: Type error: expected type = actual type ???
---------------------------------+------------------------------------------
Reporter: basvandijk | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.2.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: GHC rejects valid program
---------------------------------+------------------------------------------
Comment(by basvandijk):
Replying to [comment:3 basvandijk]:
> Replying to [comment:2 simonpj]:
> > Is it ruining your life?
>
> No, I switched to associated data types which don't have the problem.
Although this is not ruining my life, I do like to mention that if I could
use associated type synonyms I can greatly simply (and hopefully optimize)
the [https://github.com/basvandijk/monad-
control/blob/master/Control/Monad/Trans/Control.hs new design] of `monad-
control`.
For example, now I have:
{{{
instance MonadTransControl (StateT s) where
newtype St (StateT s) α = StState (α, s)
liftControl f = StateT $ \s →
liftM (\x → (x, s))
(f $ \t → liftM StState $ runStateT t s)
restoreT (StState st) = StateT $ \_ → return st
}}}
It would be nice if this could be simplified to just:
{{{
instance MonadTransControl (StateT s) where
type St (StateT s) α = (α, s)
liftControl f = StateT $ \s →
liftM (\x → (x, s))
(f $ \t → runStateT t s)
restoreT st = StateT $ \_ → return st
}}}
Look: no ugly `StState` wrappers and no potentially inefficient: `liftM
StState`.
Or take `MonadControlIO` for example:
{{{
instance MonadControlIO IO where
newtype StIO IO α = StIO α
liftControlIO f = f $ liftM StIO
restore (StIO x) = return x
instance MonadControlIO m ⇒ MonadControlIO (StateT s m) where
newtype StIO (StateT s m) α = StIOState (ComposeSt (StateT s) m α)
liftControlIO = liftControlIODefault StIOState
restore (StIOState stIO) = StateT $ \s → do
st ← restore stIO
runStateT (restoreT st) s
type ComposeSt t m α = StIO m (St t α)
liftControlIODefault ∷ (MonadTransControl t, MonadControlIO m, Monad (t
m), Monad m)
⇒ (∀ β. ComposeSt t m β → StIO (t m) β) -- ^ 'StIO'
constructor
→ ((RunInIO (t m) → IO α) → t m α)
liftControlIODefault stIO = \f → liftControl $ \run →
liftControlIO $ \runInIO →
f $ liftM stIO ∘ runInIO ∘ run
}}}
This can be neatly simplified to just:
{{{
instance MonadControlIO IO where
type StIO IO α = α
liftControlIO f = f id
restore = return
instance MonadControlIO m ⇒ MonadControlIO (StateT s m) where
type StIO (StateT s m) α = ComposeSt (StateT s) m α
liftControlIO = liftControlIODefault
restore stIO = StateT $ \s → do
st ← restore stIO
runStateT (restoreT st) s
type ComposeSt t m α = StIO m (St t α)
liftControlIODefault ∷ (MonadTransControl t, MonadControlIO m, Monad (t
m), Monad m)
→ (RunInIO (t m) → IO α) → t m α
liftControlIODefault f = liftControl $ \run →
liftControlIO $ \runInIO →
f $ runInIO ∘ run
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5595#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs