 
            Can anyone tell me why I get a type error in the following code? I have to define liftA2 twice to avoid the type error. Both times its defined identically but with different type signature. If I use the original liftA2 in place of liftA2' I get: whyerror.lhs:36:25: Ambiguous type variable `a' in the constraint: `Arrow a' arising from use of `>>>' at whyerror.lhs:36:25-27 Possible cause: the monomorphism restriction applied to the following: liftA2' :: forall b a1 b1 c. (a1 -> b1 -> c) -> a b a1 -> a b b1 -> a b c (bound at whyerror.lhs:36:1) unsplit' :: forall a1 b c. (a1 -> b -> c) -> a (a1, b) c (bound at whyerror.lhs:34:1) split' :: forall b. a b (b, b) (bound at whyerror.lhs:33:1) Probable fix: give these definition(s) an explicit type signature or use -fno-monomorphism-restriction ----- whyerror.lhs ----
{-# OPTIONS_GHC -farrows #-} module WhyError where import Control.Arrow
newtype SimpleFunc a b = SimpleFunc { runF :: (a -> b) } instance Arrow SimpleFunc where arr f = SimpleFunc f first (SimpleFunc f) = SimpleFunc (mapFst f) where mapFst g (a,b) = (g a, b) (SimpleFunc f) >>> (SimpleFunc g) = SimpleFunc (g . f)
split :: (Arrow a) => a b (b, b) split = arr (\x -> (x,x)) unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d unsplit = arr . uncurry -- arr (\op (x,y) -> x `op` y)
liftA2 :: (Arrow a) => (b -> c -> d) -> a e b -> a e c -> a e d liftA2 op f g = split >>> first f >>> second g >>> unsplit op -- f &&& g >>> unsplit op
f, g :: SimpleFunc Int Int f = arr (`div` 2) g = arr (\x -> x*3 + 1) h = liftA2 (+) f g hOutput = runF h 8
-- XXX I am getting type problems with split, unsplit and liftA2! why? split' = arr (\x -> (x,x)) unsplit' = arr . uncurry -- liftA2' :: (Arrow a) => (b -> c -> d) -> a e b -> a e c -> a e d liftA2' op f g = split' >>> first f >>> second g >>> unsplit' op
plusminus, double, h2 :: Kleisli [] Int Int plusminus = Kleisli (\x -> [x, -x]) double = arr (* 2) h2 = liftA2 (+) plusminus double h2Output = runKleisli h2 8
main = do print hOutput print h2Output
Tim Newsham http://www.thenewsh.com/~newsham/
 
            On Nov 21, 2006, at 2:24 PM, Tim Newsham wrote:
Can anyone tell me why I get a type error in the following code? I have to define liftA2 twice to avoid the type error. Both times its defined identically but with different type signature. If I use the original liftA2 in place of liftA2' I get:
whyerror.lhs:36:25: Ambiguous type variable `a' in the constraint: `Arrow a' arising from use of `>>>' at whyerror.lhs:36:25-27 Possible cause: the monomorphism restriction applied to the following: liftA2' :: forall b a1 b1 c. (a1 -> b1 -> c) -> a b a1 -> a b b1 -> a b c (bound at whyerror.lhs:36:1) unsplit' :: forall a1 b c. (a1 -> b -> c) -> a (a1, b) c (bound at whyerror.lhs:34:1) split' :: forall b. a b (b, b) (bound at whyerror.lhs:33:1) Probable fix: give these definition(s) an explicit type signature or use -fno-monomorphism-restriction
I'm not sure I understand your problem. If I comment out split', unsplit' and liftA2', your program compiles and executes. Without signatures, MR kicks in and gives the error above (which recommends you give signatures ;-) ) However, you've got type signatures, and the foul MR beast is slain, so the problem appears solved... [snip code]
Tim Newsham http://www.thenewsh.com/~newsham/
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG
 
            I'm not sure I understand your problem. If I comment out split', unsplit' and liftA2', your program compiles and executes.
Blah.. you're right! I tried so many different things I guess I didn't notice that along the way I fixed it with the type signatures..
Without signatures, MR kicks in and gives the error above (which recommends you give signatures ;-) ) However, you've got type signatures, and the foul MR beast is slain, so the problem appears solved...
MR = ? Thanks for injecting some sanity.
Rob Dockins
Tim Newsham http://www.thenewsh.com/~newsham/
 
            Hi
MR = ?
Monomorphism Restriction http://www.haskell.org/hawiki/MonomorphismRestriction Is there really not a page on the new wiki that explains that MR? We should also have a nice big FAQ, as this is often asked about. Thanks Neil
 
            On Wed, 22 Nov 2006, Neil Mitchell wrote:
http://www.haskell.org/hawiki/MonomorphismRestriction
Is there really not a page on the new wiki that explains that MR? We should also have a nice big FAQ, as this is often asked about.
 
            Hi
How is this an FAQ: http://www.haskell.org/haskellwiki/Why_Haskell_just_works It's a nice piece of marketing, but I can't imagine anyone has ever asked Why Haskell just works, unless they've already used it, in which case they've moved past an FAQ. It would be nice to flesh that out, make it more traditional FAQ style (with a bit of info on what each one means) and have a real FAQ Thanks Neil
 
            Neil Mitchell schrieb:
How is this an FAQ: http://www.haskell.org/haskellwiki/Why_Haskell_just_works
It's a nice piece of marketing, but I can't imagine anyone has ever asked Why Haskell just works, unless they've already used it, in which case they've moved past an FAQ.
Oh, but that kind of question regularly crops up after Haskell programmers have claimed that Haskell "just works". So yes indeed that's a FAQ. Regards, Jo
participants (5)
- 
                 Henning Thielemann Henning Thielemann
- 
                 Joachim Durchholz Joachim Durchholz
- 
                 Neil Mitchell Neil Mitchell
- 
                 Robert Dockins Robert Dockins
- 
                 Tim Newsham Tim Newsham