#6041: Program hangs when run under Ubuntu Precise
----------------------------+-----------------------------------------------
Reporter: dsf | Owner:
Type: bug | Status: new
Priority: high | Milestone: 7.4.2
Component: Compiler | Version: 7.4.1
Resolution: | Keywords:
Os: Linux | Architecture: Unknown/Multiple
Failure: Runtime crash | Difficulty: Unknown
Testcase: | Blockedby:
Blocking: | Related:
----------------------------+-----------------------------------------------
Comment(by guest):
On the other hand I undo my diagnosis - that `state` in transformers will
evaluate to `StateT` monad, not `Wrapper`. In any case here is a simpler
program giving <<loop>> on my machine:
{{{
{-# LANGUAGE FlexibleContexts, FlexibleInstances,
GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
module Main (main) where
import Control.Monad.State (MonadState, StateT, evalStateT, get, put,
state)
modify :: MonadState s m => (s -> s) -> m ()
modify f = state (\s -> ((), f s))
newtype Wrapper a = Wrapper { unWrapper :: StateT () IO a }
deriving (Functor, Monad)
instance MonadState () Wrapper where
get = Wrapper get
put s = Wrapper (put s)
-- state f = Wrapper (state f) -- uncomment and it works
setUnique :: Wrapper ()
setUnique =
do u <- get
seq u $ return ()
main :: IO ()
main =
do putStrLn "hello"
evalStateT (unWrapper (modify id >> setUnique)) ()
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6041#comment:13>
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