[commit: ghc] wip/D2092: GHC.Base: Use thenIO in instance Applicative IO (3350f6d)

git at git.haskell.org git at git.haskell.org
Fri Apr 8 06:35:14 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/D2092
Link       : http://ghc.haskell.org/trac/ghc/changeset/3350f6df13470bf32b9addb45991bbb5b3ba0df4/ghc

>---------------------------------------------------------------

commit 3350f6df13470bf32b9addb45991bbb5b3ba0df4
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Fri Apr 8 08:33:35 2016 +0200

    GHC.Base: Use thenIO in instance Applicative IO
    
    Since recent changes to CSE, the previous definition were no longer CSEd
    with thenIO, which resulted in extra steps in the simplifier and hence
    slightly larger compile times. See ticket:11781#comment:7.


>---------------------------------------------------------------

3350f6df13470bf32b9addb45991bbb5b3ba0df4
 libraries/base/GHC/Base.hs          | 6 +++---
 testsuite/tests/perf/compiler/all.T | 3 ++-
 2 files changed, 5 insertions(+), 4 deletions(-)

diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 89c9f63..618fa05 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -1086,9 +1086,9 @@ instance  Functor IO where
 instance Applicative IO where
     {-# INLINE pure #-}
     {-# INLINE (*>) #-}
-    pure   = returnIO
-    m *> k = m >>= \ _ -> k
-    (<*>)  = ap
+    pure  = returnIO
+    (*>)  = thenIO
+    (<*>) = ap
 
 instance  Monad IO  where
     {-# INLINE (>>)   #-}
diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T
index b3ae160..022ed92 100644
--- a/testsuite/tests/perf/compiler/all.T
+++ b/testsuite/tests/perf/compiler/all.T
@@ -624,7 +624,7 @@ test('T9020',
           [(wordsize(32), 343005716, 10),
            # Original:    381360728
            # 2014-07-31:  343005716 (Windows) (general round of updates)
-           (wordsize(64), 852298336, 10)])
+           (wordsize(64), 698401736, 10)])
            # prev:        795469104
            # 2014-07-17:  728263536 (general round of updates)
            # 2014-09-10:  785871680 post-AMP-cleanup
@@ -632,6 +632,7 @@ test('T9020',
            # 2015-10-21:  786189008 Make stronglyConnCompFromEdgedVertices deterministic
            # 2016-01-26:  698401736 improvement from using ExpTypes instead of ReturnTvs
            # 2016-04-06:  852298336 Refactoring of CSE #11781
+           # 2016-04-06:  698401736 Use thenIO in Applicative IO
       ],
       compile,[''])
 



More information about the ghc-commits mailing list