[commit: ghc] wip/inline-ioenv: Inline IOEnv methods (4a8e9b0)
git at git.haskell.org
git at git.haskell.org
Thu Feb 23 16:50:51 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/inline-ioenv
Link : http://ghc.haskell.org/trac/ghc/changeset/4a8e9b0bf2c48f1a9b8c8afd2c9b781da5fc866a/ghc
>---------------------------------------------------------------
commit 4a8e9b0bf2c48f1a9b8c8afd2c9b781da5fc866a
Author: Dmitry Ivanov <ethercrow at gmail.com>
Date: Thu Feb 23 11:50:27 2017 -0500
Inline IOEnv methods
These changes seem to make compiler allocate less and a bit faster.
However, I've checked only with a few files and only with a profiled
build of stage2. How do I check the alleged performance improvement
properly?
Reviewers: austin, bgamari, dfeuer
Subscribers: dfeuer, thomie
Differential Revision: https://phabricator.haskell.org/D3171
>---------------------------------------------------------------
4a8e9b0bf2c48f1a9b8c8afd2c9b781da5fc866a
compiler/utils/IOEnv.hs | 7 +++++++
1 file changed, 7 insertions(+)
diff --git a/compiler/utils/IOEnv.hs b/compiler/utils/IOEnv.hs
index 29854c5..17af162 100644
--- a/compiler/utils/IOEnv.hs
+++ b/compiler/utils/IOEnv.hs
@@ -58,7 +58,9 @@ unIOEnv :: IOEnv env a -> (env -> IO a)
unIOEnv (IOEnv m) = m
instance Monad (IOEnv m) where
+ {-# INLINE (>>=) #-}
(>>=) = thenM
+ {-# INLINE (>>) #-}
(>>) = (*>)
fail _ = failM -- Ignore the string
@@ -70,19 +72,24 @@ instance MonadFail.MonadFail (IOEnv m) where
instance Applicative (IOEnv m) where
pure = returnM
+ {-# INLINE (<*>) #-}
IOEnv f <*> IOEnv x = IOEnv (\ env -> f env <*> x env )
(*>) = thenM_
instance Functor (IOEnv m) where
+ {-# INLINE fmap #-}
fmap f (IOEnv m) = IOEnv (\ env -> fmap f (m env))
+{-# INLINE returnM #-}
returnM :: a -> IOEnv env a
returnM a = IOEnv (\ _ -> return a)
+{-# INLINE thenM #-}
thenM :: IOEnv env a -> (a -> IOEnv env b) -> IOEnv env b
thenM (IOEnv m) f = IOEnv (\ env -> do { r <- m env ;
unIOEnv (f r) env })
+{-# INLINE thenM_ #-}
thenM_ :: IOEnv env a -> IOEnv env b -> IOEnv env b
thenM_ (IOEnv m) f = IOEnv (\ env -> do { _ <- m env ; unIOEnv f env })
More information about the ghc-commits
mailing list