Skip to content
Snippets Groups Projects
Commit b3c6ee0e authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

[project @ 1998-06-08 10:41:08 by simonpj]

parent dc84afbc
No related merge requests found
--!!! Ambiguity in local declarations
module ShouldSucceed where
type Cp a = a -> a -> Ordering
m :: Eq a => Cp a -> [a] -> a
m _ [x,y,z] = if x==y then x else z
cpPairs :: Cp [j] -> (a,[j]) -> (a,[j]) -> Ordering
cpPairs cp (_,p) (_,q) = cp p q
mp :: (Eq i,Eq j) => Cp [j] -> [(i,[j])] -> (i,[j])
mp cp dD =
let minInRow = m (cpPairs cp)
in minInRow dD
{- GHC 3.02 reported
T.hs:24:
Ambiguous type variable(s)
`j' in the constraint `Eq (aYD, [j])'
arising from use of `m' at T.hs:24
In an equation for function `mp':
mp cp dD = let minInRow = m (cpPairs cp) in minInRow dD
This was because the ambiguity test in tcSimplify didn't
take account of the type variables free in the environment.
It should compile fine.
-}
ghc: module version changed to 1; reason: no old .hi file
_exports_
ShouldSucceed cpPairs m mp Cp;
_declarations_
1 cpPairs _:_ _forall_ [a b] => Cp [a] -> (b, [a]) -> (b, [a]) -> PrelBase.Ordering ;;
1 m _:_ _forall_ [a] {PrelBase.Eq a} => Cp a -> [a] -> a ;;
1 mp _:_ _forall_ [a b] {PrelBase.Eq b, PrelBase.Eq a} => Cp [a] -> [(b, [a])] -> (b, [a]) ;;
1 type Cp a = a -> a -> PrelBase.Ordering ;
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment