#1496: Newtypes and type families combine to produce inconsistent FC(X) axiom
sets
----------------------------------------+-----------------------------------
Reporter: sorear | Owner: simonpj
Type: bug | Status: new
Priority: normal | Milestone: 6.12 branch
Component: Compiler (Type checker) | Version: 6.7
Keywords: | Difficulty: Unknown
Os: Unknown/Multiple | Testcase:
Architecture: Unknown/Multiple | Failure: None/Unknown
----------------------------------------+-----------------------------------
Changes (by jmaessen):
* cc: jmaes...@… (added)
* failure: => None/Unknown
Comment:
Here's a simple example program that violates the invariant of `Set` while
using ''only'' newtype deriving (and not more complex extensions such as
multiparameter type classes or type functions):
{{{
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main(main) where
import Data.Set
class IsoInt a where
convFromInt :: item Int -> item a
instance IsoInt Int where
convFromInt = id
newtype Down a = Down a deriving (Eq, Show, IsoInt)
instance Ord a => Ord (Down a) where
compare (Down a) (Down b) = compare b a
asSetDown :: Set (Down Int) -> Set (Down Int)
asSetDown = id
a1 = toAscList . asSetDown . convFromInt . fromAscList $ [0..10]
a2 = toAscList . asSetDown . fromAscList . reverse . convFromInt $ [0..10]
main = do
print a1
print a2
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1496#comment:26>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs