runtime error <<loop>> when using -O compile option

Hello! I'm working on a computer game using Yampa and I get the following runtime error: $ myprog: <<loop>> when compiling with $ ghc --make MyProg.hs -o myprog -O (without -O it works fine) I stripped the bug down to the program below. What's funny is that the error disappears under certain "odd circumstances" (marked as #1-#4). My questions are: 1. How can I avoid this bug without introducing one of the "odd circumstances"? 2. Why is it that I get this error? 3. How would you hunt down such a bug? Originally I got no clue where it came from, so I just took the program apart piece by piece. {-# LANGUAGE Arrows #-} module Main (main) where import FRP.Yampa type ObjIn = Event () -- loop #1 --type ObjIn = Bool -- no loop #1 type ObjOut = (String, Int) -- loop #2 --type ObjOut = Int -- no loop #2 type GameObj = SF ObjIn ObjOut testObj :: GameObj testObj = proc hit -> do returnA -< ("testObj", 1) -- loop #2 -- returnA -< 1 -- no loop #2 process :: [GameObj] -> SF () [ObjOut] process objs = proc _ -> do rec gamestate <- par logic objs -< gamestate -- loop #3 (recursive definition!) -- -< [] -- no loop #3 returnA -< gamestate logic :: [ObjOut] -> [sf] -> [(ObjIn, sf)] logic gamestate objs = map route objs where route obj = (if null (foo gamestate) then NoEvent else NoEvent, obj) -- loop #1 -- (if null (foo gamestate) then False else False, obj) -- no loop #1 foo :: [ObjOut] -> [ObjOut] foo [] = [] foo objs = concat (collisions objs) where collisions [] = [] collisions (out:objs') = [[out, out'] | out' <- objs, out `collide` out'] -- loop #4 -- [[out, out'] | out' <- objs, True] -- no loop #4 collide :: ObjOut -> ObjOut -> Bool collide (_, p) (_, p') = True -- loop #2 --collide p p' = True -- no loop #2 main :: IO () main = do putStrLn . show $ embed (process [testObj]) ((), [(1.0, Nothing)]) (Btw: I re-opened a bug report: http://hackage.haskell.org/trac/ghc/ticket/2722#comment:10 )

Hi,
Thankyou for the update. I will confirm the delivery as soon as I receive it.
Regards,
Sangeet
----- Original Message -----
From: "Gerold Meisinger"
participants (2)
-
Gerold Meisinger
-
Sangeet Kumar