#5498: Generalized newtype deriving allows creating of instances I can't create
by
hand
---------------------------------+------------------------------------------
Reporter: dterei | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.3 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
First here is a simple module that establishes a list where once created
(with a min element) subsequent elements inserted should always be larger
than the min:
{{{
-- | Here we expose a MinList API that only allows elements
-- to be inserted into a list if they are at least greater
-- than an initial element the list is created with.
module MinList (
MinList,
newMinList,
insertMinList,
printIntMinList
) where
data MinList a = MinList a [a]
newMinList :: Ord a => a -> MinList a
newMinList n = MinList n []
insertMinList :: Ord a => MinList a -> a -> MinList a
insertMinList s@(MinList m xs) n | n > m = MinList m (n:xs)
| otherwise = s
printIntMinList :: MinList Int -> IO ()
printIntMinList (MinList min xs) = putStrLn $ "MinList Int :: MinList " ++
show min ++ " " ++ show xs
}}}
Now I import this module and use generalized newtype deriving to create a
function I couldn't create by hand:
{{{
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- | We use newtype to create an isomorphic type to Int
-- with a reversed Ord dictionary. We now use the MinList
-- API of MinList to create a new MinList. Then we use newtype
-- deriving to convert the newtype MinList to an Int
-- MinList. This final result breaks the invariants of
-- MinList which shouldn't be possible with the exposed
-- API of MinList.
module Main where
import MinList
class IntIso t where
intIso :: c t -> c Int
instance IntIso Int where
intIso = id
newtype Down a = Down a deriving (Eq, IntIso)
instance Ord a => Ord (Down a) where
compare (Down a) (Down b) = compare b a
fine :: MinList (Down Int)
fine = foldl (\x y -> insertMinList x $ Down y) (newMinList $ Down 0)
[-1,-2,-3,-4,1,2,3,4]
bad :: MinList Int
bad = intIso fine
main = do
printIntMinList bad
}}}
The problem here is the isoInt method where I can do:
{{{
isoInt :: MinList (Down Int) -> MinList Int
}}}
which I shouldn't be able to do since I don't have the constructors for
MinList.
This is the reason I've currently disabled newtype deriving in Safe
Haskell but potentially we can enable it if this bug is fixed.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5498>
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