summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/deriving/should_compile/T14682.hs10
-rw-r--r--testsuite/tests/deriving/should_compile/T14682.stderr194
-rw-r--r--testsuite/tests/deriving/should_compile/all.T1
-rw-r--r--testsuite/tests/th/T14681.hs9
-rw-r--r--testsuite/tests/th/T14681.stderr11
-rw-r--r--testsuite/tests/th/all.T1
6 files changed, 226 insertions, 0 deletions
diff --git a/testsuite/tests/deriving/should_compile/T14682.hs b/testsuite/tests/deriving/should_compile/T14682.hs
new file mode 100644
index 0000000000..8f8161f00f
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T14682.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveLift #-}
+module T14682 where
+
+import Data.Data
+import Data.Ix
+import Language.Haskell.TH.Syntax
+
+data Foo = Foo Int Int
+ deriving (Show, Lift, Data, Eq, Ord, Ix)
diff --git a/testsuite/tests/deriving/should_compile/T14682.stderr b/testsuite/tests/deriving/should_compile/T14682.stderr
new file mode 100644
index 0000000000..6ff285fbef
--- /dev/null
+++ b/testsuite/tests/deriving/should_compile/T14682.stderr
@@ -0,0 +1,194 @@
+
+==================== Derived instances ====================
+Derived class instances:
+ instance GHC.Show.Show T14682.Foo where
+ GHC.Show.showsPrec a (T14682.Foo b1 b2)
+ = GHC.Show.showParen
+ (a GHC.Classes.>= 11)
+ ((GHC.Base..)
+ (GHC.Show.showString "Foo ")
+ ((GHC.Base..)
+ (GHC.Show.showsPrec 11 b1)
+ ((GHC.Base..) GHC.Show.showSpace (GHC.Show.showsPrec 11 b2))))
+
+ instance Language.Haskell.TH.Syntax.Lift T14682.Foo where
+ Language.Haskell.TH.Syntax.lift (T14682.Foo a1 a2)
+ = Language.Haskell.TH.Lib.Internal.appE
+ (Language.Haskell.TH.Lib.Internal.appE
+ (Language.Haskell.TH.Lib.Internal.conE
+ (Language.Haskell.TH.Syntax.mkNameG_d "main" "T14682" "Foo"))
+ (Language.Haskell.TH.Syntax.lift a1))
+ (Language.Haskell.TH.Syntax.lift a2)
+
+ instance Data.Data.Data T14682.Foo where
+ Data.Data.gfoldl k z (T14682.Foo a1 a2)
+ = ((z T14682.Foo `k` a1) `k` a2)
+ Data.Data.gunfold k z _ = k (k (z T14682.Foo))
+ Data.Data.toConstr (T14682.Foo _ _) = T14682.$cFoo
+ Data.Data.dataTypeOf _ = T14682.$tFoo
+
+ instance GHC.Classes.Eq T14682.Foo where
+ (GHC.Classes.==) (T14682.Foo a1 a2) (T14682.Foo b1 b2)
+ = (((a1 GHC.Classes.== b1))
+ GHC.Classes.&& ((a2 GHC.Classes.== b2)))
+
+ instance GHC.Classes.Ord T14682.Foo where
+ GHC.Classes.compare a b
+ = case a of {
+ T14682.Foo a1 a2
+ -> case b of {
+ T14682.Foo b1 b2
+ -> case (GHC.Classes.compare a1 b1) of
+ GHC.Types.LT -> GHC.Types.LT
+ GHC.Types.EQ -> (a2 `GHC.Classes.compare` b2)
+ GHC.Types.GT -> GHC.Types.GT } }
+ (GHC.Classes.<) a b
+ = case a of {
+ T14682.Foo a1 a2
+ -> case b of {
+ T14682.Foo b1 b2
+ -> case (GHC.Classes.compare a1 b1) of
+ GHC.Types.LT -> GHC.Types.True
+ GHC.Types.EQ -> (a2 GHC.Classes.< b2)
+ GHC.Types.GT -> GHC.Types.False } }
+ (GHC.Classes.<=) a b = GHC.Classes.not ((GHC.Classes.<) b a)
+ (GHC.Classes.>) a b = (GHC.Classes.<) b a
+ (GHC.Classes.>=) a b = GHC.Classes.not ((GHC.Classes.<) a b)
+
+ instance GHC.Arr.Ix T14682.Foo where
+ GHC.Arr.range (T14682.Foo a1 a2, T14682.Foo b1 b2)
+ = [T14682.Foo c1 c2 |
+ c1 <- GHC.Arr.range (a1, b1), c2 <- GHC.Arr.range (a2, b2)]
+ GHC.Arr.unsafeIndex
+ (T14682.Foo a1 a2, T14682.Foo b1 b2)
+ T14682.Foo c1 c2
+ = (GHC.Arr.unsafeIndex (a2, b2) c2
+ GHC.Num.+
+ (GHC.Arr.unsafeRangeSize (a2, b2)
+ GHC.Num.* GHC.Arr.unsafeIndex (a1, b1) c1))
+ GHC.Arr.inRange
+ (T14682.Foo a1 a2, T14682.Foo b1 b2)
+ T14682.Foo c1 c2
+ = (GHC.Arr.inRange (a1, b1) c1
+ GHC.Classes.&& GHC.Arr.inRange (a2, b2) c2)
+
+ T14682.$con2tag_B4iUvrAY4wB3YczpMJQUOX ::
+ T14682.Foo -> GHC.Prim.Int#
+ T14682.$con2tag_B4iUvrAY4wB3YczpMJQUOX (T14682.Foo _ _) = 0#
+ T14682.$tFoo :: Data.Data.DataType
+ T14682.$cFoo :: Data.Data.Constr
+ T14682.$tFoo = Data.Data.mkDataType "Foo" [T14682.$cFoo]
+ T14682.$cFoo
+ = Data.Data.mkConstr T14682.$tFoo "Foo" [] Data.Data.Prefix
+
+Derived type family instances:
+
+
+
+==================== Filling in method body ====================
+GHC.Show.Show [T14682.Foo]
+ GHC.Show.show = GHC.Show.$dmshow @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+GHC.Show.Show [T14682.Foo]
+ GHC.Show.showList = GHC.Show.$dmshowList @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.dataCast1 = Data.Data.$dmdataCast1 @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.dataCast2 = Data.Data.$dmdataCast2 @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.gmapT = Data.Data.$dmgmapT @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.gmapQl = Data.Data.$dmgmapQl @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.gmapQr = Data.Data.$dmgmapQr @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.gmapQ = Data.Data.$dmgmapQ @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.gmapQi = Data.Data.$dmgmapQi @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.gmapM = Data.Data.$dmgmapM @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.gmapMp = Data.Data.$dmgmapMp @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+Data.Data.Data [T14682.Foo]
+ Data.Data.gmapMo = Data.Data.$dmgmapMo @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+GHC.Classes.Eq [T14682.Foo]
+ GHC.Classes./= = GHC.Classes.$dm/= @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+GHC.Classes.Ord [T14682.Foo]
+ GHC.Classes.max = GHC.Classes.$dmmax @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+GHC.Classes.Ord [T14682.Foo]
+ GHC.Classes.min = GHC.Classes.$dmmin @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+GHC.Arr.Ix [T14682.Foo]
+ GHC.Arr.index = GHC.Arr.$dmindex @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+GHC.Arr.Ix [T14682.Foo]
+ GHC.Arr.rangeSize = GHC.Arr.$dmrangeSize @(T14682.Foo)
+
+
+
+==================== Filling in method body ====================
+GHC.Arr.Ix [T14682.Foo]
+ GHC.Arr.unsafeRangeSize = GHC.Arr.$dmunsafeRangeSize @(T14682.Foo)
+
+
diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T
index 8752bbdb73..3360c81850 100644
--- a/testsuite/tests/deriving/should_compile/all.T
+++ b/testsuite/tests/deriving/should_compile/all.T
@@ -100,3 +100,4 @@ test('T14339', normal, compile, [''])
test('T14331', normal, compile, [''])
test('T14578', normal, compile, ['-ddump-deriv -dsuppress-uniques'])
test('T14579', normal, compile, [''])
+test('T14682', normal, compile, ['-ddump-deriv -dsuppress-uniques'])
diff --git a/testsuite/tests/th/T14681.hs b/testsuite/tests/th/T14681.hs
new file mode 100644
index 0000000000..341a1a66b1
--- /dev/null
+++ b/testsuite/tests/th/T14681.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T14681 where
+
+import Data.Functor.Identity
+import Language.Haskell.TH
+
+$([d| f = \(Identity x) -> x |])
+$([d| g = $(pure $ VarE '(+) `AppE` LitE (IntegerL (-1))
+ `AppE` (LitE (IntegerL (-1)))) |])
diff --git a/testsuite/tests/th/T14681.stderr b/testsuite/tests/th/T14681.stderr
new file mode 100644
index 0000000000..debb18dee5
--- /dev/null
+++ b/testsuite/tests/th/T14681.stderr
@@ -0,0 +1,11 @@
+T14681.hs:7:3-31: Splicing declarations
+ [d| f = \ (Identity x) -> x |] ======> f = \ (Identity x) -> x
+T14681.hs:(8,3)-(9,62): Splicing declarations
+ [d| g = $(pure
+ $ VarE '(+) `AppE` LitE (IntegerL (- 1))
+ `AppE` (LitE (IntegerL (- 1)))) |]
+ pending(rn) [<splice, pure
+ $ VarE '(+) `AppE` LitE (IntegerL (- 1))
+ `AppE` (LitE (IntegerL (- 1)))>]
+ ======>
+ g = ((+) (-1)) (-1)
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 2e7ffa3368..41567162e8 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -398,3 +398,4 @@ test('T13968', normal, compile_fail, ['-v0'])
test('T14204', normal, compile_fail, ['-v0'])
test('T14060', normal, compile_and_run, ['-v0'])
test('T14646', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
+test('T14681', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])