On Mar 9, 2010, at 5:53 AM, Max Cantor wrote: > Isn't this just an extension of the notion that multi-parameter typeclasses > without functional dependencies or type families are dangerous and allow for > type-naughtiness?
I wondered the same thing, but came up with an analogous problematic case that *only* uses generalized newtype deriving: > {-# LANGUAGE GeneralizedNewtypeDeriving #-} > module Main(main) where > import Data.Set > > class IsoInt a where > stripToInt :: item a -> item Int > convFromInt :: item Int -> item a > > instance IsoInt Int where > stripToInt = id > 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 -Jan-Willem Maessen_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe