Ambigous type variable, why this error?

Hello all, here is something where I don't understand the second error: *Main> (Open [1,2,3]) <: (Open ([1,2,4])) <interactive>:94:8: No instance for (Num a0) arising from the literal ‘1’ The type variable ‘a0’ is ambiguous Note: there are several potential instances: instance Num Double -- Defined in ‘GHC.Float’ instance Num Float -- Defined in ‘GHC.Float’ instance Integral a => Num (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’ ...plus 46 others In the expression: 1 In the first argument of ‘Open’, namely ‘[1, 2, 3]’ In the first argument of ‘(<:)’, namely ‘(Open [1, 2, 3])’ Okay, I understand this one, but why this: <interactive>:94:16: No instance for (Poset a0) arising from a use of ‘<:’ The type variable ‘a0’ is ambiguous Note: there are several potential instances: instance (Eq a, Ord a, Poset a) => Poset (Crust a) -- <== yes, yes, yes, take this one -- Defined at /home/martin/projects/haskell/currychicken/opal/Poset.hs:83:10 instance (Eq a, Ord a, Poset a) => Poset (PsSet a) -- Defined at /home/martin/projects/haskell/currychicken/opal/Poset.hs:50:10 instance (Eq a, Ord a, Poset a) => Poset (PsList a) -- Defined at /home/martin/projects/haskell/currychicken/opal/Poset.hs:46:10 ...plus one other In the expression: (Open [1, 2, 3]) <: (Open ([1, 2, 4])) In an equation for ‘it’: it = (Open [1, 2, 3]) <: (Open ([1, 2, 4])) The operands of (<:) are clearly Crusts, so (PsSet a) or (PsList a) shouldn't be options *Main> :t Open [1,2,3] Open [1,2,3] :: Num a => Crust a *Main> The problem goes away, when I make sure my list elements are Ints *Main> (Open [1::Int,2,3]) <: (Open ([1,2,4])) False But why do I see the second error at all? Here is the complete code: {-# Language FlexibleInstances #-} {-# Language UndecidableInstances #-} import qualified Data.List as L import qualified Data.Set as S import Debug.Trace import Test.QuickCheck hiding ((==>)) ------------------------------------------------------------ class Poset p where ------------------------------------------------------------ (<:) :: p -> p -> Bool instance Poset Int where (<:) = (==) ------------------------------------------------------------ -- Alternatives ------------------------------------------------------------ newtype PsList a = PsList [a] newtype PsSet a = PsSet (S.Set a) isSubPolist :: (Poset a) => [a] -> [a] ->Bool isSubPolist as bs = all includedInBs as where includedInBs a = any (a <:) bs instance (Eq a, Ord a, Poset a) => Poset (PsList a) where (PsList as) <: (PsList bs) = isSubPolist as bs instance (Eq a, Ord a, Poset a) => Poset (PsSet a) where (PsSet as) <: (PsSet bs) = isSubPolist (S.toList as) (S.toList bs) ------------------------------------------------------------ data Crust a = Open [a] | Closed [a] ------------------------------------------------------------ deriving (Eq, Ord, Show) instance (Eq a, Ord a, Poset a) => Poset (Crust a) where (<:) (Open as) (Closed bs) = False (<:) (Closed as) (Closed bs) = as == bs (<:) (Open _) (Open []) = True (<:) (Open []) (Open _) = False (<:) (Open (x:xs)) (Open (y:ys)) = x <: y && (Open xs) <: (Open ys) (<:) (Closed _) (Open []) = True (<:) (Closed []) (Open _) = False (<:) (Closed (x:xs)) (Open (y:ys)) = x <: y && (Closed xs) <: (Open ys)

If I had to guess, it is ambiguous because there are many valid instances it could use.
:t (Open [undefined :: Int]) <: (undefined) (Open [undefined :: Int]) <: (undefined) :: Bool :t (Open [undefined :: Crust Int]) <: (undefined) (Open [undefined :: Crust Int]) <: (undefined) :: Bool :t (Open [undefined :: Crust (Crust Int)]) <: (undefined) (Open [undefined :: Crust (Crust Int)]) <: (undefined) :: Bool
However, I do not get the same error as you do on ghc 7.10.3, so I am
unsure.
<interactive>:2:9:
No instance for (Num a0) arising from the literal ‘1’
The type variable ‘a0’ is ambiguous
Note: there are several potential instances:
instance Num Integer -- Defined in ‘GHC.Num’
instance Num Double -- Defined in ‘GHC.Float’
instance Num Float -- Defined in ‘GHC.Float’
...plus two others
In the expression: 1
In the first argument of ‘Open’, namely ‘[1, 2, 3]’
In the first argument of ‘(<:)’, namely ‘(Open [1, 2, 3])’
<interactive>:2:17:
No instance for (Ord a0) arising from a use of ‘<:’
The type variable ‘a0’ is ambiguous
Note: there are several potential instances:
instance (Ord a, Ord b) => Ord (Either a b)
-- Defined in ‘Data.Either’
instance forall (k :: BOX) (s :: k). Ord (Data.Proxy.Proxy s)
-- Defined in ‘Data.Proxy’
instance (GHC.Arr.Ix i, Ord e) => Ord (GHC.Arr.Array i e)
-- Defined in ‘GHC.Arr’
...plus 28 others
In the expression: (Open [1, 2, 3]) <: (Open ([1, 2, 4]))
In an equation for ‘it’:
it = (Open [1, 2, 3]) <: (Open ([1, 2, 4]))
If I remove the Ord constraint on the Poset (Crust a) instance, It changes
from ambiguous Ord to ambiguous Eq.
On Wed, Jan 27, 2016 at 3:44 AM, martin
Hello all,
here is something where I don't understand the second error:
*Main> (Open [1,2,3]) <: (Open ([1,2,4]))
<interactive>:94:8: No instance for (Num a0) arising from the literal ‘1’ The type variable ‘a0’ is ambiguous Note: there are several potential instances: instance Num Double -- Defined in ‘GHC.Float’ instance Num Float -- Defined in ‘GHC.Float’ instance Integral a => Num (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’ ...plus 46 others In the expression: 1 In the first argument of ‘Open’, namely ‘[1, 2, 3]’ In the first argument of ‘(<:)’, namely ‘(Open [1, 2, 3])’
Okay, I understand this one, but why this:
<interactive>:94:16: No instance for (Poset a0) arising from a use of ‘<:’ The type variable ‘a0’ is ambiguous Note: there are several potential instances: instance (Eq a, Ord a, Poset a) => Poset (Crust a) -- <== yes, yes, yes, take this one -- Defined at /home/martin/projects/haskell/currychicken/opal/Poset.hs:83:10 instance (Eq a, Ord a, Poset a) => Poset (PsSet a) -- Defined at /home/martin/projects/haskell/currychicken/opal/Poset.hs:50:10 instance (Eq a, Ord a, Poset a) => Poset (PsList a) -- Defined at /home/martin/projects/haskell/currychicken/opal/Poset.hs:46:10 ...plus one other In the expression: (Open [1, 2, 3]) <: (Open ([1, 2, 4])) In an equation for ‘it’: it = (Open [1, 2, 3]) <: (Open ([1, 2, 4]))
The operands of (<:) are clearly Crusts, so (PsSet a) or (PsList a) shouldn't be options
*Main> :t Open [1,2,3] Open [1,2,3] :: Num a => Crust a *Main>
The problem goes away, when I make sure my list elements are Ints
*Main> (Open [1::Int,2,3]) <: (Open ([1,2,4])) False
But why do I see the second error at all?
Here is the complete code:
{-# Language FlexibleInstances #-} {-# Language UndecidableInstances #-}
import qualified Data.List as L import qualified Data.Set as S import Debug.Trace import Test.QuickCheck hiding ((==>))
------------------------------------------------------------ class Poset p where ------------------------------------------------------------ (<:) :: p -> p -> Bool
instance Poset Int where (<:) = (==)
------------------------------------------------------------ -- Alternatives ------------------------------------------------------------ newtype PsList a = PsList [a] newtype PsSet a = PsSet (S.Set a)
isSubPolist :: (Poset a) => [a] -> [a] ->Bool isSubPolist as bs = all includedInBs as where includedInBs a = any (a <:) bs
instance (Eq a, Ord a, Poset a) => Poset (PsList a) where (PsList as) <: (PsList bs) = isSubPolist as bs
instance (Eq a, Ord a, Poset a) => Poset (PsSet a) where (PsSet as) <: (PsSet bs) = isSubPolist (S.toList as) (S.toList bs)
------------------------------------------------------------ data Crust a = Open [a] | Closed [a] ------------------------------------------------------------ deriving (Eq, Ord, Show)
instance (Eq a, Ord a, Poset a) => Poset (Crust a) where (<:) (Open as) (Closed bs) = False (<:) (Closed as) (Closed bs) = as == bs
(<:) (Open _) (Open []) = True (<:) (Open []) (Open _) = False (<:) (Open (x:xs)) (Open (y:ys)) = x <: y && (Open xs) <: (Open ys)
(<:) (Closed _) (Open []) = True (<:) (Closed []) (Open _) = False (<:) (Closed (x:xs)) (Open (y:ys)) = x <: y && (Closed xs) <: (Open ys)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (2)
-
David McBride
-
martin