UNPACK Existential datatype
Simon Peyton Jones
simonpj at microsoft.com
Fri Jan 23 14:14:56 UTC 2015
I think this is a very reasonable suggestion. It would take some work to implement, but nothing fundamental.
Simon
From: Glasgow-haskell-users [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Nicholas Clarke
Sent: 20 January 2015 13:08
To: glasgow-haskell-users at haskell.org
Subject: Fwd: UNPACK Existential datatype
I'd like to be able to use the UNPACK pragma on an existentially quantified datatype. So as in the below example:
{-# LANGUAGE ExistentialQuantification #-}
data Foo = forall a. Show a => Foo !a
instance Show Foo where
show (Foo a) = "Foo! " ++ show a
data Bar =
Bar {-# UNPACK #-} !Foo
deriving (Show)
main :: IO ()
main = do
let foo = Foo "Hello"
bar = Bar foo
print bar
I would expect the `Foo` constructor to be unpacked into Bar, as if I had written:
data Bar = forall a. Show a => Bar !a
However, instead I get the 'Ignoring unusable UNPACK pragma on the first argument of ‘Bar’' warning. Is there a reason this shouldn't work, or a workaround to get it to do so?
Cheers,
Nick
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20150123/29d07711/attachment.html>
More information about the Glasgow-haskell-users
mailing list