[GHC] #10697: Change template-haskell API to allow NOUNPACK, lazy annotations

GHC ghc-devs at haskell.org
Sun Dec 13 04:29:57 UTC 2015


#10697: Change template-haskell API to allow NOUNPACK, lazy annotations
-------------------------------------+-------------------------------------
        Reporter:  RyanGlScott       |                Owner:
            Type:  feature request   |               Status:  patch
        Priority:  normal            |            Milestone:
       Component:  Template Haskell  |              Version:  7.10.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #5290, #8347      |  Differential Rev(s):  Phab:D1603
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by goldfire):

 Replying to [comment:16 RyanGlScott]:
 > I will admit that I got a little too ambitious with my proposal in
 comment:12, which Simon noted. TH splices should never be altered if given
 "bad" input like what I had proposed. I like Simon's idea of granting the
 user the ability to reify a constructor's fields' strictness after
 compilation, which I incorporated in Phab:D1603.

 Yes, that may be a good middle ground.

 >
 > I'll go ahead and post the updated design here so we have a common point
 to reference in this discussion. Here is the API that concerns reification
 of data types, which coincides precisely with the strictness annotations a
 user writes in source code (i.e., `HsSrcBang`):
 >
 > {{{#!hs
 > data SourceUnpackedness = NoSourceUnpackedness
 >                         | SourceNoUnpack
 >                         | SourceUnpack
 >
 > data SourceStrictness = NoSourceStrictness
 >                       | SourceLazy
 >                       | SourceStrict
 >
 > data Con = NormalC Name [BangType]
 >          | RecC Name [VarBangType]
 >          | InfixC BangType Name BangType
 >          | ForallC [TyVarBndr] Cxt Con
 >
 > data Bang = Bang SourceUnpackedness SourceStrictness
 >
 > type BangType    = (Bang, Type)
 > type VarBangType = (Name, Bang, Type)
 > }}}
 >
 > There is also a similar API for discovering what GHC actually turns
 these strictness/unpackedness combinations into after compilation (i.e.,
 `HsImplBang`), which can be affected by `-XStrictData`, `-funbox-strict-
 fields`, etc.
 >
 > {{{#!hs
 > data DecidedStrictness = DecidedLazy
 >                        | DecidedStrict
 >                        | DecidedUnpack
 >
 > class Monad m => Quasi m where
 >   ...
 >   qReifyConStrictness :: Con -> m [DecidedStrictness]
 > }}}

 This might be more useful taking a `Name` instead of a `Con`. I imagine it
 has to just extract the name and look it up anyway, no? Or does it apply
 the extensions currently enabled to the `Con` definition and report back
 what GHC would decide if the declaration were given? That seems a bit
 silly.

 >
 > > 1. TH quotes should faithfully turn user-written syntax into the TH
 AST.
 >
 > Agreed.
 >
 > > But it's not obliged to deal with meaningless user-written syntax. ...
 >
 > I somewhat disagree here. TH splices should produce syntactically valid
 code, but there's no guarantee that code that it will be meaningful. After
 all, you could conceivably splice in something like `foo :: Maybe ->
 Maybe`.

 You're talking about splices; I'm talking about quotes. Yes, splices need
 to deal with whatever the TH AST provides it, producing compilation errors
 as appropriate. But I don't think quoting does. For example `[| x $$$ y
 %%% z |]` fails if `$$$` and `%%%` are both non-fix operators of the same
 precedence. And the TH AST even has the ability to represent that one!
 (Via `UInfixE`.) So I maintain that quoting doesn't need to deal with
 nonsensical code, if that makes things easier.

 >
 > You're right in that internally, GHC doesn't think all nine combinations
 are compatible. In fact, `HsImplBang` only has three combinations: strict,
 lazy, and unpacked. But the source language is much richer, and it would
 be difficult to graft `{-# NOUNPACK #-}` and laziness annotations onto
 Template Haskell without acknowledging that unpackedness annotations and
 strictness annotations can be used independently of each other in source
 code.

 I agree. Especially with the various flags that can affect this behavior.

 >
 > Not only that, you can't always tell what GHC will produce just from
 examining the unpackedness and strictness annotations alone; it's also
 affected by language extensions, optimization levels, and other
 inscrutable factors. That's why GHC keeps track of `HsSrcBang` information
 even after it's determined what the `HsImplBang`s are. If it didn't,
 there'd be no way things like GHCi could tell you how the original data
 type was written in source code, since that information could have been
 distorted.
 >
 > For these reasons, I feel strongly that we need to be able to express
 all combinations of annotations, even if some of them aren't meaningful to
 GHC.

 I'm not at all disagreeing here. Just saying that it's not the only
 option. But perhaps this isn't worth debating, as I do tend to agree that
 representing the source Haskell straightforwardly works out nicely in this
 case.
 >
 > > 4. Reification should behave identically no matter what extensions are
 enabled. Anything else seems doomed to endlessly befuddle users.
 >
 > I feel like you need to be more specific here before I can respond to
 this. Are you referring to reification of what the user ''wrote'', or
 reification of GHC-specific info that depends on compilation settings? If
 it's the former, I agree, but not if it's the latter.

 I'm saying that if I reify `Foo`, I should get the same results no matter
 what extensions are enabled at the point of reification. Of course, if you
 change the extensions at `Foo`'s definition site, then that substantively
 changes the definition of `Foo` and should change the output of
 reification. I can't distinguish between your two cases, I'm afraid.
 Reification never promises to get back what the user wrote -- it gives you
 what GHC knows.

 >
 > > I think I favor an implementation of reification that never returns
 `NoStrictAnnot` and never returns `NoUnpackAnnot`; that is, it tells you
 precisely what GHC is doing, all the time. This has the noted downside
 that laziness annotations will cause compilation problems without
 `StrictData`. So we also add new (quite straightforward, pure) functions
 that make a reified data declaration suitable for `-XNoStrictData` or
 `-XStrictData`. Perhaps with Phab:D1200 complete (extension checking), we
 can offer a function that just does the right thing.
 >
 > Again, are you referring to the source strictness or the GHC-decided
 strictness here? If it's the decided strictness, then as you say, it
 doesn't make sense to return "no strictness". If it's the source
 strictness, adding a "no strictness" option is, IMO, unavoidable (see my
 response to point 1).

 Reification talks about compiled things, not source things. The fact that
 it returns information using surface syntax is the "lie". So this is GHC-
 decided strictness.

 >
 > > This reification problem is quite similar (as you point out) to kind
 annotations on type variable binders. A few versions ago, reification used
 `PlainTV` for all `*`-kinded variables and `KindedTV` for others. But this
 was just bogus, and now there are a lot more kind signatures. Of course,
 this means that reified code might not always compile if spliced -- just
 like what I'm proposing about strictness, etc.
 >
 > Upon further thought, I don't think this comparison is a very good one.
 `TyVarBndr` is special because it's possible to write type variables
 without kind signatures and have GHC infer them; that is, there's a
 special input form for splicing that never appears in the reified output.
 Strictness, on the other hand, has special ''output'' forms that should
 never appear in the spliced input. Going the other way is problematic, and
 for that reason, I adopted Simon's suggestion of splitting off the
 `DecidedStrictness` stuff and moving it to a `reifyConStrictness`
 function.

 I don't agree here. Strictness does not need to have special output forms.
 It just needs to use unambiguous forms like (unpacked/strict), (not-
 unpacked/strict) and (not-unpacked/lazy), and never return that it doesn't
 know. On the other hand, there are 6 extra input forms. Exactly like
 `TyVarBndr`. You've chosen to implement this asymmetry by introducing new
 output forms. The same could have been done for `TyVarBndr`, by never
 giving kind annotations and instead requiring users to reify type
 variables to get their kinds. I prefer the current behavior.

 Might strictness be different? That is, might it be easier to reify
 strictness instead of include it in reified `Con`s? Perhaps. But it's yet
 another datatype and yet another function in `Quasi`, when we have the
 ability to say exactly what we want right in the `Con`. With the right
 flags set, you could even round-trip the reified `Con`s.

 To be honest, I don't feel strongly about a special reification function
 vs. returning the info right in the `Con`. But it does seem to me that
 this is design choice and is not a forced decision. I favor (weakly)
 returning the info right in the `Con`, just to lessen the footprint of
 this feature.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10697#comment:18>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list