[tor-commits] [tordnsel/master] remove compatibility shim for Control.Exception

arlo at torproject.org arlo at torproject.org
Fri Mar 4 17:39:44 UTC 2016


commit 45e962d5fd0100fe3a603b7c450d4ac624be42ae
Author: David Kaloper <david at numm.org>
Date:   Thu Aug 8 03:16:14 2013 +0200

    remove compatibility shim for Control.Exception
---
 src/TorDNSEL/Compat/Exception.hs                  | 26 -----------------------
 src/TorDNSEL/Config/Internals.hs                  |  2 +-
 src/TorDNSEL/Control/Concurrent/Future.hs         |  2 +-
 src/TorDNSEL/Control/Concurrent/Link/Internals.hs |  2 +-
 src/TorDNSEL/Control/Concurrent/Util.hs           |  2 +-
 src/TorDNSEL/DNS/Internals.hs                     |  2 +-
 src/TorDNSEL/DNS/Server/Internals.hs              |  2 +-
 src/TorDNSEL/Directory/Internals.hs               |  2 +-
 src/TorDNSEL/ExitTest/Initiator/Internals.hs      |  2 +-
 src/TorDNSEL/ExitTest/Server/Internals.hs         |  2 +-
 src/TorDNSEL/Log/Internals.hsc                    |  2 +-
 src/TorDNSEL/Main.hsc                             |  2 +-
 src/TorDNSEL/NetworkState/Internals.hs            |  2 +-
 src/TorDNSEL/NetworkState/Storage/Internals.hs    |  2 +-
 src/TorDNSEL/Socks/Internals.hs                   |  2 +-
 src/TorDNSEL/Statistics/Internals.hs              |  2 +-
 src/TorDNSEL/TorControl/Internals.hs              |  2 +-
 src/TorDNSEL/Util.hsc                             |  2 +-
 18 files changed, 17 insertions(+), 43 deletions(-)

diff --git a/src/TorDNSEL/Compat/Exception.hs b/src/TorDNSEL/Compat/Exception.hs
deleted file mode 100644
index b206513..0000000
--- a/src/TorDNSEL/Compat/Exception.hs
+++ /dev/null
@@ -1,26 +0,0 @@
-{-# LANGUAGE CPP #-}
-
------------------------------------------------------------------------------
--- |
--- Module      : TorDNSEL.Compat.Exception
--- Copyright   : (c) tup 2007
--- License     : Public domain (see LICENSE)
---
--- Maintainer  : tup.tuple at googlemail.com
--- Stability   : alpha
--- Portability : non-portable (pattern guards, bang patterns, concurrency,
---                             STM, FFI)
---
--- Ensure compatibility between several GHC versions on exception handling.
---
------------------------------------------------------------------------------
-
-module TorDNSEL.Compat.Exception (
-    module Exception
-  ) where
-
-#if __GLASGOW_HASKELL__ == 610
-import Control.OldException as Exception
-#else
-import Control.Exception as Exception
-#endif
diff --git a/src/TorDNSEL/Config/Internals.hs b/src/TorDNSEL/Config/Internals.hs
index 54366f3..5458813 100644
--- a/src/TorDNSEL/Config/Internals.hs
+++ b/src/TorDNSEL/Config/Internals.hs
@@ -49,7 +49,7 @@ import Prelude hiding (log)
 import Control.Arrow ((***), second)
 import Control.Concurrent.Chan
 import Control.Concurrent.MVar
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (liftM, liftM2, ap)
 import Control.Monad.Error (MonadError(..))
 import Control.Monad.Fix (fix)
diff --git a/src/TorDNSEL/Control/Concurrent/Future.hs b/src/TorDNSEL/Control/Concurrent/Future.hs
index 8f3c77e..4b5c6ac 100644
--- a/src/TorDNSEL/Control/Concurrent/Future.hs
+++ b/src/TorDNSEL/Control/Concurrent/Future.hs
@@ -18,7 +18,7 @@ module TorDNSEL.Control.Concurrent.Future (
   ) where
 
 import Control.Concurrent.MVar (MVar, newEmptyMVar, putMVar, withMVar)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 
 import TorDNSEL.Control.Concurrent.Link
 
diff --git a/src/TorDNSEL/Control/Concurrent/Link/Internals.hs b/src/TorDNSEL/Control/Concurrent/Link/Internals.hs
index 8f8988e..8107481 100644
--- a/src/TorDNSEL/Control/Concurrent/Link/Internals.hs
+++ b/src/TorDNSEL/Control/Concurrent/Link/Internals.hs
@@ -28,7 +28,7 @@ module TorDNSEL.Control.Concurrent.Link.Internals where
 import qualified Control.Concurrent as C
 import Control.Concurrent.MVar
   (MVar, newMVar, withMVar, modifyMVar, modifyMVar_)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (unless)
 import qualified Data.Foldable as F
 import qualified Data.Map as M
diff --git a/src/TorDNSEL/Control/Concurrent/Util.hs b/src/TorDNSEL/Control/Concurrent/Util.hs
index cad89f4..1defc31 100644
--- a/src/TorDNSEL/Control/Concurrent/Util.hs
+++ b/src/TorDNSEL/Control/Concurrent/Util.hs
@@ -12,7 +12,7 @@
 -----------------------------------------------------------------------------
 module TorDNSEL.Control.Concurrent.Util where
 
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Concurrent.MVar (newEmptyMVar, takeMVar, putMVar, tryPutMVar)
 import Data.Dynamic (Dynamic)
 import Data.Maybe (isJust)
diff --git a/src/TorDNSEL/DNS/Internals.hs b/src/TorDNSEL/DNS/Internals.hs
index 23f1595..54d1c08 100644
--- a/src/TorDNSEL/DNS/Internals.hs
+++ b/src/TorDNSEL/DNS/Internals.hs
@@ -59,7 +59,7 @@ module TorDNSEL.DNS.Internals (
   , Class(..)
   ) where
 
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (when, unless, replicateM, liftM2, liftM3, forM)
 import qualified Control.Monad.State as S
 import Control.Monad.Trans (lift)
diff --git a/src/TorDNSEL/DNS/Server/Internals.hs b/src/TorDNSEL/DNS/Server/Internals.hs
index 008af72..622de9b 100644
--- a/src/TorDNSEL/DNS/Server/Internals.hs
+++ b/src/TorDNSEL/DNS/Server/Internals.hs
@@ -21,7 +21,7 @@
 module TorDNSEL.DNS.Server.Internals where
 
 import Prelude hiding (log)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (when, guard, liftM2, liftM3)
 import Data.Bits ((.|.), shiftL)
 import qualified Data.ByteString.Char8 as B
diff --git a/src/TorDNSEL/Directory/Internals.hs b/src/TorDNSEL/Directory/Internals.hs
index ace1f68..7dc1eb2 100644
--- a/src/TorDNSEL/Directory/Internals.hs
+++ b/src/TorDNSEL/Directory/Internals.hs
@@ -51,7 +51,7 @@ module TorDNSEL.Directory.Internals (
   ) where
 
 import Control.Concurrent.MVar (newMVar, withMVar)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (when, unless, liftM)
 import Control.Monad.Error (MonadError(throwError))
 import Data.Char
diff --git a/src/TorDNSEL/ExitTest/Initiator/Internals.hs b/src/TorDNSEL/ExitTest/Initiator/Internals.hs
index 9acd2c3..a63e25f 100644
--- a/src/TorDNSEL/ExitTest/Initiator/Internals.hs
+++ b/src/TorDNSEL/ExitTest/Initiator/Internals.hs
@@ -62,7 +62,7 @@ import Prelude hiding (log)
 import Control.Arrow (first, second)
 import Control.Concurrent (threadDelay)
 import Control.Concurrent.Chan (Chan, newChan, writeChan, readChan)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (replicateM_, guard, when)
 import qualified Data.ByteString.Char8 as B
 import Data.Dynamic (fromDynamic)
diff --git a/src/TorDNSEL/ExitTest/Server/Internals.hs b/src/TorDNSEL/ExitTest/Server/Internals.hs
index 560221a..b6aa705 100644
--- a/src/TorDNSEL/ExitTest/Server/Internals.hs
+++ b/src/TorDNSEL/ExitTest/Server/Internals.hs
@@ -24,7 +24,7 @@ module TorDNSEL.ExitTest.Server.Internals where
 import Prelude hiding (log)
 import Control.Concurrent.Chan (Chan, newChan, readChan, writeChan, isEmptyChan)
 import Control.Concurrent.QSemN (QSemN, newQSemN, waitQSemN, signalQSemN)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (when, forM, foldM)
 import Control.Monad.Fix (fix)
 import Control.Monad.Trans (lift)
diff --git a/src/TorDNSEL/Log/Internals.hsc b/src/TorDNSEL/Log/Internals.hsc
index 5e7854e..7d7a2d8 100644
--- a/src/TorDNSEL/Log/Internals.hsc
+++ b/src/TorDNSEL/Log/Internals.hsc
@@ -25,7 +25,7 @@ module TorDNSEL.Log.Internals where
 import Prelude hiding (log)
 import Control.Concurrent.Chan (Chan, newChan, writeChan, readChan)
 import Control.Concurrent.MVar (MVar, newMVar, readMVar, swapMVar)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (when, liftM2)
 import Control.Monad.Fix (fix)
 import Control.Monad.Trans (MonadIO, liftIO)
diff --git a/src/TorDNSEL/Main.hsc b/src/TorDNSEL/Main.hsc
index 5a76519..3037ee7 100644
--- a/src/TorDNSEL/Main.hsc
+++ b/src/TorDNSEL/Main.hsc
@@ -64,7 +64,7 @@ module TorDNSEL.Main (
 
 import Prelude hiding (log)
 import Control.Concurrent.Chan (Chan, newChan, readChan, writeChan)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (when, liftM, forM, forM_)
 import Control.Monad.Fix (fix)
 import Control.Monad.State (StateT, runStateT, liftIO, get, put)
diff --git a/src/TorDNSEL/NetworkState/Internals.hs b/src/TorDNSEL/NetworkState/Internals.hs
index 933b7eb..32b4a42 100644
--- a/src/TorDNSEL/NetworkState/Internals.hs
+++ b/src/TorDNSEL/NetworkState/Internals.hs
@@ -64,7 +64,7 @@ import Control.Monad.State
 import Control.Concurrent (threadDelay)
 import Control.Concurrent.Chan (newChan, readChan, writeChan)
 import Control.Concurrent.MVar (MVar, newMVar, readMVar, swapMVar)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import qualified Data.ByteString.Char8 as B
 import Data.ByteString.Char8 (ByteString)
 import Data.List (foldl')
diff --git a/src/TorDNSEL/NetworkState/Storage/Internals.hs b/src/TorDNSEL/NetworkState/Storage/Internals.hs
index e0d610c..fd9a04b 100644
--- a/src/TorDNSEL/NetworkState/Storage/Internals.hs
+++ b/src/TorDNSEL/NetworkState/Storage/Internals.hs
@@ -22,7 +22,7 @@ module TorDNSEL.NetworkState.Storage.Internals where
 import Prelude hiding (log)
 import Control.Arrow (second)
 import Control.Concurrent.Chan (newChan, readChan, writeChan)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (liftM2, when, forM)
 import Control.Monad.Error (MonadError(throwError))
 import Control.Monad.Fix (fix)
diff --git a/src/TorDNSEL/Socks/Internals.hs b/src/TorDNSEL/Socks/Internals.hs
index 719e367..e556bf9 100644
--- a/src/TorDNSEL/Socks/Internals.hs
+++ b/src/TorDNSEL/Socks/Internals.hs
@@ -40,7 +40,7 @@ module TorDNSEL.Socks.Internals (
   , showSocksError
   ) where
 
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import qualified Data.ByteString.Char8 as B
 import qualified Data.ByteString.Lazy as L
 import Data.ByteString (ByteString)
diff --git a/src/TorDNSEL/Statistics/Internals.hs b/src/TorDNSEL/Statistics/Internals.hs
index 3dcd510..e24c745 100644
--- a/src/TorDNSEL/Statistics/Internals.hs
+++ b/src/TorDNSEL/Statistics/Internals.hs
@@ -23,7 +23,7 @@ import Prelude hiding (log)
 import Control.Concurrent.Chan (Chan, newChan, readChan, writeChan)
 import Control.Concurrent.MVar (MVar, newMVar, modifyMVar_, readMVar)
 import Control.Concurrent.QSem (QSem, newQSem, waitQSem, signalQSem)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad.Fix (fix)
 import qualified Data.ByteString.Char8 as B
 import Data.Maybe (isJust, isNothing)
diff --git a/src/TorDNSEL/TorControl/Internals.hs b/src/TorDNSEL/TorControl/Internals.hs
index 015bd76..dba1e85 100644
--- a/src/TorDNSEL/TorControl/Internals.hs
+++ b/src/TorDNSEL/TorControl/Internals.hs
@@ -145,7 +145,7 @@ import Control.Arrow (first, second)
 import Control.Concurrent.Chan (newChan, readChan, writeChan)
 import Control.Concurrent.MVar
   (MVar, newMVar, newEmptyMVar, takeMVar, tryPutMVar, withMVar, modifyMVar_)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad (when, unless, liftM, mzero, mplus)
 import Control.Monad.Error (MonadError(..))
 import Control.Monad.Fix (fix)
diff --git a/src/TorDNSEL/Util.hsc b/src/TorDNSEL/Util.hsc
index bb81b43..a2357d8 100644
--- a/src/TorDNSEL/Util.hsc
+++ b/src/TorDNSEL/Util.hsc
@@ -101,7 +101,7 @@ module TorDNSEL.Util (
   ) where
 
 import Control.Arrow ((&&&), first, second)
-import qualified TorDNSEL.Compat.Exception as E
+import qualified Control.Exception as E
 import Control.Monad.Error
   (Error(..), MonadError(..), MonadTrans(..), MonadIO(..))
 import qualified Control.Monad.State as State



More information about the tor-commits mailing list