summaryrefslogtreecommitdiff
path: root/compiler/utils
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/utils')
-rw-r--r--compiler/utils/Binary.hs23
-rw-r--r--compiler/utils/Digraph.lhs17
-rw-r--r--compiler/utils/FastMutInt.lhs4
-rw-r--r--compiler/utils/Panic.lhs23
-rw-r--r--compiler/utils/Pretty.lhs9
-rw-r--r--compiler/utils/UniqFM.lhs12
-rw-r--r--compiler/utils/Util.lhs4
7 files changed, 7 insertions, 85 deletions
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index e479b791da..6bce8321fa 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -202,12 +202,6 @@ writeBinMem (BinMem _ ix_r sz_r arr_r) fn = do
arr <- readIORef arr_r
ix <- readFastMutInt ix_r
hPutArray h arr ix
-#if __GLASGOW_HASKELL__ <= 500
- -- workaround a bug in old implementation of hPutBuf (it doesn't
- -- set the FILEOBJ_RW_WRITTEN flag on the file object, so the file doens't
- -- get flushed properly). Adding an extra '\0' doens't do any harm.
- hPutChar h '\0'
-#endif
hClose h
readBinMem :: FilePath -> IO BinHandle
@@ -272,11 +266,7 @@ getWord8 (BinMem _ ix_r sz_r arr_r) = do
ix <- readFastMutInt ix_r
sz <- readFastMutInt sz_r
when (ix >= sz) $
-#if __GLASGOW_HASKELL__ <= 408
- throw (mkIOError eofErrorType "Data.Binary.getWord8" Nothing Nothing)
-#else
ioError (mkIOError eofErrorType "Data.Binary.getWord8" Nothing Nothing)
-#endif
arr <- readIORef arr_r
w <- unsafeRead arr ix
writeFastMutInt ix_r (ix+1)
@@ -516,23 +506,12 @@ freezeByteArray arr = IO $ \s ->
(# s, BA arr #) }
writeByteArray :: MutableByteArray# RealWorld -> Int# -> Word8 -> IO ()
-
-#if __GLASGOW_HASKELL__ < 503
-writeByteArray arr i w8 = IO $ \s ->
- case word8ToWord w8 of { W# w# ->
- case writeCharArray# arr i (chr# (word2Int# w#)) s of { s ->
- (# s , () #) }}
-#else
writeByteArray arr i (W8# w) = IO $ \s ->
case writeWord8Array# arr i w s of { s ->
(# s, () #) }
-#endif
-#if __GLASGOW_HASKELL__ < 503
-indexByteArray a# n# = fromIntegral (I# (ord# (indexCharArray# a# n#)))
-#else
+indexByteArray :: ByteArray# -> Int# -> Word8
indexByteArray a# n# = W8# (indexWord8Array# a# n#)
-#endif
instance (Integral a, Binary a) => Binary (Ratio a) where
put_ bh (a :% b) = do put_ bh a; put_ bh b
diff --git a/compiler/utils/Digraph.lhs b/compiler/utils/Digraph.lhs
index 669f718b43..9129d9d929 100644
--- a/compiler/utils/Digraph.lhs
+++ b/compiler/utils/Digraph.lhs
@@ -252,27 +252,16 @@ draw (Node x ts) = grp this (space (length this)) (stLoop ts)
%************************************************************************
\begin{code}
-#if __GLASGOW_HASKELL__ >= 504
-newSTArray :: Ix i => (i,i) -> e -> ST s (STArray s i e)
-newSTArray = newArray
-
-readSTArray :: Ix i => STArray s i e -> i -> ST s e
-readSTArray = readArray
-
-writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s ()
-writeSTArray = writeArray
-#endif
-
type Set s = STArray s Vertex Bool
mkEmpty :: Bounds -> ST s (Set s)
-mkEmpty bnds = newSTArray bnds False
+mkEmpty bnds = newArray bnds False
contains :: Set s -> Vertex -> ST s Bool
-contains m v = readSTArray m v
+contains m v = readArray m v
include :: Set s -> Vertex -> ST s ()
-include m v = writeSTArray m v True
+include m v = writeArray m v True
\end{code}
\begin{code}
diff --git a/compiler/utils/FastMutInt.lhs b/compiler/utils/FastMutInt.lhs
index 86ca0bd7f7..3c2a199198 100644
--- a/compiler/utils/FastMutInt.lhs
+++ b/compiler/utils/FastMutInt.lhs
@@ -19,10 +19,6 @@ module FastMutInt(
import GHC.Base
import GHC.IOBase
-
-#if __GLASGOW_HASKELL__ < 411
-newByteArray# = newCharArray#
-#endif
\end{code}
\begin{code}
diff --git a/compiler/utils/Panic.lhs b/compiler/utils/Panic.lhs
index eb3ce78dd3..53d75b05a9 100644
--- a/compiler/utils/Panic.lhs
+++ b/compiler/utils/Panic.lhs
@@ -39,7 +39,7 @@ import Posix ( Handler(Catch), installHandler, sigINT, sigQUIT )
import GHC.ConsoleHandler
#endif
-import Control.Exception hiding (try)
+import Control.Exception
import Control.Concurrent ( myThreadId, MVar, ThreadId, withMVar, newMVar )
import Data.Dynamic
import qualified Control.Exception as Exception
@@ -171,33 +171,14 @@ tryMost action = do r <- try action; filter r
tryUser :: IO a -> IO (Either Exception.Exception a)
tryUser action = tryJust tc_errors action
where
-#if __GLASGOW_HASKELL__ > 504 || __GLASGOW_HASKELL__ < 500
+#if __GLASGOW_HASKELL__ > 504
tc_errors e@(Exception.IOException ioe) | isUserError ioe = Just e
-#elif __GLASGOW_HASKELL__ == 502
- tc_errors e@(UserError _) = Just e
#else
tc_errors e@(Exception.IOException ioe) | isUserError e = Just e
#endif
tc_errors _other = Nothing
\end{code}
-Compatibility stuff:
-
-\begin{code}
-#if __GLASGOW_HASKELL__ <= 408
-try = Exception.tryAllIO
-#else
-try = Exception.try
-#endif
-
-#if __GLASGOW_HASKELL__ <= 408
-catchJust = Exception.catchIO
-tryJust = Exception.tryIO
-ioErrors = Exception.justIoErrors
-throwTo = Exception.raiseInThread
-#endif
-\end{code}
-
Standard signal handlers for catching ^C, which just throw an
exception in the target thread. The current target thread is
the thread at the head of the list in the MVar passed to
diff --git a/compiler/utils/Pretty.lhs b/compiler/utils/Pretty.lhs
index 0fc817f288..f611d7a13c 100644
--- a/compiler/utils/Pretty.lhs
+++ b/compiler/utils/Pretty.lhs
@@ -1022,11 +1022,7 @@ printDoc mode hdl doc
-- some versions of hPutBuf will barf if the length is zero
hPutLitString handle a# 0# = return ()
hPutLitString handle a# l#
-#if __GLASGOW_HASKELL__ < 411
- = hPutBuf handle (A# a#) (I# l#)
-#else
= hPutBuf handle (Ptr a#) (I# l#)
-#endif
-- Printing output in LeftMode is performance critical: it's used when
-- dumping C and assembly output, so we allow ourselves a few dirty
@@ -1066,9 +1062,4 @@ layLeft b (TextBeside s sl p) = put b s >> layLeft b p
put b (Str s) = bPutStr b s
put b (PStr s) = bPutFS b s
put b (LStr s l) = bPutLitString b s l
-
-#if __GLASGOW_HASKELL__ < 503
-hPutBuf = hPutBufFull
-#endif
-
\end{code}
diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs
index 267aeabd81..bb5b33e8bc 100644
--- a/compiler/utils/UniqFM.lhs
+++ b/compiler/utils/UniqFM.lhs
@@ -827,18 +827,8 @@ shiftR_ :: FastInt -> FastInt -> FastInt
#if __GLASGOW_HASKELL__
{-# INLINE shiftL_ #-}
{-# INLINE shiftR_ #-}
-#if __GLASGOW_HASKELL__ >= 503
shiftL_ n p = word2Int#((int2Word# n) `uncheckedShiftL#` p)
-#else
-shiftL_ n p = word2Int#((int2Word# n) `shiftL#` p)
-#endif
-shiftR_ n p = word2Int#((int2Word# n) `shiftr` p)
- where
-#if __GLASGOW_HASKELL__ >= 503
- shiftr x y = uncheckedShiftRL# x y
-#else
- shiftr x y = shiftRL# x y
-#endif
+shiftR_ n p = word2Int#((int2Word# n) `uncheckedShiftRL#` p)
#else /* not GHC */
shiftL_ n p = n * (2 ^ p)
diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs
index 6463c1ac42..39fd64b679 100644
--- a/compiler/utils/Util.lhs
+++ b/compiler/utils/Util.lhs
@@ -890,13 +890,9 @@ handleDyn :: Typeable ex => (ex -> IO a) -> IO a -> IO a
handleDyn = flip catchDyn
handle :: (Exception -> IO a) -> IO a -> IO a
-#if __GLASGOW_HASKELL__ < 501
-handle = flip Exception.catchAllIO
-#else
handle h f = f `Exception.catch` \e -> case e of
ExitException _ -> throw e
_ -> h e
-#endif
-- --------------------------------------------------------------
-- check existence & modification time at the same time