Re: [Haskell-cafe] weird type signature in Arrow Notation

2011-08-04 Thread Brent Yorgey
On Tue, Aug 02, 2011 at 05:08:33PM -0400, bob zhang wrote: hi, all testB :: (ArrowChoice t1, Num a1, Num a) = (a - a1 - t2) - t1 a t3 - t1 a1 t3 - t1 (a, a1) t testB f g h = proc (x,y) - do if (f x y)then g - x + 1 else h - y + 2 it's very strange that the type of _f_ is (a-a1-t2) which I

Re: [Haskell-cafe] weird type signature in Arrow Notation

2011-08-04 Thread Sebastian Fischer
here is a reduced program that still segfaults: {-# LANGUAGE Arrows #-} import Control.Arrow main :: IO () main = print segfault segfault :: [()] segfault = anythingYouWant () anythingYouWant :: a anythingYouWant = testB False (const ()) () testB :: ArrowChoice arrow = bool - arrow ()

Re: [Haskell-cafe] weird type signature in Arrow Notation

2011-08-04 Thread Sebastian Fischer
I created a ticket with a slightly further simplified program: http://hackage.haskell.org/trac/ghc/ticket/5380 On Fri, Aug 5, 2011 at 10:10 AM, Sebastian Fischer fisc...@nii.ac.jpwrote: here is a reduced program that still segfaults: {-# LANGUAGE Arrows #-} import Control.Arrow main :: IO

[Haskell-cafe] weird type signature in Arrow Notation

2011-08-02 Thread bob zhang
hi, all testB :: (ArrowChoice t1, Num a1, Num a) = (a - a1 - t2) - t1 a t3 - t1 a1 t3 - t1 (a, a1) t testB f g h = proc (x,y) - do if (f x y)then g - x + 1 else h - y + 2 it's very strange that the type of _f_ is (a-a1-t2) which I thought should be a - a1 - Bool, btw, is there any way to get the