summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2020-06-22 21:06:51 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-10-20 00:47:54 -0400
commitee5dcdf95a7c408e9c339aacebf89a007a735f8f (patch)
tree2e87e1da0045d9e70d8f3382a4e840644a8ccca6
parent9648d680b4b07d48cf8741e0847abf07b95c7c1d (diff)
downloadhaskell-ee5dcdf95a7c408e9c339aacebf89a007a735f8f.tar.gz
testsuite: Add test for #18346
This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20.
-rw-r--r--testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs23
-rw-r--r--testsuite/tests/simplCore/should_compile/T18346/T18346.hs18
-rw-r--r--testsuite/tests/simplCore/should_compile/T18346/all.T2
3 files changed, 43 insertions, 0 deletions
diff --git a/testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs b/testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs
new file mode 100644
index 0000000000..fb727b003b
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE RankNTypes #-}
+
+module MiniLens ((^.), Getting, Lens', lens, view) where
+
+import Data.Functor.Const (Const(..))
+
+type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
+
+type Lens' s a = Lens s s a a
+
+lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
+lens sa sbt afb s = sbt s <$> afb (sa s)
+{-# INLINE lens #-}
+
+type Getting r s a = (a -> Const r a) -> s -> Const r s
+
+view :: Getting a s a -> s -> a
+view l = getConst . l Const
+{-# INLINE view #-}
+
+(^.) :: s -> Getting a s a -> a
+s ^. l = getConst (l Const s)
+{-# INLINE (^.) #-}
diff --git a/testsuite/tests/simplCore/should_compile/T18346/T18346.hs b/testsuite/tests/simplCore/should_compile/T18346/T18346.hs
new file mode 100644
index 0000000000..d0dbf88cd6
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T18346/T18346.hs
@@ -0,0 +1,18 @@
+{-# LANGUAGE RankNTypes #-}
+
+module GHCBug (field) where
+
+import MiniLens ((^.), Getting, Lens', lens, view)
+
+t' :: Getting () () ()
+t' = lens id const
+{-# NOINLINE t' #-}
+
+mlift :: Functor f => Getting b a b -> Lens' (f a) (f b)
+mlift l = lens (fmap (^. l)) const
+{-# INLINE mlift #-}
+
+newtype Field = F (Maybe () -> Maybe ())
+
+field :: Field
+field = F (view (mlift t'))
diff --git a/testsuite/tests/simplCore/should_compile/T18346/all.T b/testsuite/tests/simplCore/should_compile/T18346/all.T
new file mode 100644
index 0000000000..008ae05ba6
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T18346/all.T
@@ -0,0 +1,2 @@
+test('T18346', [extra_files(['MiniLens.hs'])], multimod_compile, ['T18346.hs', '-v0'])
+