[GHC] #11078: Access to module renaming with reifyModule, in TemplateHaskell
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Template | Version: 7.10.2 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 am writing a bit of TemplateHaskell for stringing together QuickCheck style specifications. I require every module containing properties to export a symbol called ''axiom_set''. Then, my checkAxioms function finds all the ''axiom_set'' symbols from modules imported where I call checkAxioms. checkAxioms :: DecsQ checkAxioms = do ModuleInfo ms <- reifyModule =<< thisModule forM_ ms $ \mi@(Module _ m) -> do runIO . print =<< lookupValueName (modString m ++ ".axiom_set") The above code should find all the imported "axiom_set" symbols. However, if Module.Axioms defines axiom_set but that I imported as follows import Module.Axioms as MA my code can't find MA.axiom_set. I think either modString should return MA in the case of Module.Axioms or there should be a function that takes a symbol and a module and constructs a Name referring to the symbol in the module and considering possible renamings of modules. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.2 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: | -------------------------------------+------------------------------------- Description changed by jstolarek: Old description:
I am writing a bit of TemplateHaskell for stringing together QuickCheck style specifications. I require every module containing properties to export a symbol called ''axiom_set''. Then, my checkAxioms function finds all the ''axiom_set'' symbols from modules imported where I call checkAxioms.
checkAxioms :: DecsQ checkAxioms = do ModuleInfo ms <- reifyModule =<< thisModule forM_ ms $ \mi@(Module _ m) -> do runIO . print =<< lookupValueName (modString m ++ ".axiom_set")
The above code should find all the imported "axiom_set" symbols. However, if Module.Axioms defines axiom_set but that I imported as follows
import Module.Axioms as MA
my code can't find MA.axiom_set.
I think either modString should return MA in the case of Module.Axioms or there should be a function that takes a symbol and a module and constructs a Name referring to the symbol in the module and considering possible renamings of modules.
New description: I am writing a bit of TemplateHaskell for stringing together QuickCheck style specifications. I require every module containing properties to export a symbol called `axiom_set`. Then, my `checkAxioms` function finds all the `axiom_set` symbols from modules imported where I call `checkAxioms`. {{{#!hs checkAxioms :: DecsQ checkAxioms = do ModuleInfo ms <- reifyModule =<< thisModule forM_ ms $ \mi@(Module _ m) -> do runIO . print =<< lookupValueName (modString m ++ ".axiom_set") }}} The above code should find all the imported `axiom_set` symbols. However, if `Module.Axioms` defines `axiom_set` but that I imported as follows {{{#!hs import Module.Axioms as MA }}} my code can't find `MA.axiom_set`. I think either `modString` should return `MA` in the case of `Module.Axioms` or there should be a function that takes a symbol and a module and constructs a `Name` referring to the symbol in the module and considering possible renamings of modules. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.2 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 jstolarek): * cc: jstolarek (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 goldfire): * milestone: => 8.0.1 Comment: Good point. What about this design: {{{ data ModuleInfo = ModuleInfo [ModuleImport] data ModuleImport = ModuleImport Module -- ^ imported module Bool -- ^ qualified? (Maybe String) -- ^ synonym [Name] -- ^ imported names data Module = Module PkgName ModName -- as it is today }}} I'm not sure that GHC can fully populate `ModuleImport` given the information that it has to hand. But if we could build `ModuleImport`s, would this solve your problem? One further refinement is to enable querying of whether or not the user specified an import list or if simply all names were imported. But I'm less convinced of the need for that at this point. It would be lovely if someone were to do this for 8.0! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 cipher1024): Yes, I believe that would do the trick nicely. Instead of a Maybe String, you could have a String stand for the synonym. Whenever the import is not renamed, it would hold the exact name of the imported module. After thinking some more about your proposal, I'm really liking the list of names. That should simplify my design significantly. How hard do you think it will be to implement? Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 osa1): * cc: osa1 (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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):
How hard do you think it will be to implement?
I don't know. But I do know I don't have time to do this for 8.0, so if I'm the one implementing, then it is ∞ hard. But I'm happy to advise someone else. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 osa1): I think I can implement this. When's the deadline for 8.0 patches? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 osa1): I tried to implement this but as also noted by @goldfire I don't think we have necessary information in `TcM` for this change. One way to pass necessary information to type checker might be to pass `HsRnModule` in `tcRnModule` to `initTc`, and `initTc` would then record it in `TcGblEnv` or `TcLclEnv` (I don't know the difference yet). @goldfire, do you have any ideas about this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 afraid I don't have any ideas until my "type=kind" branch is merged, which is of highest priority. What's the specific piece of info that's missing? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 jstolarek): Ömer, do you have your work somewhere on a brach? Perhaps I can allocate some cycles to this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 osa1): Jan, I worked on this until I got stuck because of the missing information in `TcM`. I don't really have any code in any branch, it was only a couple of lines until I realized something's missing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 jstolarek): I just had a quick look at the code. Let's assume we are using definition proposed by Richard (slightly modified by me): {{{#!hs data ImportType = Qualified | Unqualified deriving( Show, Eq, Ord, Data, Typeable, Generic ) data ModuleImport = ModuleImport Module -- ^ Imported module ImportType -- ^ qualified? (Maybe String) -- ^ synonym [Name] -- ^ imported names deriving( Show, Eq, Ord, Data, Typeable, Generic ) }}} I understand that the place where we need to fill in these fields is `TcSplice.reifyModule`. At least that is the place where the build fails for me after I make changes to TH syntax. In `TcM` we have access to `getImports`, which gives us a list of `Module`s, each with an assigned `ImportedModsVal`: {{{#!hs type ImportedMods = ModuleEnv [ImportedModsVal] data ImportedModsVal = ImportedModsVal { imv_name :: ModuleName, -- ^ The name the module is imported with imv_span :: SrcSpan, -- ^ the source span of the whole import imv_is_safe :: IsSafeImport, -- ^ whether this is a safe import imv_is_hiding :: Bool, -- ^ whether this is an "hiding" import imv_all_exports :: GlobalRdrEnv -- ^ all the things the module could provide } }}} Now, in `reifyModule` we need the following: 1. `Module`: this is readily available and created by the existing implementation (see `TcSplice.modToTHMod`. 2. `ImportType`: I can't figure out how we could acces that one 3. `Maybe String`, aka the module synonym. I would look at `imv_name` to see what exactlt it holds. Also, I would adjust TH representation to work nicely with information stored in that field. 4. `[Name]` - it seems that this can be extracted from `imv_all_exports`. Does that allow to make progress? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 concerned about `all the things the module could provide`. That sounds like it contains all the exports of the module in question, which is larger than the list of all definitions that are imported here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 osa1): I believe that would allow to make progress. You may want to have a look at `HsModule` and `HsParsedModule` types. We can easily pass them(or some information taken from them) to the type checker and they have everything we need. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell
-------------------------------------+-------------------------------------
Reporter: cipher1024 | Owner:
Type: feature request | Status: new
Priority: normal | Milestone: 8.0.1
Component: Template Haskell | Version: 7.10.2
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 jstolarek):
Replying to [comment:13 goldfire]:
> I'm concerned about `all the things the module could provide`. That
sounds like it contains all the exports of the module in question.
Yes, that is exactly the case.
After some more hacking I believe that `Maybe String` for representing a
synonym is not a good idea. We should have a `[String]` instead to store
all names used to import a module. For example, if I say:
{{{
import Foo
import Foo as Bar
}}}
then the list would contain `[Foo, Bar]`.
Replying to [comment:14 osa1]:
> You may want to have a look at `HsModule` and `HsParsedModule` types. We
can easily pass them(or some information taken from them) to the type
checker and they have everything we need.
Two questions:
1. Which field of these data types stores the list of *imported*
functions?
2. How can we pass data from these to the type checker? Won't this be a
gross hack?
--
Ticket URL:
GHC
The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 osa1):
Which field of these data types stores the list of *imported* functions?
I don't think there's a way to get all the imported functions from those types. But we can learn qualified imports by looking at `HsModule`s `hsmodImports :: [LImportDecl]` field. `LImportDecl` has this field: `iDeclHiding :: Maybe (Bool, LIE)`. As far as I understand from the documentation if the `Bool` is `False` it's an explicit import. Otherwise it's an explicit `hiding (...)`.
How can we pass data from these to the type checker? Won't this be a gross hack?
We should decide how to update the state type in type checker to pass this information. I wouldn't call this a hack, if we want this functionality we need to somehow pass this information. Or we can create some new types instead of just passing `HsModule`. I'm busy until next week and I can try some alternative designs next week, unless someone solves this in the meantime. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 jstolarek): Replying to [comment:16 osa1]:
`LImportDecl` has this field: `iDeclHiding :: Maybe (Bool, LIE)`. As far as I understand from the documentation if the `Bool` is `False` it's an explicit import. Otherwise it's an explicit `hiding (...)`. Good point. So it looks like we have all the necessary information at hand. When `fst . ideclHiding` is `False` then the second component of the tuple stores the names of imported things. If `fst . ideclHiding` is `True`, then we must compute imported names based on `imv_all_exports` (all things provided by the module) and the second component of `ideclHiding` (hidden things, that need to be excluded from the list). Probably a bit tedious, but doable. We'd need to figure out how to sensibly extract names from `LIE name`.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
#11078: Access to module renaming with reifyModule, in TemplateHaskell -------------------------------------+------------------------------------- Reporter: cipher1024 | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.0.1 Component: Template Haskell | Version: 7.10.2 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 osa1): I don't have any progress yet but I just wanted to say that passing `HsModule`(or some fields of it) around may not be very bad, and GHC is already doing similar things. For example, `DataCon` has a `[HsSrcBang]` field which is carried around until Cmm(or maybe even backend code generation) stage I think. `HsSrcBang` is this: {{{#!haskell data HsSrcBang = HsSrcBang (Maybe SourceText) SrcUnpackedness SrcStrictness }}} Some(maybe all) parts of this are coming from the parser. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11078#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC