[GHC] #8510: Clear up what extensions are needed at a Template Haskell splice site

#8510: Clear up what extensions are needed at a Template Haskell splice site ------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- Suppose you write {{{ module M where data T = ... $(cleverThFunction ''T) }}} where `cleverThFunction` is some Template Haskell code in a library somewhere. Question: * '''If `cleverThFunction` generates code that uses `GADTs`, or `ConstraintKinds`, or `TypeFamilies` or whatnot, do those language extension flags have to be in force in module M, or only at the definition of `cleverThFunction`?''' Currently the situation is anarchic; see below. It should be made tidy. My personal preference is to say that the extensions must be in force in the definition of `cleverThFunction`, but '''not''' at the splice site. Reason: the client doesn't know or care how `cleverThFunction` works. This decision would be compatible with the handling of overlapping instances. Gergely writes: There are a lot of extensions that simply can't be used with TH: {{{ - n+k, - RecursiveDo, - TransformListComp, - Arrows, - ImplicitParams, - TupleSections, - Monadcomprehensions. }}} The rest can be grouped into two parts. The following extensions still work when spliced in without the corresponding language pragma: {{{ - UnicodeSyntax, - LambdaCase, - NamedFieldPuns, - RecordWildCards, - DataTypeContexts (and you get rid of the deprecation warning generation this way :)), - ConstraintKind, - MagicHash (note that UnboxedTuples is in the other part), - TraditionalRecordSyntax, - MultiWayIf, - GADTs (extra nice example at the end of this message). }}} The following needs the pragma at the place of splicing: {{{ - PostfixOperators, - ScopedTypeVariables, - Rank2, RankN, - deriving typeable and data, - UnboxedTuples, - ViewPatterns, - ParallelListComp, - ExistentialQuantification, - EmptyDataDecls, - TypeFamilies, - MultiParamTypeClasses, - FunctionalDependencies. }}} I don't see any trivial distinction, like based on Reader vs Typechecker, or anything like that. In particular * Note `ViewPatterns` vs `LambdaCase`. * Note `GADTs` vs `Rank2`. A very interesting example is `ExplicitForAll`. The AST for polymorphic functions always have explicit foralls in TH.Syntax; so there is no way to require the user at the point of splicing to enable the language extension. GADTs are cool too: {{{ {-# LANGUAGE TemplateHaskell #-} -- No need for GADTs at all! -- {-# LANGUAGE GADTs #-} $([d| data Foo where Foo1 :: Int -> Foo Foo2 :: String -> Foo f1 :: Foo f1 = Foo1 5 f :: Foo -> Either Int String f (Foo1 n) = Left n f (Foo2 s) = Right s |]) main = print (f f1) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8510 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8510: Clear up what extensions are needed at a Template Haskell splice site -------------------------------------+------------------------------------ Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): Note that if `cleverThFunction` uses explicit data constructors to construct a syntax tree, it doesn't need ANY language extension flags. Maybe that is acceptable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8510#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8510: Clear up what extensions are needed at a Template Haskell splice site -------------------------------------+------------------------------------ Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): While I agree that the current situation -- anarchic is a good description -- should be improved, there are competing forces at work here. As Simon notes, it's possible to create syntax trees in TH without using TH quotes, which gets around the need for language extensions. Indeed, I tend to prefer writing my code this way, as the quoting mechanism isn't quite flexible enough for my needs. So, if we follow Simon's plan of requiring extensions only at the quote site, not at at the splice site, it's possible to write a program using arbitrary extensions while mentioning only `TemplateHaskell`. This seems to fly in the face of the desire to use extensions to help control which compiler (or which version of a compiler) is used to build a cabal package. On the other hand, requiring users of a TH library to turn on extensions feels silly. I know that this a (quite small) point of annoyance when I'm working on my `singletons` package. It currently requires users to turn on roughly 10 extensions to use it. Even worse, if a user doesn't turn on `ScopedTypeVariables` in particular, the error message is ''very'' obscure. One potential solution here is to allow TH to interact directly with the extensions mechanism. At the least, it could query what extensions are in force and then report errors or warnings to the user accordingly. At the most, TH would be able to turn on (and off?) extensions within splices. If the extensions are named via an enumeration type (as opposed to strings), that might be a poor man's mechanism to enforce that the compiler supports an extension -- if the extension isn't present, the use of the relevant constructor wouldn't compile. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8510#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8510: Clear up what extensions are needed at a Template Haskell splice site -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Template Haskell -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8510#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8510: Clear up what extensions are needed at a Template Haskell splice site -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.6.3 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/8510#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC