module IdeSession.Util.BlockingOps (
lineNumber
, traceOnException
, mapExceptionIO
, mapExceptionShow
, putMVar
, takeMVar
, modifyMVar
, modifyMVar_
, withMVar
, readMVar
, swapMVar
, putStrictMVar
, takeStrictMVar
, modifyStrictMVar
, modifyStrictMVar_
, withStrictMVar
, readStrictMVar
, swapStrictMVar
, readChan
, wait
, waitCatch
, waitAny
, waitAnyCatchCancel
) where
import Language.Haskell.TH
import qualified Control.Concurrent as C
import qualified Control.Concurrent.Async as Async
import System.IO (hPutStrLn, stderr)
import qualified Control.Exception as Ex
import qualified IdeSession.Strict.MVar as StrictMVar
lineNumber :: ExpQ
lineNumber = do
Loc{loc_module, loc_start=(line, _)} <- location
[| loc_module ++ ":" ++ show (line :: Int) |]
mapExceptionIO :: (Ex.Exception e1, Ex.Exception e2)
=> (e1 -> e2) -> IO a -> IO a
mapExceptionIO f io = Ex.catch io (Ex.throwIO . f)
mapExceptionShow :: (String -> String) -> IO a -> IO a
mapExceptionShow f = mapExceptionIO (userError . f . showSomeException)
where
showSomeException :: Ex.SomeException -> String
showSomeException = show
traceOnException :: String -> IO a -> IO a
traceOnException str io = Ex.catch io $ \e -> do
hPutStrLn stderr (str ++ ": " ++ show e)
Ex.throwIO (e :: Ex.SomeException)
#define DEBUGGING 0
#if DEBUGGING == 1
rethrowWithLineNumber1 :: ExpQ -> ExpQ
rethrowWithLineNumber1 expr =
[| \arg1 -> mapExceptionShow (\e -> $lineNumber ++ ": " ++ e)
($expr arg1)
|]
rethrowWithLineNumber2 :: ExpQ -> ExpQ
rethrowWithLineNumber2 expr =
[| \arg1 arg2 -> mapExceptionShow (\e -> $lineNumber ++ ": " ++ e)
($expr arg1 arg2)
|]
takeMVar :: ExpQ
takeMVar = rethrowWithLineNumber1 [| C.takeMVar |]
putMVar :: ExpQ
putMVar = rethrowWithLineNumber2 [| C.putMVar |]
readMVar :: ExpQ
readMVar = rethrowWithLineNumber1 [| C.readMVar |]
modifyMVar :: ExpQ
modifyMVar = rethrowWithLineNumber2 [| C.modifyMVar |]
modifyMVar_ :: ExpQ
modifyMVar_ = rethrowWithLineNumber2 [| C.modifyMVar_ |]
withMVar :: ExpQ
withMVar = rethrowWithLineNumber2 [| C.withMVar |]
swapMVar :: ExpQ
swapMVar = rethrowWithLineNumber2 [| C.swapMVar |]
takeStrictMVar :: ExpQ
takeStrictMVar = rethrowWithLineNumber1 [| StrictMVar.takeMVar |]
putStrictMVar :: ExpQ
putStrictMVar = rethrowWithLineNumber2 [| StrictMVar.putMVar |]
readStrictMVar :: ExpQ
readStrictMVar = rethrowWithLineNumber1 [| StrictMVar.readMVar |]
modifyStrictMVar :: ExpQ
modifyStrictMVar = rethrowWithLineNumber2 [| StrictMVar.modifyMVar |]
modifyStrictMVar_ :: ExpQ
modifyStrictMVar_ = rethrowWithLineNumber2 [| StrictMVar.modifyMVar_ |]
withStrictMVar :: ExpQ
withStrictMVar = rethrowWithLineNumber2 [| StrictMVar.withMVar |]
swapStrictMVar :: ExpQ
swapStrictMVar = rethrowWithLineNumber2 [| StrictMVar.swapMVar |]
readChan :: ExpQ
readChan = rethrowWithLineNumber1 [| C.readChan |]
wait :: ExpQ
wait = rethrowWithLineNumber1 [| Async.wait |]
waitCatch :: ExpQ
waitCatch = rethrowWithLineNumber1 [| Async.waitCatch |]
waitAny :: ExpQ
waitAny = rethrowWithLineNumber1 [| Async.waitAny |]
waitAnyCatchCancel :: ExpQ
waitAnyCatchCancel = rethrowWithLineNumber1 [| Async.waitAnyCatchCancel |]
#else
takeMVar :: ExpQ
takeMVar = [| C.takeMVar |]
putMVar :: ExpQ
putMVar = [| C.putMVar |]
readMVar :: ExpQ
readMVar = [| C.readMVar |]
modifyMVar :: ExpQ
modifyMVar = [| C.modifyMVar |]
modifyMVar_ :: ExpQ
modifyMVar_ = [| C.modifyMVar_ |]
withMVar :: ExpQ
withMVar = [| C.withMVar |]
swapMVar :: ExpQ
swapMVar = [| C.swapMVar |]
takeStrictMVar :: ExpQ
takeStrictMVar = [| StrictMVar.takeMVar |]
putStrictMVar :: ExpQ
putStrictMVar = [| StrictMVar.putMVar |]
readStrictMVar :: ExpQ
readStrictMVar = [| StrictMVar.readMVar |]
modifyStrictMVar :: ExpQ
modifyStrictMVar = [| StrictMVar.modifyMVar |]
modifyStrictMVar_ :: ExpQ
modifyStrictMVar_ = [| StrictMVar.modifyMVar_ |]
withStrictMVar :: ExpQ
withStrictMVar = [| StrictMVar.withMVar |]
swapStrictMVar :: ExpQ
swapStrictMVar = [| StrictMVar.swapMVar |]
readChan :: ExpQ
readChan = [| C.readChan |]
wait :: ExpQ
wait = [| Async.wait |]
waitCatch :: ExpQ
waitCatch = [| Async.waitCatch |]
waitAny :: ExpQ
waitAny = [| Async.waitAny |]
waitAnyCatchCancel :: ExpQ
waitAnyCatchCancel = [| Async.waitAnyCatchCancel |]
#endif