[GHC] #13054: Generating unique names with template haskell

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I need to use template haskell to generate a few instances where those instances each use a foreign function obtained from a particular {{{FunPtr}}}. As far as I'm aware, the only clean way to do this requires top level declarations of the form: {{{foreign import ccall "dynamic" makeFun1 :: FunPtr Foo -> Foo}}} If there was either: * Another way to do this without requiring top level named declarations. * The possibility to use these within a where clause (template haskell would suggest so given that it lets you use {{{Dec}}} within a {{{where}}}). Then I'd be fine probably be fine without names. I've tried using {{{newName}}} as it apparently generates fresh names but I cannot get it work for me. I've put a copy of the test case [https://gitlab.com/tim-m89/hs-th-name- issue here]. I compile with {{{stack build --ghc-options="-ddump-splices -ddump-to-file"}}} and the error is: {{{ th-name-issue/app/Main.hs:7:12: error: Multiple declarations of ‘makeFun’ Declared at: app/Main.hs:7:12 app/Main.hs:7:12 }}} Then I run {{{gvim .stack-work/dist/x86_64-linux/Cabal-1.24.0.0/build/th- name-issue-exe/th-name-issue-exe-tmp/app/Main.dump-splices}}} And can see: {{{ app/Main.hs:7:12-25: Splicing declarations template-haskell-2.11.0.0:Language.Haskell.TH.Quote.quoteDec importGen " stuff here " ======> foreign import ccall safe "dynamic" makeFun_a3pc :: GHC.Ptr.FunPtr (Foreign.C.String.CString -> IO ()) -> Foreign.C.String.CString -> IO () foreign import ccall safe "dynamic" makeFun_a3pd :: GHC.Ptr.FunPtr (Foreign.C.String.CString -> IO ()) -> Foreign.C.String.CString -> IO () }}} Which suggests that I did manage to get unique names after all, so I don't know why it didn't compile?? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): `newName` is intended for producing local names only, not anything top- level. I'm not surprised that it runs into trouble when you're using it at top-level. In a terrible horrible no-good workaround, my `th-desugar` library exports {{{ -- | Like newName, but even more unique (unique across different splices), -- and with unique @nameBase@s. Precondition: the string is a valid Haskell -- alphanumeric identifier (could be upper- or lower-case). newUniqueName :: Quasi q => String -> q Name newUniqueName str = do n <- qNewName str qNewName $ show n }}} This should fix your problem but is a sad, sad thing. The whole `newName` facility needs an update. Waiting for copious free time to do so! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I recently ran into this with fixity declarations: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Language.Haskell.TH $(do n1 <- newName "&&&" n2 <- newName "&&&" let mkDecs n = [ InfixD (Fixity 5 InfixL) n , SigD n (AppT (AppT ArrowT (ConT ''Bool)) (AppT (AppT ArrowT (ConT ''Bool)) (ConT ''Bool))) , FunD n [Clause [WildP,WildP] (NormalB (ConE 'False)) []] ] return (mkDecs n1 ++ mkDecs n2)) }}} {{{ $ /opt/ghc/8.2.1/bin/runghc -ddump-splices Bug.hs Bug.hs:(6,3)-(12,36): Splicing declarations do n1_a3Xj <- newName "&&&" n2_a3Xk <- newName "&&&" let mkDecs_a3Xl n_a3Xm = [InfixD (Fixity 5 InfixL) n_a3Xm, SigD n_a3Xm (AppT (AppT ArrowT (ConT ''Bool)) (AppT (AppT ArrowT (ConT ''Bool)) (ConT ''Bool))), FunD n_a3Xm [Clause [WildP, WildP] (NormalB (ConE 'False)) []]] return (mkDecs_a3Xl n1_a3Xj ++ mkDecs_a3Xl n2_a3Xk) ======> infixl 5 &&&_a4dl (&&&_a4dl) :: Bool -> Bool -> Bool (&&&_a4dl) _ _ = False infixl 5 &&&_a4dm (&&&_a4dm) :: Bool -> Bool -> Bool (&&&_a4dm) _ _ = False Bug.hs:6:3: error: Multiple fixity declarations for ‘&&&_a4dl’ also at Bug.hs:(6,3)-(12,36) | 6 | $(do n1 <- newName "&&&" | ^^^^^^^^^^^^^^^^^^^^^^... }}} (To be precise, you'd encounter the same issue if you commented out the line that gives you a fixity declaration, but that was the first place I noticed it.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I've given this some further thought, and my belief is that `newName` really can't be made to work well with top-level identifier names. After all, if you have two top-level foreign imports with the name `makeFun` and you try invoking `makeFun` somewhere, how is GHC supposed to tell the two `makeFun`s apart, even with different uniques? `newName` just doesn't work for that purpose. Now perhaps you don't care about having a foreign import with the exact name `makeFun`—you just want a unique top-level name that sorta kinda looks like `makeFun` (perhaps, say, `makeFun_4j121c4`). I think there is a valid need for such functionality, and in fact, I think Richard's `newUniqueName` provides more or less a blueprint for how one might actually implement it in GHC. I propose adapting the implementation to create a `newGlobalName` function for this purpose. Moreover, I propose we note the fact that `newName` is insufficient for top-level names in its Haddocks, and point to `newGlobalName` as an example of how you should do it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm not convinced yet. Expanding the API for TH is ok, but it complicates the user model. Let's see. This conversation concerns top-level declarations. I can see two use-cases * Functions or data types that are used locally (in some other function or data type), but not really exported. * Functions or data types that are exported. For the former, it's in implementation shortcoming that `newName` does not work (e.g. comment:2). For the latter, for it to be useful importing module needs to know the name, so exporting (say) `makeFun_4j121c4` and `makeFun_4j12137` is not helpful. So maybe the latter is a non-use-case. If it's just the former I think we should be able to make it "just work". -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Agreed with comment:5. `newName`s should not be exportable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I also agree that `newName`s should not be exportable! Moreover, I don't think you really should be exporting `newGlobalName`s either—but that doesn't mean it's a non-use-case! Quite often in Template Haskell code you'll want to define top-level functions that are used across other functions. For example, in my [http://hackage.haskell.org/package /deriving-compat-0.3.6/docs/Data-Enum-Deriving.html deriving-compat] library, I've found myself wanting to define a function: {{{#!hs con2tagFoo :: Foo -> Int# }}} Like what happens when you derive `Enum` in GHC today, only in Template Haskell. This needs to be a top-level identifier, however, since `con2tag` functions also get used across multiple `Enum` methods, so I need to ensure that this `con2TagFoo` name is globally unique. However, it certainly doesn't need to be exported. Currently, the only way to do this is with something like `newUniqueName` from comment:2, which isn't robust against things like infix names. I imagine tim-m89's use case would also be served by `newGlobalName`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I need to ensure that this `con2TagFoo` name is globally unique.
Indeed. So shouldn't `newName` work for that purpose? Presumably it doesn't, but wouldn't it be nicer for our users if it did? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I don't see how `newName` could possibly be made to work for this purpose. The problem is that after you splice in a Template Haskell splice (in `Convert`), it has to be fed back into the renamer. But `newName` is designed to keep the same original name (just with a different unique), so the renamer will rightly reject multiple top-level things named `con2Tag`, even if they were produced via `newName`, as there's no good way to disambiguate them. Now, you might object "but RyanGlScott, just disambiguate them by their uniques!" That's all well and good, but disambiguating by uniques is really a strategy that I can only envision working in the internals of GHC. The problem is that there are adversarial users who will want to abuse the fact that `newName` can now be used to create top-level names. For instance, what happens if a user tries this? {{{#!hs {-# LANGUAGE TemplateHaskell #-} $(splice1) -- produces top-level function named con2Tag $(splice2) -- produces top-level function named con2Tag uhOh = con2Tag }}} Here, `con2Tag` is written using surface syntax, where we don't have the power to refer to the unique of the particular `con2Tag` we want. The only sensible thing I can see doing in this situation is to error. To avoid this hornet's nest of tricky design questions, I propose we not try to retrofit the ability to create top-level names onto `newName`, but instead create a different function for this purpose. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It doesn't look like a hornets nest to me. In the example you give, the occurrence of `con2Tag` is simply ambiguous because there are two bindings, both with the same unqualified name. I think the `RdrName`s generated by `newName` are `Exact`, right? Not `Unqual`. Maybe the renamer should not complain about collisions between `Exact` top-level names. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:10 simonpj]:
I think the `RdrName`s generated by `newName` are `Exact`, right? Not `Unqual`. Maybe the renamer should not complain about collisions between `Exact` top-level names.
No, they are unqualified. See https://git.haskell.org/ghc.git/blob/791947db6db32ef7d4772a821a0823e558e3c05... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Are you sure? `newName` generate a TH `NameU`; and `Convert.thRdrName` converts a `NameU` to an `Exact` `RdrName`. No? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): My apologies, I was mistakenly under the impression that `NameU`s weren't exact. As for the idea of having GHC accept collisions between two `Exact` names with the same `nameBase` but different uniques... the idea still makes me a little bit queasy. I can think of a couple of unfortunate consequences of permitting this: 1. The fact that the program in comment:9 would still be ambiguous. Allowing `newName` to create valid top-level names means that you can effectively only use them from Template Haskell code in the event you use `newName` to create multiple copies of the same name. If you did such a thing, any attempt to use one copy of the name would result in ambiguity. This means that exporting them, importing them, using them in user- written source code, etc. is a no-go. This really feels like the wrong design to me—we shouldn't be encouraging the use of such a fragile mechanism. 2. How will Haddock render two top-level names with the same `nameBase` generated with two different calls to `newName`? Haddock would pretty much have to render the same function names twice, which is bound to cause confusion for readers. On the other hand `newGlobalName` would not be subject to these flaws. Because names produced by `newGlobalName` are truly unique (due to the suffix attached to them), no problems emerge from calling `newGlobalName` twice with the same `nameBase`. (I'm aware that programs like comment:9 aren't the intended //purpose// of `newGlobalName`, but it would be nice to rule out such tomfoolery by construction.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I'm very confused here. I think this is much simpler than we're making it out to be. `newName` is a facility for creating a name distinct from all others. As I've always understood it, the parameter given to `newName` is simply a hint, so that printing out the names are legible to a human. It should ''not'' be an integral part of its behavior. A corollary of the above definition is that it should be impossible to write the result of a `newName` outside of TH. Thus comment:9 is a non- issue. As it turns out, the renamer doesn't always respect the opaqueness of `newName`s (for example, in fixity declarations). This should be fixed. Perhaps there are other bugs, too. But when all is well, `newName` should work fine for local and top-level definitions. You naturally can't export `newName`s, because you can't write them in an export list. (And we would make sure they're not exported if there is no export list.) And, I think, that's it. Is there something I'm missing? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Hm. Provided there's a robust way to comprehensively rule out //all// occurrences of duplicate names with different uniques, I think I could support this idea. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I guess I'm saying that `newName "foo"` and `newName "foo"` do ''not'' create duplicate names with different uniques... they just create different names that get rendered similarly when pretty-printing. Any implementation that does so is fine by me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13054: Generating unique names with template haskell -------------------------------------+------------------------------------- Reporter: tim-m89 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, that's what I've been trying to say too. If you want a name you can mention outside TH, use `mkName :: String -> Name`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13054#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC