diff options
author | joe <joe@jerkface.net> | 2017-01-23 22:32:17 -0500 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-01-23 22:33:08 -0500 |
commit | 058ccb22f43e9053fa37ed719d31c72dd6dac27c (patch) | |
tree | f6faea43c0b4cc9428e0b8cb8d0b836a9ec13107 /src/Control | |
parent | 6a2506745dd06ad0849a1b0d440ad9751a69cf81 (diff) |
Added thread-debug flag and "threads" command.
Diffstat (limited to 'src/Control')
-rw-r--r-- | src/Control/Concurrent/Async/Lifted/Instrument.hs | 5 | ||||
-rw-r--r-- | src/Control/Concurrent/Lifted/Instrument.hs | 78 |
2 files changed, 83 insertions, 0 deletions
diff --git a/src/Control/Concurrent/Async/Lifted/Instrument.hs b/src/Control/Concurrent/Async/Lifted/Instrument.hs new file mode 100644 index 00000000..eab0fadc --- /dev/null +++ b/src/Control/Concurrent/Async/Lifted/Instrument.hs | |||
@@ -0,0 +1,5 @@ | |||
1 | module Control.Concurrent.Async.Lifted.Instrument | ||
2 | ( module Control.Concurrent.Async.Lifted | ||
3 | ) where | ||
4 | |||
5 | import Control.Concurrent.Async.Lifted | ||
diff --git a/src/Control/Concurrent/Lifted/Instrument.hs b/src/Control/Concurrent/Lifted/Instrument.hs new file mode 100644 index 00000000..9ec5deef --- /dev/null +++ b/src/Control/Concurrent/Lifted/Instrument.hs | |||
@@ -0,0 +1,78 @@ | |||
1 | {-# LANGUAGE FlexibleContexts #-} | ||
2 | module Control.Concurrent.Lifted.Instrument | ||
3 | ( module Control.Concurrent.Lifted | ||
4 | , forkIO | ||
5 | , fork | ||
6 | , labelThread | ||
7 | , threadsInformation | ||
8 | , PerThread(..) | ||
9 | ) where | ||
10 | |||
11 | import qualified Control.Concurrent.Lifted as Raw | ||
12 | import Control.Concurrent.Lifted hiding (fork) | ||
13 | import Control.Monad.Trans.Control | ||
14 | import System.IO.Unsafe | ||
15 | import System.Mem.Weak | ||
16 | import qualified Data.Map as Map | ||
17 | import qualified Data.IntMap as IntMap | ||
18 | import Control.Exception.Lifted | ||
19 | import Control.Monad.Base | ||
20 | -- import Control.Monad.IO.Class | ||
21 | import qualified GHC.Conc as GHC | ||
22 | import Data.Time.Clock | ||
23 | |||
24 | data PerThread = PerThread | ||
25 | { -- wkid :: Weak ThreadId | ||
26 | lbl :: String | ||
27 | , startTime :: UTCTime | ||
28 | } | ||
29 | deriving (Eq,Ord,Show) -- ,Data,Generic) | ||
30 | |||
31 | data GlobalState = GlobalState | ||
32 | { threads :: Map.Map ThreadId PerThread -- IntMap.IntMap PerThread | ||
33 | -- , uniqSource :: Int | ||
34 | } | ||
35 | |||
36 | globals :: MVar GlobalState | ||
37 | globals = unsafePerformIO $ newMVar $ GlobalState | ||
38 | { threads = Map.empty | ||
39 | -- , uniqSource = 0 | ||
40 | } | ||
41 | {-# NOINLINE globals #-} | ||
42 | |||
43 | |||
44 | forkIO :: IO () -> IO ThreadId | ||
45 | forkIO = fork | ||
46 | |||
47 | fork :: MonadBaseControl IO m => m () -> m ThreadId | ||
48 | fork action = do | ||
49 | t <- Raw.fork $ do | ||
50 | -- wkid <- myThreadId >>= liftBase . mkWeakThreadId | ||
51 | -- tid <- newUniq | ||
52 | tid <- myThreadId | ||
53 | tm <- liftBase getCurrentTime | ||
54 | bracket_ (modifyThreads $ Map.insert tid (PerThread "" tm)) | ||
55 | (modifyThreads $ Map.delete tid) | ||
56 | action | ||
57 | return t | ||
58 | |||
59 | labelThread :: ThreadId -> String -> IO () | ||
60 | labelThread tid s = do | ||
61 | GHC.labelThread tid s | ||
62 | putStrLn $ "labelThread "++s++" "++show tid | ||
63 | modifyThreads $ Map.adjust (\pt -> pt { lbl = s }) tid | ||
64 | |||
65 | threadsInformation :: IO [PerThread] | ||
66 | threadsInformation = do | ||
67 | m <- threads <$> readMVar globals | ||
68 | return $ Map.elems m | ||
69 | |||
70 | -- newUniq :: MonadBaseControl IO m => m Int | ||
71 | -- newUniq = do | ||
72 | -- modifyMVar globals (\st -> return (st { uniqSource = succ (uniqSource st) }, uniqSource st)) | ||
73 | |||
74 | modifyThreads :: MonadBase IO m => (Map.Map ThreadId PerThread -> Map.Map ThreadId PerThread) -> m () | ||
75 | modifyThreads f = do | ||
76 | g <- takeMVar globals | ||
77 | let f' st = st { threads = f (threads st) } | ||
78 | putMVar globals (f' g) | ||