[Haskell-beginners] Ambigous type variable, why this error?

martin martin.drautzburg at web.de
Wed Jan 27 08:44:07 UTC 2016


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)




More information about the Beginners mailing list