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