#5498: Generalized newtype deriving allows creating of instances I can't create
by
hand
---------------------------------+------------------------------------------
Reporter: dterei | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.3
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Changes (by simonpj):
* cc: dimitris@…, sweirich@… (added)
Old description:
> 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.
New description:
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.
--
Comment:
I believe that this bug is very closely related to #1496 (just look at the
type of the class moethod in each case).
We have an as-yet-unimplemented solution to #1496, namely our POPL'11
paper [http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/
Generative type abstraction and type level computation]. I don't yet
know if the same approach deals with the problem you identify in this
ticket, but my nose tells me yes. I'm adding Stephanie and Dimitrios to
the cc.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5498#comment:1>
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