Fwd: UNPACK Existential datatype
Roman Cheplyaka
roma at ro-che.info
Fri Jan 23 08:59:35 UTC 2015
I did. The rest is whitespace; @git show -w 1d32a85@ shows only one
changed line (NOUNPACK).
On 23/01/15 10:53, Alexander V Vershilov wrote:
> Please take a took at that commit, UNPACK was also handled there,
> despite commit message do not explicitly state this.
>
> On Jan 23, 2015 11:49 AM, "Roman Cheplyaka" <roma at ro-che.info
> <mailto:roma at ro-che.info>> wrote:
>
> How is parsing of the *NOUNPACK* pragma relevant here?
>
> On 23/01/15 10:45, Alexander V Vershilov wrote:
> > Hi.
> >
> > As far as I understand it was fixed as:
> >
> > commit 1d32a8503c2ebfab2bbdb696fe65dd0823d1ed27
> > Author: Simon Peyton Jones <simonpj at microsoft.com
> <mailto:simonpj at microsoft.com>>
> > Date: Mon Dec 1 17:07:48 2014 +0000
> >
> > Fix parser for UNPACK pragmas
> >
> > {-# NOUNPACK #-}
> > {-# NOUNPACK #-} !
> > were being parsed the same way. The former was wrong.
> >
> > Thanks to Alan Zimmerman for pointing this out
> >
> >
> > So it will fix is in 7.10. And I can't reproduce this anymore on
> > ghc-HEAD.
> >
> >
> > On 20 January 2015 at 17:35, Roman Cheplyaka <roma at ro-che.info
> <mailto:roma at ro-che.info>> wrote:
> >> Interesting question. I managed to trace this to:
> >>
> >> compiler/basicTypes/MkId.hs:699
> >>
> >> isUnpackableType fam_envs ty
> >> | Just (tc, _) <- splitTyConApp_maybe ty
> >> , Just con <- tyConSingleAlgDataCon_maybe tc
> >> , isVanillaDataCon con
> >> = ok_con_args (unitNameSet (getName tc)) con
> >> | otherwise
> >> = False
> >>
> >> where isVanillaDataCon is defined as:
> >>
> >> dcVanilla :: Bool,
> >> -- True <=> This is a vanilla Haskell 98 data constructor
> >> -- Its type is of form
> >> -- forall a1..an . t1 -> ... tm -> T a1..an
> >> -- No existentials, no coercions, nothing.
> >>
> >> There's no explanation why this limitation is introduced; it might be
> >> just a conservative one.
> >>
> >> On 20/01/15 15:08, Nicholas Clarke wrote:
> >>> 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?
> >>
> >> _______________________________________________
> >> Glasgow-haskell-users mailing list
> >> Glasgow-haskell-users at haskell.org
> <mailto:Glasgow-haskell-users at haskell.org>
> >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> >
> >
> >
>
More information about the Glasgow-haskell-users
mailing list