summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/basicTypes/UniqSupply.lhs28
-rw-r--r--compiler/deSugar/DsGRHSs.lhs6
-rw-r--r--compiler/ghci/RtClosureInspect.hs2
-rw-r--r--compiler/rename/RnEnv.lhs23
-rw-r--r--compiler/rename/RnExpr.lhs22
-rw-r--r--compiler/rename/RnSource.lhs21
-rw-r--r--compiler/specialise/SpecConstr.lhs1
-rw-r--r--compiler/stranal/WorkWrap.lhs1
-rw-r--r--compiler/typecheck/TcHsSyn.lhs15
-rw-r--r--compiler/utils/State.hs2
10 files changed, 111 insertions, 10 deletions
diff --git a/compiler/basicTypes/UniqSupply.lhs b/compiler/basicTypes/UniqSupply.lhs
index 2599d8d5f0..7bd84b3e9d 100644
--- a/compiler/basicTypes/UniqSupply.lhs
+++ b/compiler/basicTypes/UniqSupply.lhs
@@ -20,11 +20,14 @@ module UniqSupply (
UniqSM, -- type: unique supply monad
initUs, initUs_,
lazyThenUs, lazyMapUs,
- module MonadUtils, mapAndUnzipM,
+ mapAndUnzipM,
MonadUnique(..),
mkSplitUniqSupply,
- splitUniqSupply, listSplitUniqSupply
+ splitUniqSupply, listSplitUniqSupply,
+
+ -- Deprecated:
+ getUniqueUs, getUs, returnUs, thenUs, mapUs
) where
#include "HsVersions.h"
@@ -32,6 +35,9 @@ module UniqSupply (
import Unique
import FastTypes
+import MonadUtils
+import Control.Monad
+import Control.Monad.Fix
#if __GLASGOW_HASKELL__ >= 607
import GHC.IOBase (unsafeDupableInterleaveIO)
#else
@@ -112,6 +118,16 @@ instance Monad UniqSM where
(>>=) = thenUs
(>>) = thenUs_
+instance Functor UniqSM where
+ fmap f (USM x) = USM (\us -> case x us of
+ (r, us') -> (f r, us'))
+
+instance Applicative UniqSM where
+ pure = returnUs
+ (USM f) <*> (USM x) = USM $ \us -> case f us of
+ (ff, us') -> case x us' of
+ (xx, us'') -> (ff xx, us'')
+
-- the initUs function also returns the final UniqSupply; initUs_ drops it
initUs :: UniqSupply -> UniqSM a -> (a,UniqSupply)
initUs init_us m = case unUSM m init_us of { (r,us) -> (r,us) }
@@ -176,6 +192,13 @@ getUniqueUs = USM (\us -> case splitUniqSupply us of
getUniquesUs :: UniqSM [Unique]
getUniquesUs = USM (\us -> case splitUniqSupply us of
(us1,us2) -> (uniqsFromSupply us1, us2))
+
+mapUs :: (a -> UniqSM b) -> [a] -> UniqSM [b]
+mapUs f [] = returnUs []
+mapUs f (x:xs)
+ = f x `thenUs` \ r ->
+ mapUs f xs `thenUs` \ rs ->
+ returnUs (r:rs)
\end{code}
\begin{code}
@@ -189,5 +212,4 @@ lazyMapUs f (x:xs)
= f x `lazyThenUs` \ r ->
lazyMapUs f xs `lazyThenUs` \ rs ->
returnUs (r:rs)
-
\end{code}
diff --git a/compiler/deSugar/DsGRHSs.lhs b/compiler/deSugar/DsGRHSs.lhs
index db5cc0cf8d..70a3724484 100644
--- a/compiler/deSugar/DsGRHSs.lhs
+++ b/compiler/deSugar/DsGRHSs.lhs
@@ -33,8 +33,6 @@ import PrelNames
import Name
import SrcLoc
-import Control.Monad ((>=>))
-
\end{code}
@dsGuarded@ is used for both @case@ expressions and pattern bindings.
@@ -142,11 +140,11 @@ isTrueLHsExpr (L _ (HsVar v)) | v `hasKey` otherwiseIdKey
= Just return
-- trueDataConId doesn't have the same unique as trueDataCon
isTrueLHsExpr (L loc (HsTick ix frees e))
- | Just ticks <- isTrueLHsExpr e = Just (ticks >=> mkTickBox ix frees)
+ | Just ticks <- isTrueLHsExpr e = Just (\x -> ticks x >>= mkTickBox ix frees)
-- This encodes that the result is constant True for Hpc tick purposes;
-- which is specifically what isTrueLHsExpr is trying to find out.
isTrueLHsExpr (L loc (HsBinTick ixT _ e))
- | Just ticks <- isTrueLHsExpr e = Just (ticks >=> mkTickBox ixT [])
+ | Just ticks <- isTrueLHsExpr e = Just (\x -> ticks x >>= mkTickBox ixT [])
isTrueLHsExpr (L _ (HsPar e)) = isTrueLHsExpr e
isTrueLHsExpr other = Nothing
\end{code}
diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs
index db8930a05e..b5d67cf10b 100644
--- a/compiler/ghci/RtClosureInspect.hs
+++ b/compiler/ghci/RtClosureInspect.hs
@@ -73,7 +73,7 @@ import Panic
import GHC.Arr ( Array(..) )
import GHC.Exts
-import GHC.IOBase
+import GHC.IOBase ( IO(IO) )
import Control.Monad
import Data.Maybe
diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs
index 2909af34bf..801dda860c 100644
--- a/compiler/rename/RnEnv.lhs
+++ b/compiler/rename/RnEnv.lhs
@@ -70,9 +70,30 @@ import Util
import Maybes
import ListSetOps ( removeDups )
import List ( nubBy )
-import Monad ( when )
import DynFlags
import FastString
+import Control.Monad
+\end{code}
+
+\begin{code}
+-- XXX
+thenM :: Monad a => a b -> (b -> a c) -> a c
+thenM = (>>=)
+
+thenM_ :: Monad a => a b -> a c -> a c
+thenM_ = (>>)
+
+returnM :: Monad m => a -> m a
+returnM = return
+
+mappM :: (Monad m) => (a -> m b) -> [a] -> m [b]
+mappM = mapM
+
+mappM_ :: (Monad m) => (a -> m b) -> [a] -> m ()
+mappM_ = mapM_
+
+checkM :: Monad m => Bool -> m () -> m ()
+checkM = unless
\end{code}
%*********************************************************
diff --git a/compiler/rename/RnExpr.lhs b/compiler/rename/RnExpr.lhs
index 176fdb4d41..d6a87136a1 100644
--- a/compiler/rename/RnExpr.lhs
+++ b/compiler/rename/RnExpr.lhs
@@ -64,9 +64,31 @@ import SrcLoc ( Located(..), unLoc, getLoc, noLoc )
import FastString
import List ( unzip4 )
+import Control.Monad
\end{code}
+\begin{code}
+-- XXX
+thenM :: Monad a => a b -> (b -> a c) -> a c
+thenM = (>>=)
+
+thenM_ :: Monad a => a b -> a c -> a c
+thenM_ = (>>)
+
+returnM :: Monad m => a -> m a
+returnM = return
+
+mappM :: (Monad m) => (a -> m b) -> [a] -> m [b]
+mappM = mapM
+
+mappM_ :: (Monad m) => (a -> m b) -> [a] -> m ()
+mappM_ = mapM_
+
+checkM :: Monad m => Bool -> m () -> m ()
+checkM = unless
+\end{code}
+
%************************************************************************
%* *
\subsubsection{Expressions}
diff --git a/compiler/rename/RnSource.lhs b/compiler/rename/RnSource.lhs
index 1cb2223367..8847f3bc5a 100644
--- a/compiler/rename/RnSource.lhs
+++ b/compiler/rename/RnSource.lhs
@@ -59,6 +59,27 @@ import ListSetOps (findDupsEq, mkLookupFun)
import Control.Monad
\end{code}
+\begin{code}
+-- XXX
+thenM :: Monad a => a b -> (b -> a c) -> a c
+thenM = (>>=)
+
+thenM_ :: Monad a => a b -> a c -> a c
+thenM_ = (>>)
+
+returnM :: Monad m => a -> m a
+returnM = return
+
+mappM :: (Monad m) => (a -> m b) -> [a] -> m [b]
+mappM = mapM
+
+mappM_ :: (Monad m) => (a -> m b) -> [a] -> m ()
+mappM_ = mapM_
+
+checkM :: Monad m => Bool -> m () -> m ()
+checkM = unless
+\end{code}
+
@rnSourceDecl@ `renames' declarations.
It simultaneously performs dependency analysis and precedence parsing.
It also does the following error checks:
diff --git a/compiler/specialise/SpecConstr.lhs b/compiler/specialise/SpecConstr.lhs
index d9903ee3e4..f0648ccc00 100644
--- a/compiler/specialise/SpecConstr.lhs
+++ b/compiler/specialise/SpecConstr.lhs
@@ -47,6 +47,7 @@ import UniqSupply
import Outputable
import FastString
import UniqFM
+import MonadUtils
\end{code}
-----------------------------------------------------
diff --git a/compiler/stranal/WorkWrap.lhs b/compiler/stranal/WorkWrap.lhs
index 3af7e2d7c5..a6f9bede70 100644
--- a/compiler/stranal/WorkWrap.lhs
+++ b/compiler/stranal/WorkWrap.lhs
@@ -40,6 +40,7 @@ import DynFlags
import WwLib
import Util ( lengthIs, notNull )
import Outputable
+import MonadUtils
\end{code}
We take Core bindings whose binders have:
diff --git a/compiler/typecheck/TcHsSyn.lhs b/compiler/typecheck/TcHsSyn.lhs
index df6c50a6b2..7bb1d5e38d 100644
--- a/compiler/typecheck/TcHsSyn.lhs
+++ b/compiler/typecheck/TcHsSyn.lhs
@@ -59,6 +59,21 @@ import Bag
import Outputable
\end{code}
+\begin{code}
+-- XXX
+thenM :: Monad a => a b -> (b -> a c) -> a c
+thenM = (>>=)
+
+thenM_ :: Monad a => a b -> a c -> a c
+thenM_ = (>>)
+
+returnM :: Monad m => a -> m a
+returnM = return
+
+mappM :: (Monad m) => (a -> m b) -> [a] -> m [b]
+mappM = mapM
+\end{code}
+
%************************************************************************
%* *
diff --git a/compiler/utils/State.hs b/compiler/utils/State.hs
index b8fcaa1576..0b6a285562 100644
--- a/compiler/utils/State.hs
+++ b/compiler/utils/State.hs
@@ -1,5 +1,5 @@
-module State where
+module State (module State, mapAccumLM {- XXX hack -}) where
import MonadUtils