Ambiguous type variable prevents the constraint `(Ord t0)' from being solved.

I get this error (full message at the end of the mail). How could I correct my code? =================== Code: =================== module Intro where import Data.Bits -- for xor, .&. data Func a b = Empty | Leaf Int [(a, b)] | Branch Int Int (Func a b) (Func a b) applyd = let apply_listd l d x = case l of [] -> d x (a, b) : t -> let c = compare x a in if c == EQ then b else if c == GT then apply_listd t d x else d x in \f d x -> let k = 5 -- hash x - todo in let look t = case t of Leaf h l | h == k -> apply_listd l d x Branch p b l r | (k `xor` p) .&. (b - 1) == 0 -> -- (Branch p b l r) | ((k xor p) .&. (b - 1)) == 0 -> look (if k .&. b == 0 then l else r) _ -> d x in look f =================== Error: =================== Intro.hs:37:25: error: * Ambiguous type variable `t0' arising from a use of `apply_listd' prevents the constraint `(Ord t0)' from being solved. Relevant bindings include l :: [(t0, t)] (bound at Intro.hs:36:28) t :: Func t0 t (bound at Intro.hs:34:21) look :: Func t0 t -> t (bound at Intro.hs:34:16) x :: t0 (bound at Intro.hs:32:15) d :: t0 -> t (bound at Intro.hs:32:13) f :: Func t0 t (bound at Intro.hs:32:11) (Some bindings suppressed; use -fmax-relevant-binds=N or -fno-max-relevant-binds) Probable fix: use a type annotation to specify what `t0' should be. These potential instances exist: instance Ord Ordering -- Defined in `GHC.Classes' instance Ord Integer -- Defined in `integer-gmp-1.0.0.1:GHC.Integer.Type' instance Ord a => Ord (Maybe a) -- Defined in `GHC.Base' ...plus 22 others ...plus five instances involving out-of-scope types (use -fprint-potential-instances to see them all) * In the expression: apply_listd l d x In a case alternative: Leaf h l | h == k -> apply_listd l d x In the expression: case t of { Leaf h l | h == k -> apply_listd l d x Branch p b l r | (k `xor` p) .&. (b - 1) == 0 -> look (if k .&. b == 0 then l else r) _ -> d x } -- Best wishes, Ivan Kush

Try removing the lambda: applyd f d x = let apply_listd l d x = [..] in let k = 5 -- hash x - todo [...] Regards, Sylvain On 28/01/2017 21:09, Ivan Kush wrote:
I get this error (full message at the end of the mail). How could I correct my code?
=================== Code: ===================
module Intro where
import Data.Bits -- for xor, .&.
data Func a b = Empty | Leaf Int [(a, b)] | Branch Int Int (Func a b) (Func a b)
applyd = let apply_listd l d x = case l of [] -> d x (a, b) : t -> let c = compare x a in if c == EQ then b else if c == GT then apply_listd t d x else d x
in \f d x -> let k = 5 -- hash x - todo in let look t = case t of Leaf h l | h == k -> apply_listd l d x Branch p b l r | (k `xor` p) .&. (b - 1) == 0 -> -- (Branch p b l r) | ((k xor p) .&. (b - 1)) == 0 -> look (if k .&. b == 0 then l else r) _ -> d x in look f
=================== Error: ===================
Intro.hs:37:25: error: * Ambiguous type variable `t0' arising from a use of `apply_listd' prevents the constraint `(Ord t0)' from being solved. Relevant bindings include l :: [(t0, t)] (bound at Intro.hs:36:28) t :: Func t0 t (bound at Intro.hs:34:21) look :: Func t0 t -> t (bound at Intro.hs:34:16) x :: t0 (bound at Intro.hs:32:15) d :: t0 -> t (bound at Intro.hs:32:13) f :: Func t0 t (bound at Intro.hs:32:11) (Some bindings suppressed; use -fmax-relevant-binds=N or -fno-max-relevant-binds) Probable fix: use a type annotation to specify what `t0' should be. These potential instances exist: instance Ord Ordering -- Defined in `GHC.Classes' instance Ord Integer -- Defined in `integer-gmp-1.0.0.1:GHC.Integer.Type' instance Ord a => Ord (Maybe a) -- Defined in `GHC.Base' ...plus 22 others ...plus five instances involving out-of-scope types (use -fprint-potential-instances to see them all) * In the expression: apply_listd l d x In a case alternative: Leaf h l | h == k -> apply_listd l d x In the expression: case t of { Leaf h l | h == k -> apply_listd l d x Branch p b l r | (k `xor` p) .&. (b - 1) == 0 -> look (if k .&. b == 0 then l else r) _ -> d x }
-- Best wishes, Ivan Kush _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (2)
-
Ivan Kush
-
Sylvain Henry