[commit: ghc] wip/T14677: WIP: reproduction of bug with slow/wrapper closure (36f1621)
git at git.haskell.org
git at git.haskell.org
Thu Jan 25 12:21:49 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T14677
Link : http://ghc.haskell.org/trac/ghc/changeset/36f1621014a86ed1d591802020d9b68499b9783e/ghc
>---------------------------------------------------------------
commit 36f1621014a86ed1d591802020d9b68499b9783e
Author: Gabor Greif <ggreif at gmail.com>
Date: Thu Jan 25 12:20:30 2018 +0100
WIP: reproduction of bug with slow/wrapper closure
>---------------------------------------------------------------
36f1621014a86ed1d591802020d9b68499b9783e
T14677.hs | 31 +++++++++++++++++++++++++++++++
1 file changed, 31 insertions(+)
diff --git a/T14677.hs b/T14677.hs
new file mode 100644
index 0000000..3c6dd87
--- /dev/null
+++ b/T14677.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE ExistentialQuantification #-}
+
+module Main where
+
+import GHC.Event
+
+-- frobbed from GHC.Event.Internal
+data Backend = forall a. Backend {
+ beState :: !a
+
+ , beModifyFd :: a
+ -> Event -- old events to watch for ('mempty' for new)
+ -> Event -- new events to watch for ('mempty' to delete)
+ -> IO Bool
+ }
+
+backend :: (a -> Event -> Event -> IO Bool) -> a -> Backend
+backend = flip Backend
+
+{-# NOINLINE be #-}
+be = backend mod ev
+ where mod e0 e1 e2 = do putStrLn "Should be:"
+ putStrLn "([evtRead],[],[evtWrite])"
+ putStrLn "Is:"
+ print (e0, e1, e2)
+ "([evtRead],[],[evtWrite])" <- pure $ show (e0, e1, e2)
+ pure $ e0 == evtRead
+ ev = evtRead
+
+main = case be of
+ Backend { beModifyFd = mod, beState = sta } -> mod sta mempty evtWrite >>= print
More information about the ghc-commits
mailing list