summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAndreas Klebinger <klebinger.andreas@gmx.at>2021-03-30 18:02:38 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-04-05 20:43:27 -0400
commit048af266ff63f08d4ff2cb4345b7805162442f29 (patch)
tree3da2f5500221a7fefe9e334026dddf708c8ecede
parent10782edf760d60987a3202d5dad0c5ea44aca8fc (diff)
downloadhaskell-048af266ff63f08d4ff2cb4345b7805162442f29.tar.gz
One-Shotify GHC.Utils.Monad.State (#18202)
-rw-r--r--compiler/GHC/Utils/Monad/State.hs16
1 files changed, 15 insertions, 1 deletions
diff --git a/compiler/GHC/Utils/Monad/State.hs b/compiler/GHC/Utils/Monad/State.hs
index c7b9e3f591..997137525b 100644
--- a/compiler/GHC/Utils/Monad/State.hs
+++ b/compiler/GHC/Utils/Monad/State.hs
@@ -1,13 +1,27 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE PatternSynonyms #-}
module GHC.Utils.Monad.State where
import GHC.Prelude
-newtype State s a = State { runState' :: s -> (# a, s #) }
+import GHC.Exts (oneShot)
+
+newtype State s a = State' { runState' :: s -> (# a, s #) }
deriving (Functor)
+pattern State :: (s -> (# a, s #))
+ -> State s a
+
+-- This pattern synonym makes the monad eta-expand,
+-- which as a very beneficial effect on compiler performance
+-- See #18202.
+-- See Note [The one-shot state monad trick] in GHC.Utils.Monad
+pattern State m <- State' m
+ where
+ State m = State' (oneShot $ \s -> m s)
+
instance Applicative (State s) where
pure x = State $ \s -> (# x, s #)
m <*> n = State $ \s -> case runState' m s of