summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorCheng Shao <astrohavoc@gmail.com>2022-09-12 19:27:05 +0000
committerMarge Bot <ben+marge-bot@smart-cactus.org>2022-09-13 10:29:45 -0400
commitdc6af9ed87e619d754bfc385df931c81cba6d93a (patch)
tree413aa89a8c82d2d88cb2eee7a4f9d743eb7aa6d5
parentc14370d765efb81ead9a80dc5450dc97e3167b6e (diff)
downloadhaskell-dc6af9ed87e619d754bfc385df931c81cba6d93a.tar.gz
compiler: remove unused lazy state monad
-rw-r--r--compiler/GHC/Utils/Monad/State/Lazy.hs78
-rw-r--r--compiler/ghc.cabal.in1
2 files changed, 0 insertions, 79 deletions
diff --git a/compiler/GHC/Utils/Monad/State/Lazy.hs b/compiler/GHC/Utils/Monad/State/Lazy.hs
deleted file mode 100644
index 4f9cb034df..0000000000
--- a/compiler/GHC/Utils/Monad/State/Lazy.hs
+++ /dev/null
@@ -1,78 +0,0 @@
-{-# LANGUAGE DeriveFunctor #-}
-{-# LANGUAGE UnboxedTuples #-}
-{-# LANGUAGE PatternSynonyms #-}
-
--- | A lazy state monad.
-module GHC.Utils.Monad.State.Lazy
- ( -- * The State monda
- State(State)
- , state
- , evalState
- , execState
- , runState
- -- * Operations
- , get
- , gets
- , put
- , modify
- ) where
-
-import GHC.Prelude
-
-import GHC.Exts (oneShot)
-
--- | A state monad which is lazy in the state.
-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
- (# f, s' #) -> case runState' n s' of
- (# x, s'' #) -> (# f x, s'' #)
-
-instance Monad (State s) where
- m >>= n = State $ \s -> case runState' m s of
- (# r, s' #) -> runState' (n r) s'
-
-state :: (s -> (a, s)) -> State s a
-state f = State $ \s -> case f s of
- (r, s') -> (# r, s' #)
-
-get :: State s s
-get = State $ \s -> (# s, s #)
-
-gets :: (s -> a) -> State s a
-gets f = State $ \s -> (# f s, s #)
-
-put :: s -> State s ()
-put s' = State $ \_ -> (# (), s' #)
-
-modify :: (s -> s) -> State s ()
-modify f = State $ \s -> (# (), f s #)
-
-
-evalState :: State s a -> s -> a
-evalState s i = case runState' s i of
- (# a, _ #) -> a
-
-
-execState :: State s a -> s -> s
-execState s i = case runState' s i of
- (# _, s' #) -> s'
-
-
-runState :: State s a -> s -> (a, s)
-runState s i = case runState' s i of
- (# a, s' #) -> (a, s')
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 9bd00b77ed..0ac1080c65 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -795,7 +795,6 @@ Library
GHC.Utils.Misc
GHC.Utils.Monad
GHC.Utils.Monad.State.Strict
- GHC.Utils.Monad.State.Lazy
GHC.Utils.Outputable
GHC.Utils.Panic
GHC.Utils.Panic.Plain