[commit: ghc] master: Add 'Lift' instances for 'NonEmpty' and 'Void' (47875bd)
git at git.haskell.org
git at git.haskell.org
Fri Nov 30 14:47:48 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/47875bd4d79ca633b589e63e320aa5a5c631d096/ghc
>---------------------------------------------------------------
commit 47875bd4d79ca633b589e63e320aa5a5c631d096
Author: Alec Theriault <alec.theriault at gmail.com>
Date: Fri Nov 30 09:18:10 2018 -0500
Add 'Lift' instances for 'NonEmpty' and 'Void'
Summary:
Since 'NonEmpty' and 'Void' are now part of 'base', it makes
sense that we put 'Lift' instances for them in 'template-haskell'.
Not doing so is going to force users to define their own (possibly
colliding) orphan instances downstream.
Test Plan: ./validate
Reviewers: goldfire, bgamari, RyanGlScott
Reviewed By: RyanGlScott
Subscribers: RyanGlScott, rwbarton, carter
GHC Trac Issues: #15961
Differential Revision: https://phabricator.haskell.org/D5391
>---------------------------------------------------------------
47875bd4d79ca633b589e63e320aa5a5c631d096
libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 16 ++++++++++++++++
libraries/template-haskell/changelog.md | 2 ++
testsuite/tests/quotes/TH_localname.stderr | 2 +-
testsuite/tests/th/TH_Lift.hs | 3 +++
4 files changed, 22 insertions(+), 1 deletion(-)
diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
index b75a048..ef44a5c 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
@@ -34,6 +34,8 @@ import Control.Monad.IO.Class (MonadIO (..))
import System.IO ( hPutStrLn, stderr )
import Data.Char ( isAlpha, isAlphaNum, isUpper )
import Data.Int
+import Data.List.NonEmpty ( NonEmpty(..) )
+import Data.Void ( Void, absurd )
import Data.Word
import Data.Ratio
import GHC.Generics ( Generic )
@@ -701,6 +703,17 @@ liftString :: String -> Q Exp
-- Used in TcExpr to short-circuit the lifting for strings
liftString s = return (LitE (StringL s))
+-- | @since 2.15.0.0
+instance Lift a => Lift (NonEmpty a) where
+ lift (x :| xs) = do
+ x' <- lift x
+ xs' <- lift xs
+ return (InfixE (Just x') (ConE nonemptyName) (Just xs'))
+
+-- | @since 2.15.0.0
+instance Lift Void where
+ lift = pure . absurd
+
instance Lift () where
lift () = return (ConE (tupleDataName 0))
@@ -752,6 +765,9 @@ leftName, rightName :: Name
leftName = mkNameG DataName "base" "Data.Either" "Left"
rightName = mkNameG DataName "base" "Data.Either" "Right"
+nonemptyName :: Name
+nonemptyName = mkNameG DataName "base" "GHC.Base" ":|"
+
-----------------------------------------------------
--
-- Generic Lift implementations
diff --git a/libraries/template-haskell/changelog.md b/libraries/template-haskell/changelog.md
index de8b96f..5dca983 100644
--- a/libraries/template-haskell/changelog.md
+++ b/libraries/template-haskell/changelog.md
@@ -12,6 +12,8 @@
`Maybe [TyVarBndrQ]` argument. Non-API-breaking versions of these
functions can be found in `Language.Haskell.TH.Lib`.
+ * Add `Lift` instances for `NonEmpty` and `Void`
+
## 2.14.0.0 *TBA*
* Introduce an `addForeignFilePath` function, as well as a corresponding
diff --git a/testsuite/tests/quotes/TH_localname.stderr b/testsuite/tests/quotes/TH_localname.stderr
index 41eb988..df38597 100644
--- a/testsuite/tests/quotes/TH_localname.stderr
+++ b/testsuite/tests/quotes/TH_localname.stderr
@@ -19,7 +19,7 @@ TH_localname.hs:3:11: error:
Language.Haskell.TH.Syntax.Lift (Maybe a)
-- Defined in ‘Language.Haskell.TH.Syntax’
...plus 14 others
- ...plus 10 instances involving out-of-scope types
+ ...plus 12 instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
• In the expression: Language.Haskell.TH.Syntax.lift y
In the expression:
diff --git a/testsuite/tests/th/TH_Lift.hs b/testsuite/tests/th/TH_Lift.hs
index eff0f1b..87bd47b 100644
--- a/testsuite/tests/th/TH_Lift.hs
+++ b/testsuite/tests/th/TH_Lift.hs
@@ -9,6 +9,7 @@ import Data.Ratio
import Data.Word
import Data.Int
import Numeric.Natural
+import Data.List.NonEmpty
a :: Integer
a = $( (\x -> [| x |]) (5 :: Integer) )
@@ -76,4 +77,6 @@ n = $( (\x -> [| x |]) () )
o :: (Bool, Char, Int)
o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) )
+p :: NonEmpty Char
+p = $( (\x -> [| x |]) ('a' :| "bcde") )
More information about the ghc-commits
mailing list