[GHC] #12787: Weird type constraint with undecidable instances
GHC
ghc-devs at haskell.org
Mon Oct 31 07:49:43 UTC 2016
#12787: Weird type constraint with undecidable instances
-------------------------------------+-------------------------------------
Reporter: nome | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
(Type checker) |
Keywords: | Operating System: Linux
UndecidableInstances |
Architecture: x86_64 | Type of failure: GHC rejects
(amd64) | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Minimal example:
{{{#!hs
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
module Test where
class PreOrd a where
(<~) :: a -> a -> Bool
class PreOrd a => PartialOrd a where
tryCompare :: a -> a -> Maybe Ordering
instance PartialOrd a => PreOrd a where
x <~ y = let cmp = tryCompare x y in cmp == Just LT || cmp == Just EQ
class PartialOrd a => TotalOrd a where
tcompare :: a -> a -> Ordering
instance TotalOrd a => PartialOrd a where
tryCompare x y = Just $ tcompare x y
instance TotalOrd Int where
tcompare x y = compare x y
}}}
GHC (tested with 7.10.3 and 8.0.1) rejects this with the following error:
{{{
test.hs:11:24: error:
• Could not deduce (TotalOrd a) arising from a use of ‘tryCompare’
from the context: PartialOrd a
bound by the instance declaration at test.hs:10:10-33
Possible fix:
add (TotalOrd a) to the context of the instance declaration
• In the expression: tryCompare x y
In an equation for ‘cmp’: cmp = tryCompare x y
In the expression:
let cmp = tryCompare x y in cmp == Just LT || cmp == Just EQ
}}}
After banging my head against this for a while, and having successfully
run this in Hugs, I tend to see it as a bug in GHC. Which is to say, I
have no idea why tryCompare could possibly require TotalOrd when it's
actually defined in its superclass.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12787>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list