Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

4 changed files:

Changes:

  • libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
    ... ... @@ -26,10 +26,10 @@ import GHC.Internal.Base hiding (Type)
    26 26
     -- | The 'QuasiQuoter' type, a value @q@ of this type can be used
    
    27 27
     -- in the syntax @[q| ... string to parse ...|]@.  In fact, for
    
    28 28
     -- convenience, a 'QuasiQuoter' actually defines multiple quasiquoters
    
    29
    --- to be used in different splice contexts; if you are only interested
    
    30
    --- in defining a quasiquoter to be used for expressions, you would
    
    31
    --- define a 'QuasiQuoter' with only 'quoteExp', and leave the other
    
    32
    --- fields stubbed out with errors.
    
    29
    +-- to be used in different splice contexts. In the usual case of a
    
    30
    +-- @QuasiQuoter@ that is only intended to be used in certain splice
    
    31
    +-- contexts, the unused fields should just 'fail'. This is most easily
    
    32
    +-- accomplished using 'namedefaultQuasiQuoter' or 'defaultQuasiQuoter'.
    
    33 33
     data QuasiQuoter = QuasiQuoter {
    
    34 34
         -- | Quasi-quoter for expressions, invoked by quotes like @lhs = $[q|...]@
    
    35 35
         quoteExp  :: String -> Q Exp,
    

  • libraries/template-haskell/Language/Haskell/TH/Quote.hs
    ... ... @@ -16,6 +16,8 @@ that is up to you.
    16 16
     module Language.Haskell.TH.Quote
    
    17 17
       ( QuasiQuoter(..)
    
    18 18
       , quoteFile
    
    19
    +  , namedDefaultQuasiQuoter
    
    20
    +  , defaultQuasiQuoter
    
    19 21
       -- * For backwards compatibility
    
    20 22
       ,dataToQa, dataToExpQ, dataToPatQ
    
    21 23
       ) where
    
    ... ... @@ -39,3 +41,54 @@ quoteFile (QuasiQuoter { quoteExp = qe, quotePat = qp, quoteType = qt, quoteDec
    39 41
        get old_quoter file_name = do { file_cts <- runIO (readFile file_name)
    
    40 42
                                      ; addDependentFile file_name
    
    41 43
                                      ; old_quoter file_cts }
    
    44
    +
    
    45
    +-- | A 'QuasiQuoter' that fails with a helpful error message in every
    
    46
    +-- context. It is intended to be modified to create a 'QuasiQuoter' that
    
    47
    +-- fails in all inappropriate contexts.
    
    48
    +--
    
    49
    +-- For example, you could write
    
    50
    +--
    
    51
    +-- @
    
    52
    +-- myPatQQ = (namedDefaultQuasiQuoter "myPatQQ")
    
    53
    +--   { quotePat = ... }
    
    54
    +-- @
    
    55
    +--
    
    56
    +-- If 'myPatQQ' is used in an expression context, the compiler will report
    
    57
    +-- that, naming 'myPatQQ'.
    
    58
    +--
    
    59
    +-- See also 'defaultQuasiQuoter', which does not name the 'QuasiQuoter' in
    
    60
    +-- the error message, and might therefore be more appropriate when
    
    61
    +-- the users of a particular 'QuasiQuoter' tend to define local \"synonyms\"
    
    62
    +-- for it.
    
    63
    +namedDefaultQuasiQuoter :: String -> QuasiQuoter
    
    64
    +namedDefaultQuasiQuoter name = QuasiQuoter
    
    65
    +  { quoteExp = f "use in expression contexts."
    
    66
    +  , quotePat = f "use in pattern contexts."
    
    67
    +  , quoteType = f "use in types."
    
    68
    +  , quoteDec = f "creating declarations."
    
    69
    +  }
    
    70
    +  where
    
    71
    +    f m _ = fail $ "The " ++ name ++ " quasiquoter is not for " ++ m
    
    72
    +
    
    73
    +-- | A 'QuasiQuoter' that fails with a helpful error message in every
    
    74
    +-- context. It is intended to be modified to create a 'QuasiQuoter' that
    
    75
    +-- fails in all inappropriate contexts.
    
    76
    +--
    
    77
    +-- For example, you could write
    
    78
    +--
    
    79
    +-- @
    
    80
    +-- myExpressionQQ = defaultQuasiQuoter
    
    81
    +--   { quoteExp = ... }
    
    82
    +-- @
    
    83
    +--
    
    84
    +-- See also 'namedDefaultQuasiQuoter', which names the 'QuasiQuoter' in the
    
    85
    +-- error messages.
    
    86
    +defaultQuasiQuoter :: QuasiQuoter
    
    87
    +defaultQuasiQuoter = QuasiQuoter
    
    88
    +  { quoteExp = f "use in expression contexts."
    
    89
    +  , quotePat = f "use in pattern contexts."
    
    90
    +  , quoteType = f "use in types."
    
    91
    +  , quoteDec = f "creating declarations."
    
    92
    +  }
    
    93
    +  where
    
    94
    +    f m _ = fail $ "This quasiquoter is not for " ++ m

  • libraries/template-haskell/changelog.md
    1 1
     # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell)
    
    2 2
     
    
    3
    +## 2.25.0.0
    
    4
    +  * Introduce `namedDefaultQuasiQuoter` and `defaultQuasiQuoter`, which fail with a helpful error when used in an inappropriate context.
    
    5
    +
    
    3 6
     ## 2.24.0.0
    
    4 7
     
    
    5 8
       * Introduce `dataToCodeQ` and `liftDataTyped`, typed variants of `dataToExpQ` and `liftData` respectively.
    

  • testsuite/tests/interface-stability/template-haskell-exports.stdout
    ... ... @@ -1370,6 +1370,8 @@ module Language.Haskell.TH.Quote where
    1370 1370
       dataToExpQ :: forall (m :: * -> *) a. (GHC.Internal.TH.Syntax.Quote m, GHC.Internal.Data.Data.Data a) => (forall b. GHC.Internal.Data.Data.Data b => b -> GHC.Internal.Maybe.Maybe (m GHC.Internal.TH.Syntax.Exp)) -> a -> m GHC.Internal.TH.Syntax.Exp
    
    1371 1371
       dataToPatQ :: forall (m :: * -> *) a. (GHC.Internal.TH.Syntax.Quote m, GHC.Internal.Data.Data.Data a) => (forall b. GHC.Internal.Data.Data.Data b => b -> GHC.Internal.Maybe.Maybe (m GHC.Internal.TH.Syntax.Pat)) -> a -> m GHC.Internal.TH.Syntax.Pat
    
    1372 1372
       dataToQa :: forall (m :: * -> *) a k q. (GHC.Internal.TH.Syntax.Quote m, GHC.Internal.Data.Data.Data a) => (GHC.Internal.TH.Syntax.Name -> k) -> (GHC.Internal.TH.Syntax.Lit -> m q) -> (k -> [m q] -> m q) -> (forall b. GHC.Internal.Data.Data.Data b => b -> GHC.Internal.Maybe.Maybe (m q)) -> a -> m q
    
    1373
    +  defaultQuasiQuoter :: QuasiQuoter
    
    1374
    +  namedDefaultQuasiQuoter :: GHC.Internal.Base.String -> QuasiQuoter
    
    1373 1375
       quoteFile :: QuasiQuoter -> QuasiQuoter
    
    1374 1376
     
    
    1375 1377
     module Language.Haskell.TH.Syntax where
    
    ... ... @@ -1720,8 +1722,8 @@ module Language.Haskell.TH.Syntax where
    1720 1722
         qAddForeignFilePath :: ForeignSrcLang -> GHC.Internal.Base.String -> m ()
    
    1721 1723
         qAddModFinalizer :: Q () -> m ()
    
    1722 1724
         qAddCorePlugin :: GHC.Internal.Base.String -> m ()
    
    1723
    -    qGetQ :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => m (GHC.Internal.Maybe.Maybe a)
    
    1724
    -    qPutQ :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => a -> m ()
    
    1725
    +    qGetQ :: forall a. ghc-internal-9.1500.0:GHC.Internal.Data.Typeable.Internal.Typeable a => m (GHC.Internal.Maybe.Maybe a)
    
    1726
    +    qPutQ :: forall a. ghc-internal-9.1500.0:GHC.Internal.Data.Typeable.Internal.Typeable a => a -> m ()
    
    1725 1727
         qIsExtEnabled :: Extension -> m GHC.Internal.Types.Bool
    
    1726 1728
         qExtsEnabled :: m [Extension]
    
    1727 1729
         qPutDoc :: DocLoc -> GHC.Internal.Base.String -> m ()
    
    ... ... @@ -1802,7 +1804,7 @@ module Language.Haskell.TH.Syntax where
    1802 1804
       falseName :: Name
    
    1803 1805
       getDoc :: DocLoc -> Q (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
    
    1804 1806
       getPackageRoot :: Q GHC.Internal.IO.FilePath
    
    1805
    -  getQ :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => Q (GHC.Internal.Maybe.Maybe a)
    
    1807
    +  getQ :: forall a. ghc-internal-9.1500.0:GHC.Internal.Data.Typeable.Internal.Typeable a => Q (GHC.Internal.Maybe.Maybe a)
    
    1806 1808
       get_cons_names :: Con -> [Name]
    
    1807 1809
       hoistCode :: forall (m :: * -> *) (n :: * -> *) (r :: GHC.Internal.Types.RuntimeRep) (a :: TYPE r). GHC.Internal.Base.Monad m => (forall x. m x -> n x) -> Code m a -> Code n a
    
    1808 1810
       isExtEnabled :: Extension -> Q GHC.Internal.Types.Bool
    
    ... ... @@ -1849,7 +1851,7 @@ module Language.Haskell.TH.Syntax where
    1849 1851
       oneName :: Name
    
    1850 1852
       pkgString :: PkgName -> GHC.Internal.Base.String
    
    1851 1853
       putDoc :: DocLoc -> GHC.Internal.Base.String -> Q ()
    
    1852
    -  putQ :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => a -> Q ()
    
    1854
    +  putQ :: forall a. ghc-internal-9.1500.0:GHC.Internal.Data.Typeable.Internal.Typeable a => a -> Q ()
    
    1853 1855
       recover :: forall a. Q a -> Q a -> Q a
    
    1854 1856
       reify :: Name -> Q Info
    
    1855 1857
       reifyAnnotations :: forall a. GHC.Internal.Data.Data.Data a => AnnLookup -> Q [a]