summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorÖmer Sinan Ağacan <omeragacan@gmail.com>2020-03-09 16:35:15 +0300
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-03-10 02:07:22 -0400
commitca8f51d475a69583a228f118e6b9dac98ba483d3 (patch)
treeee1e274247391c384cffc989d2144095240083a4
parentee2c50cbeead0d865a02a963f3f3c72e298398d7 (diff)
downloadhaskell-ca8f51d475a69583a228f118e6b9dac98ba483d3.tar.gz
Add regression test for T17904
Closes #17904
-rw-r--r--testsuite/tests/codeGen/should_compile/T17904.hs63
-rw-r--r--testsuite/tests/codeGen/should_compile/all.T1
2 files changed, 64 insertions, 0 deletions
diff --git a/testsuite/tests/codeGen/should_compile/T17904.hs b/testsuite/tests/codeGen/should_compile/T17904.hs
new file mode 100644
index 0000000000..ca5526c255
--- /dev/null
+++ b/testsuite/tests/codeGen/should_compile/T17904.hs
@@ -0,0 +1,63 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE TypeInType #-}
+{-# OPTIONS_GHC -fno-full-laziness #-}
+
+module T17904
+ ( difference
+ , differenceWith
+ ) where
+
+import GHC.Exts ( TYPE, Int (..) )
+import Prelude hiding (lookup)
+
+{-# ANN module ("HLint: ignore Eta reduce" :: String) #-}
+
+class Hashable a where
+ hashWithSalt :: Int -> a -> Int
+
+data Leaf k v = L k v
+
+data HashMap k v
+ = Empty
+ | Leaf Word (Leaf k v)
+
+lookup :: (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
+lookup k m = case lookupCont (\_ -> (# (# #) | #)) (\v _i -> (# | v #)) (fromIntegral $ (hashWithSalt undefined) k) k m of
+ _ -> undefined
+{-# INLINE lookup #-}
+
+lookupCont ::
+ forall rep (r :: TYPE rep) k v.
+ Eq k
+ => ((# #) -> r)
+ -> (v -> Int -> r)
+ -> Word
+ -> k -> HashMap k v -> r
+lookupCont _absent _present _h0 _k0 _m0 = go undefined undefined undefined undefined
+ where
+ go :: Word -> k -> Int -> HashMap k v -> r
+ go h k _ _
+ | h == undefined && k == undefined = undefined
+ | otherwise = undefined
+
+difference :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v
+difference a b = foldlWithKey' go undefined a
+ where
+ go _m k _v = case lookup k b of
+ Nothing -> undefined
+ _ -> undefined
+
+differenceWith :: (Eq k, Hashable k) => a -> HashMap k v -> HashMap k w -> HashMap k v
+differenceWith _f a b = foldlWithKey' go undefined a
+ where
+ go _m k _v = case lookup k b of
+ Nothing -> undefined
+ _ -> undefined
+
+foldlWithKey' :: (a -> k -> v -> a) -> a -> HashMap k v -> a
+foldlWithKey' _f = go
+ where
+ go _z Empty = undefined
+ go _z (Leaf _ _) = undefined
diff --git a/testsuite/tests/codeGen/should_compile/all.T b/testsuite/tests/codeGen/should_compile/all.T
index 83cedc8015..cffe3d9769 100644
--- a/testsuite/tests/codeGen/should_compile/all.T
+++ b/testsuite/tests/codeGen/should_compile/all.T
@@ -91,3 +91,4 @@ test('T14373d', [],
switch_skeleton_and_entries_only])
test('T17648', normal, makefile_test, [])
+test('T17904', normal, compile, ['-O'])