[this is also my reply to Ekmett's comment] On Wed, 6 Nov 2013 12:06:04 +0000, Simon Peyton-Jones <simo...@microsoft.com> writes:
> But this is true for ANY language extension. If a TH library exports a > function that generates (say) a type family declaration, and you > splice that into a file, do you need -XTypeFamilies in the client > file? I think currently you do. So, we've made a little bit of testing on this. 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. 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 to: ------------------------------ {-# 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) ------------------------------ So all I'm asking for is that if it's not very inconvenient for the implementor, please put the Annotations language pragma into the first group. :) Thanks, Gergely _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users