
#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