[GHC] #10385: Annotation restriction is not respected while generating Annotation via TH

#10385: Annotation restriction is not respected while generating Annotation via TH -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Magesh B [https://mail.haskell.org/pipermail/ghc-devs/2015-May/008910.html writes]: As per user guide one of the restriction in annotating value is ''the binder being annotated must be declared in the current module''. But when I use TH to generate the annotation above restriction is not respected. Below is the minimal test case to reproduce the issue {{{ ---- Ann.hs {-# LANGUAGE TemplateHaskell #-} module Ann where import Language.Haskell.TH -- {-# Ann id "Orphan Ann for id" #-} -- Rightly produces error "Not in scope: ‘id’" $(pragAnnD (ValueAnnotation 'id) [|"Orphan Ann for id"|] >>= return . return) -- Ideally this should have produced same error as above ---- End of Ann.hs ---- Main.hs {-# LANGUAGE TemplateHaskell #-} module Main where import Ann () import Language.Haskell.TH ann :: [String] ann = $((reifyAnnotations (AnnLookupName 'id) :: Q [String]) >>= (\anns -> [|anns|])) --err = 'a' && True -- Uncomment to introduce compile error main :: IO () main = print ann ---- End of Main.hs }}} Also there is another bug in reifying the Orphan Annotations. In the above example `Main.hs` depends on `Ann.hs` which defines Annotation for `id` When `Main.hs` compiles fine in the first go, its is able to retrieve the annotation for `id` Instead, if `Ann.hs` compiled successfully and `Main.hs` failed to compile and when you later fix the `Main.hs` error, it is not able to retrieve that annotation without recompiling `Ann.hs` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10385 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10385: Annotation restriction is not respected while generating Annotation via TH -------------------------------------+------------------------------------- Reporter: simonpj | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by ezyang): * owner: => alanz Comment: Alan, could you take a look? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10385#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10385: Annotation restriction is not respected while generating Annotation via TH -------------------------------------+------------------------------------- Reporter: simonpj | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by alanz): I could look, but it is outside my area of expertise. There are two different kinds of Annotations in GHC, the API Annotations which I brought in, and these ones. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10385#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10385: Annotation restriction is not respected while generating Annotation via TH -------------------------------------+------------------------------------- Reporter: simonpj | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * component: Compiler => Template Haskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10385#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC