[Haskell-cafe] Type Error. Why!?

Tim Newsham newsham at lava.net
Tue Nov 21 14:24:38 EST 2006


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/


More information about the Haskell-Cafe mailing list