From 8054d24c65260e8ab0c0a092a12420aaffc9c8c2 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Mon, 6 Mar 2017 05:58:53 +0900 Subject: [PATCH 01/17] Add GHC.RTS.Events.Incremental --- ghc-events.cabal | 1 + src/GHC/RTS/Events/Incremental.hs | 130 ++++++++++++++++++++++++++++++ src/GHC/RTS/EventsIncremental.hs | 4 +- 3 files changed, 134 insertions(+), 1 deletion(-) create mode 100644 src/GHC/RTS/Events/Incremental.hs diff --git a/ghc-events.cabal b/ghc-events.cabal index a2f3a91..4df4740 100644 --- a/ghc-events.cabal +++ b/ghc-events.cabal @@ -53,6 +53,7 @@ library array >= 0.2 && < 0.6 exposed-modules: GHC.RTS.Events, GHC.RTS.EventsIncremental + GHC.RTS.Events.Incremental GHC.RTS.Events.Merge GHC.RTS.Events.Analysis GHC.RTS.Events.Analysis.Capability diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs new file mode 100644 index 0000000..1c30823 --- /dev/null +++ b/src/GHC/RTS/Events/Incremental.hs @@ -0,0 +1,130 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE OverloadedStrings #-} +module GHC.RTS.Events.Incremental + ( -- * Incremental API + Decoder(..) + , decodeHeader + , decodeEvents + , decodeEventLog + + -- * Lazy API + , readHeader + , readEvents + , readEventLog + + -- * Legacy API + , readEventLogFromFile + ) where +import Control.Applicative +import Control.Monad +import Data.Either +import Data.Maybe +import Data.Monoid +import Data.Word +import Prelude + +import qualified Data.Binary.Get as G +import qualified Data.ByteString as B +import qualified Data.ByteString.Lazy as BL +import qualified Data.ByteString.Lazy.Internal as BL + +import GHC.RTS.Events +import GHC.RTS.EventsIncremental (mkEventDecoder) + +data Decoder a + = Consume (B.ByteString -> Decoder a) + | Produce !a (Decoder a) + | Done B.ByteString + | Error B.ByteString String + +pushChunk :: Decoder a -> B.ByteString -> Decoder a +pushChunk decoder chunk = case decoder of + Consume k -> k chunk + Produce a decoder' -> Produce a $ decoder' `pushChunk` chunk + Done leftover -> Done $ leftover `B.append` chunk + Error leftover err -> Error (leftover `B.append` chunk) err + +withHeader :: (Header -> B.ByteString -> Decoder r) -> Decoder r +withHeader f = go $ G.runGetIncremental getHeader + where + go decoder = case decoder of + G.Done leftover _ header -> f header leftover + G.Partial k -> Consume $ \chunk -> go $ k $ Just chunk + G.Fail leftover _ err -> Error leftover err + +decodeHeader :: Decoder Header +decodeHeader = withHeader $ \header leftover -> Produce header $ Done leftover + +decodeEvents :: Header -> Decoder Event +decodeEvents header = go (0 :: Int) Nothing decoder0 + where + decoder0 = mkEventDecoder header + go !remaining !blockCap decoder = case decoder of + G.Done leftover consumed r -> do + let !decoder' = decoder0 `G.pushChunk` leftover + case r of + Just event -> case evSpec event of + EventBlock {..} -> + go (fromIntegral block_size) (mkCap cap) decoder' + _ -> do + let + !remaining' = remaining - fromIntegral consumed + !blockCap' = if remaining' > 0 then blockCap else Nothing + !event' = event { evCap = blockCap } + Produce event' $ go remaining' blockCap' decoder' + Nothing -> go remaining blockCap decoder' + G.Partial k -> + Consume $ \chunk -> go remaining blockCap $ k $ Just chunk + G.Fail leftover _ err -> + Error leftover err + mkCap cap = do + guard $ fromIntegral cap /= (-1 :: Word16) + return cap + +decodeEventLog :: Decoder Event +decodeEventLog = withHeader $ \header leftover -> + decodeEvents header `pushChunk` leftover + +readHeader :: BL.ByteString -> Either String (Header, BL.ByteString) +readHeader = go $ Left decodeHeader + where + go r bytes = case r of + Left decoder -> case decoder of + Produce header decoder' -> case decoder' of + Done leftover -> Right (header, BL.Chunk leftover bytes) + _ -> fail "readHeader: unexpected decoder" + Consume k -> case bytes of + BL.Empty -> fail "readHeader: not enough bytes" + BL.Chunk chunk chunks -> go (Left $! k chunk) chunks + Done _ -> fail "readHeader: unexpected termination" + Error _ err -> fail err + Right header -> Right (header, bytes) + +readEvents :: Header -> BL.ByteString -> ([Event], Maybe String) +readEvents header = f . go (decodeEvents header) + where + f :: [Either e a] -> ([a], Maybe e) + f xs = (rights rs, listToMaybe (lefts ls)) + where + (rs, ls) = break isLeft xs +#if !MIN_VERSION_base(4, 7, 0) + isLeft (Left _) = True + isLeft _ = False +#endif + go :: Decoder Event -> BL.ByteString -> [Either String Event] + go decoder bytes = case decoder of + Produce event decoder' -> Right event : go decoder' bytes + Consume k -> case bytes of + BL.Empty -> [] + BL.Chunk chunk chunks -> go (k chunk) chunks + Done {} -> [] + Error _ err -> [Left err] + +readEventLog :: BL.ByteString -> Either String (EventLog, Maybe String) +readEventLog bytes = do + (header, bytes') <- readHeader bytes + case readEvents header bytes' of + (events, err) -> return (EventLog header (Data events), err) + +readEventLogFromFile :: FilePath -> IO (Either String EventLog) +readEventLogFromFile path = fmap fst . readEventLog <$> BL.readFile path diff --git a/src/GHC/RTS/EventsIncremental.hs b/src/GHC/RTS/EventsIncremental.hs index 96d2b78..a5d3807 100644 --- a/src/GHC/RTS/EventsIncremental.hs +++ b/src/GHC/RTS/EventsIncremental.hs @@ -30,7 +30,9 @@ module GHC.RTS.EventsIncremental ( -- * Helper functions serialiseEventLog, readRemainingEvents, - printEventsIncremental + printEventsIncremental, + + mkEventDecoder ) where import GHC.RTS.Events From b9962e5d805567869f9c1c552d592937fed08160 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Tue, 7 Mar 2017 08:43:52 +0900 Subject: [PATCH 02/17] Move mkEventDecoder from EventsIncremental --- src/GHC/RTS/Events/Incremental.hs | 79 ++++++++++++++++++++++++++++++- 1 file changed, 77 insertions(+), 2 deletions(-) diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs index 1c30823..49b0239 100644 --- a/src/GHC/RTS/Events/Incremental.hs +++ b/src/GHC/RTS/Events/Incremental.hs @@ -12,8 +12,10 @@ module GHC.RTS.Events.Incremental , readEvents , readEventLog - -- * Legacy API + -- * IO interface , readEventLogFromFile + , printEventsIncremental + , hPrintEventsIncremental ) where import Control.Applicative import Control.Monad @@ -21,15 +23,22 @@ import Data.Either import Data.Maybe import Data.Monoid import Data.Word +import System.IO import Prelude import qualified Data.Binary.Get as G import qualified Data.ByteString as B +import qualified Data.ByteString.Builder as BB import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy.Internal as BL +import qualified Data.IntMap.Strict as IM +import GHC.RTS.EventParserUtils +import GHC.RTS.EventTypes import GHC.RTS.Events -import GHC.RTS.EventsIncremental (mkEventDecoder) + +#define EVENTLOG_CONSTANTS_ONLY +#include "EventLogFormat.h" data Decoder a = Consume (B.ByteString -> Decoder a) @@ -128,3 +137,69 @@ readEventLog bytes = do readEventLogFromFile :: FilePath -> IO (Either String EventLog) readEventLogFromFile path = fmap fst . readEventLog <$> BL.readFile path + +printEventsIncremental :: FilePath -> IO () +printEventsIncremental path = withFile path ReadMode hPrintEventsIncremental + +hPrintEventsIncremental :: Handle -> IO () +hPrintEventsIncremental hdl = go decodeEventLog + where + go decoder = case decoder of + Produce event decoder' -> do + BB.hPutBuilder stdout $ buildEvent event <> "\n" + go decoder' + Consume k -> do + chunk <- B.hGetSome hdl 4096 + unless (B.null chunk) $ go $ k chunk + Done {} -> return () + Error _ err -> fail err + +-- | Makes a decoder with all the required parsers when given a Header +mkEventDecoder :: Header -> G.Decoder (Maybe Event) +mkEventDecoder header = G.runGetIncremental $ getEvent parsers + where + imap = IM.fromList [(fromIntegral (num t), t) | t <- eventTypes header] + -- This test is complete, no-one has extended this event yet and all future + -- extensions will use newly allocated event IDs. + is_ghc_6 = Just sz_old_tid == do + create_et <- IM.lookup EVENT_CREATE_THREAD imap + size create_et + -- GHC6 writes an invalid header, we handle it here by using a + -- different set of event parsers. Note that the ghc7 event parsers + -- are standard events, and can be used by other runtime systems that + -- make use of threadscope. + + -- GHC-7.8.2 uses a different thread block status encoding, + -- and therefore requires a different parser for the stop + -- event. Later, in GHC-7.8.3, the old encoding was restored. + -- GHC-7.8.2 can be recognised by presence and absence of + -- events in the header: + -- * User markers were added in GHC-7.8 + -- * an empty event HACK_BUG_T9003 was added in GHC-7.8.3 + -- This fix breaks software which uses ghc-events and combines + -- user markers with the older stop status encoding. We don't + -- know of any such software, though. + is_pre77 = IM.notMember EVENT_USER_MARKER imap + is_ghc782 = IM.member EVENT_USER_MARKER imap + && IM.notMember EVENT_HACK_BUG_T9003 imap + + stopParsers + | is_pre77 = pre77StopParsers + | is_ghc782 = [ghc782StopParser] + | otherwise = [post782StopParser] + + event_parsers + | is_ghc_6 = concat + [ standardParsers + , ghc6Parsers + , parRTSParsers sz_old_tid + ] + | otherwise = concat + [ standardParsers + , ghc7Parsers + , stopParsers + , parRTSParsers sz_tid + , mercuryParsers + , perfParsers + ] + parsers = EventParsers $ mkEventTypeParsers imap event_parsers From 4186e095f44af088b72a8d31a2e1b08b34322ad0 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Tue, 7 Mar 2017 08:59:27 +0900 Subject: [PATCH 03/17] ghc-events: Switch to the new incremental API --- GhcEvents.hs | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/GhcEvents.hs b/GhcEvents.hs index 0ae1b3a..6102f61 100644 --- a/GhcEvents.hs +++ b/GhcEvents.hs @@ -4,6 +4,7 @@ module Main where import GHC.RTS.Events import GHC.RTS.EventsIncremental +import qualified GHC.RTS.Events.Incremental as Inc import GHC.RTS.Events.Merge import GHC.RTS.Events.Analysis import GHC.RTS.Events.Analysis.SparkThread @@ -22,10 +23,7 @@ main = getArgs >>= command command :: [String] -> IO () command ["--help"] = putStr usage -command ["inc", file] = do - h <- openBinaryFile file ReadMode - eh <- ehOpen h 4096 - printEventsIncremental eh False +command ["inc", file] = Inc.printEventsIncremental file command ["inc", "force", file] = do h <- openBinaryFile file ReadMode @@ -181,7 +179,7 @@ command _ = putStr usage >> die "Unrecognized command" readLogOrDie :: FilePath -> IO EventLog readLogOrDie file = do - e <- readEventLogFromFile file + e <- Inc.readEventLogFromFile file case e of Left s -> die ("Failed to parse " ++ file ++ ": " ++ s) Right evtLog -> return evtLog From 7e16284d979e0789578421e646cfdb7078f45130 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Tue, 7 Mar 2017 14:12:11 +0900 Subject: [PATCH 04/17] test: Switch to the new incremental API --- test/TestVersions.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/test/TestVersions.hs b/test/TestVersions.hs index bc50d64..8a99cac 100644 --- a/test/TestVersions.hs +++ b/test/TestVersions.hs @@ -17,7 +17,7 @@ Where queens.hs is http://darcs.haskell.org/nofib/parallel/queens/Main.hs import System.Exit (exitFailure) import GHC.RTS.Events -import GHC.RTS.EventsIncremental +import GHC.RTS.Events.Incremental import Utils (files, diffLines) @@ -40,4 +40,3 @@ main = do if and successes then return () else exitFailure - From b402895ad1d45292ea7d887a358d7e8c0cfb0c90 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Tue, 7 Mar 2017 15:23:17 +0900 Subject: [PATCH 05/17] Strictify status to prevent space leak --- src/GHC/RTS/EventTypes.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/GHC/RTS/EventTypes.hs b/src/GHC/RTS/EventTypes.hs index 3c88cfa..ac59ef8 100644 --- a/src/GHC/RTS/EventTypes.hs +++ b/src/GHC/RTS/EventTypes.hs @@ -158,7 +158,7 @@ data EventInfo | RunThread { thread :: {-# UNPACK #-}!ThreadId } | StopThread { thread :: {-# UNPACK #-}!ThreadId, - status :: ThreadStopStatus + status :: !ThreadStopStatus } | ThreadRunnable { thread :: {-# UNPACK #-}!ThreadId } From 6bddb6f1266682a42aa44725a38a453ec2781b60 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Tue, 7 Mar 2017 16:08:31 +0900 Subject: [PATCH 06/17] Use bytestring builder for ppEventLog --- src/GHC/RTS/Events.hs | 61 +- src/GHC/RTS/Events/Incremental.hs | 2 +- src/GHC/RTS/EventsIncremental.hs | 2 +- test/782stop.eventlog.reference | 187 +- test/783stop.eventlog.reference | 189 +- ...ndelbrot-mmc-2011-06-14.eventlog.reference | 4413 ++++++++--------- test/parallelTest.eventlog.reference | 131 +- test/pre77stop.eventlog.reference | 177 +- test/queens-ghc-6.12.1.eventlog.reference | 1011 ++-- test/queens-ghc-7.0.2.eventlog.reference | 1879 ++++--- 10 files changed, 4025 insertions(+), 4027 deletions(-) diff --git a/src/GHC/RTS/Events.hs b/src/GHC/RTS/Events.hs index 964008f..1d43e2b 100644 --- a/src/GHC/RTS/Events.hs +++ b/src/GHC/RTS/Events.hs @@ -51,7 +51,7 @@ module GHC.RTS.Events ( showEventInfo, buildEventInfo, showThreadStopStatus, ppEventLog, ppEventType, - ppEvent, ppEvent', buildEvent, + ppEvent, buildEvent, buildEvent', -- * Perf events nEVENT_PERF_NAME, nEVENT_PERF_COUNTER, nEVENT_PERF_TRACEPOINT, @@ -73,6 +73,7 @@ import qualified Data.ByteString.Lazy.Char8 as BL8 import Control.Monad (when, replicateM) import Data.IntMap (IntMap) import qualified Data.IntMap as M +import Data.Foldable (foldMap) import Data.Function hiding (id) import Data.List import Data.Maybe (fromMaybe, fromJust) @@ -1045,48 +1046,52 @@ showThreadStopStatus (BlockedOnBlackHoleOwnedBy target) = showThreadStopStatus NoStatus = "No stop thread status" ppEventLog :: EventLog -> String -ppEventLog (EventLog (Header ets) (Data es)) = unlines $ concat - [ ["Event Types:"] - , map ppEventType ets - , [""] -- newline - , ["Events:"] - , map (ppEvent imap) sorted - , [""] ] -- extra trailing newline - where +ppEventLog = BL8.unpack . BB.toLazyByteString . buildEventLog + +buildEventLog :: EventLog -> BB.Builder +buildEventLog (EventLog (Header ets) (Data es)) = + "Event Types:\n" + <> foldMap (\evType -> buildEventType evType <> "\n") ets + <> "\n" + <> "Events:\n" + <> foldMap (\ev -> buildEvent imap ev <> "\n") sorted + where imap = buildEventTypeMap ets sorted = sortEvents es ppEventType :: EventType -> String -ppEventType (EventType num dsc msz) = printf "%4d: %s (size %s)" num dsc - (case msz of Nothing -> "variable"; Just x -> show x) +ppEventType = BL8.unpack . BB.toLazyByteString . buildEventType + +buildEventType :: EventType -> BB.Builder +buildEventType (EventType num dsc msz) = + BB.word16Dec num <> ": " + <> BB.stringUtf8 dsc <> " (size " + <> maybe "variable" BB.word16Dec msz <> ")" -- | Pretty prints an 'Event', with clean handling for 'UnknownEvent' ppEvent :: IntMap EventType -> Event -> String -ppEvent imap (Event {evTime = time, evSpec = spec, evCap = cap}) = - printf "%9d: " time ++ - (case cap of - Nothing -> "" - Just c -> printf "cap %d: " c) ++ - case spec of - UnknownEvent{ ref=ref } -> - printf (desc (fromJust (M.lookup (fromIntegral ref) imap))) - _ -> showEventInfo spec - --- | Pretty prints an 'Event'. Cannot identify 'UnknownEvent's but has a --- simple type signature -ppEvent' :: Event -> String -ppEvent' = BL8.unpack . BB.toLazyByteString . buildEvent +ppEvent imap = BL8.unpack . BB.toLazyByteString . buildEvent imap -buildEvent :: Event -> BB.Builder -buildEvent (Event time spec evCap) = +buildEvent :: IntMap EventType -> Event -> BB.Builder +buildEvent imap (Event time spec evCap) = BB.word64Dec time <> ": " <> maybe "" (\c -> "cap " <> BB.intDec c <> ": ") evCap <> case spec of UnknownEvent{ ref=ref } -> - "Unknown Event (ref: " <> BB.word16Dec ref <> ")" + maybe "" (BB.stringUtf8 . desc) $ M.lookup (fromIntegral ref) imap _ -> buildEventInfo spec +buildEvent' :: Event -> BB.Builder +buildEvent' (Event time spec evCap) = + BB.word64Dec time + <> ": " + <> maybe "" (\c -> "cap " <> BB.intDec c <> ": ") evCap + <> case spec of + UnknownEvent{ ref=ref } -> + "Unknown Event (ref: " <> BB.word16Dec ref <> ")" + _ -> buildEventInfo spec + type PutEvents a = PutM a putE :: Binary a => a -> PutEvents () diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs index 49b0239..f8b1051 100644 --- a/src/GHC/RTS/Events/Incremental.hs +++ b/src/GHC/RTS/Events/Incremental.hs @@ -146,7 +146,7 @@ hPrintEventsIncremental hdl = go decodeEventLog where go decoder = case decoder of Produce event decoder' -> do - BB.hPutBuilder stdout $ buildEvent event <> "\n" + BB.hPutBuilder stdout $ buildEvent' event <> "\n" go decoder' Consume k -> do chunk <- B.hGetSome hdl 4096 diff --git a/src/GHC/RTS/EventsIncremental.hs b/src/GHC/RTS/EventsIncremental.hs index a5d3807..7db07d0 100644 --- a/src/GHC/RTS/EventsIncremental.hs +++ b/src/GHC/RTS/EventsIncremental.hs @@ -376,7 +376,7 @@ printEventsIncremental eh dashf = do event <- ehReadEvent eh case event of Item ev -> do - BB.hPutBuilder stdout (buildEvent ev <> "\n") -- if actual printing is needed + BB.hPutBuilder stdout (buildEvent' ev <> "\n") -- if actual printing is needed printEventsIncremental eh dashf Incomplete -> if dashf diff --git a/test/782stop.eventlog.reference b/test/782stop.eventlog.reference index 6e9ae69..b7c5ac5 100644 --- a/test/782stop.eventlog.reference +++ b/test/782stop.eventlog.reference @@ -1,99 +1,99 @@ Event Types: - 0: Create thread (size 4) - 1: Run thread (size 4) - 2: Stop thread (size 10) - 3: Thread runnable (size 4) - 4: Migrate thread (size 6) - 8: Wakeup thread (size 6) - 9: Starting GC (size 0) - 10: Finished GC (size 0) - 11: Request sequential GC (size 0) - 12: Request parallel GC (size 0) - 15: Create spark thread (size 4) - 16: Log message (size variable) - 17: Create capabilities (size 2) - 18: Block marker (size 14) - 19: User message (size variable) - 20: GC idle (size 0) - 21: GC working (size 0) - 22: GC done (size 0) - 23: Version (size variable) - 24: Program invocation (size variable) - 25: Create capability set (size 6) - 26: Delete capability set (size 4) - 27: Add capability to capability set (size 6) - 28: Remove capability from capability set (size 6) - 29: RTS name and version (size variable) - 30: Program arguments (size variable) - 31: Program environment variables (size variable) - 32: Process ID (size 8) - 33: Parent process ID (size 8) - 34: Spark counters (size 56) - 35: Spark create (size 0) - 36: Spark dud (size 0) - 37: Spark overflow (size 0) - 38: Spark run (size 0) - 39: Spark steal (size 2) - 40: Spark fizzle (size 0) - 41: Spark GC (size 0) - 43: Wall clock time (size 16) - 44: Thread label (size variable) - 45: Create capability (size 2) - 46: Delete capability (size 2) - 47: Disable capability (size 2) - 48: Enable capability (size 2) - 49: Total heap mem ever allocated (size 12) - 50: Current heap size (size 12) - 51: Current heap live data (size 12) - 52: Heap static parameters (size 38) - 53: GC statistics (size 50) - 54: Synchronise stop-the-world GC (size 0) - 55: Task create (size 18) - 56: Task migrate (size 12) - 57: Task delete (size 8) - 58: User marker (size variable) - 60: Starting message receival (size 0) - 61: Finished message receival (size 0) - 62: Creating Process (size 4) - 63: Killing Process (size 4) - 64: Assigning thread to process (size 8) - 65: Creating machine (size 10) - 66: Killing machine (size 2) - 67: Sending message (size 19) - 68: Receiving message (size 23) - 69: Sending/Receiving local message (size 17) +0: Create thread (size 4) +1: Run thread (size 4) +2: Stop thread (size 10) +3: Thread runnable (size 4) +4: Migrate thread (size 6) +8: Wakeup thread (size 6) +9: Starting GC (size 0) +10: Finished GC (size 0) +11: Request sequential GC (size 0) +12: Request parallel GC (size 0) +15: Create spark thread (size 4) +16: Log message (size variable) +17: Create capabilities (size 2) +18: Block marker (size 14) +19: User message (size variable) +20: GC idle (size 0) +21: GC working (size 0) +22: GC done (size 0) +23: Version (size variable) +24: Program invocation (size variable) +25: Create capability set (size 6) +26: Delete capability set (size 4) +27: Add capability to capability set (size 6) +28: Remove capability from capability set (size 6) +29: RTS name and version (size variable) +30: Program arguments (size variable) +31: Program environment variables (size variable) +32: Process ID (size 8) +33: Parent process ID (size 8) +34: Spark counters (size 56) +35: Spark create (size 0) +36: Spark dud (size 0) +37: Spark overflow (size 0) +38: Spark run (size 0) +39: Spark steal (size 2) +40: Spark fizzle (size 0) +41: Spark GC (size 0) +43: Wall clock time (size 16) +44: Thread label (size variable) +45: Create capability (size 2) +46: Delete capability (size 2) +47: Disable capability (size 2) +48: Enable capability (size 2) +49: Total heap mem ever allocated (size 12) +50: Current heap size (size 12) +51: Current heap live data (size 12) +52: Heap static parameters (size 38) +53: GC statistics (size 50) +54: Synchronise stop-the-world GC (size 0) +55: Task create (size 18) +56: Task migrate (size 12) +57: Task delete (size 8) +58: User marker (size variable) +60: Starting message receival (size 0) +61: Finished message receival (size 0) +62: Creating Process (size 4) +63: Killing Process (size 4) +64: Assigning thread to process (size 8) +65: Creating machine (size 10) +66: Killing machine (size 2) +67: Sending message (size 19) +68: Receiving message (size 23) +69: Sending/Receiving local message (size 17) Events: - 431075: startup: 1 capabilities - 438021: created capset 0 of type CapsetOsProcess - 438382: created capset 1 of type CapsetClockDomain - 439886: created cap 0 - 440061: assigned cap 0 to capset 0 - 440191: assigned cap 0 to capset 1 - 446866: capset 1: wall clock time 1405192655s 464811000ns (unix epoch) - 447318: capset 0: pid 19951 - 449452: capset 0: parent pid 18797 - 453913: capset 0: RTS version "GHC-7.8.20140411 rts_l" - 462067: capset 0: args: ["./wrong782","+RTS","-lsu-g-p","-K80m","-k10m","-H200m","-C1s"] - 468191: capset 0: env: ["SSH_AGENT_PID=1817","PVM_RSH=/usr/bin/ssh","GPG_AGENT_INFO=/tmp/keyring-yTUMmt/gpg:0:1","TERM=xterm","SHELL=/bin/bash","XDG_SESSION_COOKIE=acf1c79e0e2de67643be755c00000003-1405160974.283591-1531347675","WINDOWID=58743399","OLDPWD=/opt/Eden/edentv/fixFor783/BLD-ghc-events-parallel","GNOME_KEYRING_CONTROL=/tmp/keyring-yTUMmt","USER=jost","LS_COLORS=rs=0:di=01;34:ln=01;36:mh=00:pi=40;33:so=01;35:do=01;35:bd=40;33;01:cd=40;33;01:or=40;31;01:su=37;41:sg=30;43:ca=30;41:tw=30;42:ow=34;42:st=37;44:ex=01;32:*.tar=01;31:*.tgz=01;31:*.arj=01;31:*.taz=01;31:*.lzh=01;31:*.lzma=01;31:*.tlz=01;31:*.txz=01;31:*.zip=01;31:*.z=01;31:*.Z=01;31:*.dz=01;31:*.gz=01;31:*.lz=01;31:*.xz=01;31:*.bz2=01;31:*.bz=01;31:*.tbz=01;31:*.tbz2=01;31:*.tz=01;31:*.deb=01;31:*.rpm=01;31:*.jar=01;31:*.war=01;31:*.ear=01;31:*.sar=01;31:*.rar=01;31:*.ace=01;31:*.zoo=01;31:*.cpio=01;31:*.7z=01;31:*.rz=01;31:*.jpg=01;35:*.jpeg=01;35:*.gif=01;35:*.bmp=01;35:*.pbm=01;35:*.pgm=01;35:*.ppm=01;35:*.tga=01;35:*.xbm=01;35:*.xpm=01;35:*.tif=01;35:*.tiff=01;35:*.png=01;35:*.svg=01;35:*.svgz=01;35:*.mng=01;35:*.pcx=01;35:*.mov=01;35:*.mpg=01;35:*.mpeg=01;35:*.m2v=01;35:*.mkv=01;35:*.webm=01;35:*.ogm=01;35:*.mp4=01;35:*.m4v=01;35:*.mp4v=01;35:*.vob=01;35:*.qt=01;35:*.nuv=01;35:*.wmv=01;35:*.asf=01;35:*.rm=01;35:*.rmvb=01;35:*.flc=01;35:*.avi=01;35:*.fli=01;35:*.flv=01;35:*.gl=01;35:*.dl=01;35:*.xcf=01;35:*.xwd=01;35:*.yuv=01;35:*.cgm=01;35:*.emf=01;35:*.axv=01;35:*.anx=01;35:*.ogv=01;35:*.ogx=01;35:*.aac=00;36:*.au=00;36:*.flac=00;36:*.mid=00;36:*.midi=00;36:*.mka=00;36:*.mp3=00;36:*.mpc=00;36:*.ogg=00;36:*.ra=00;36:*.wav=00;36:*.axa=00;36:*.oga=00;36:*.spx=00;36:*.xspf=00;36:","XDG_SESSION_PATH=/org/freedesktop/DisplayManager/Session0","XDG_SEAT_PATH=/org/freedesktop/DisplayManager/Seat0","PVM_ROOT=/usr/lib/pvm3","SSH_AUTH_SOCK=/tmp/keyring-yTUMmt/ssh","SESSION_MANAGER=local/onAir:@/tmp/.ICE-unix/1781,unix/onAir:/tmp/.ICE-unix/1781","DEFAULTS_PATH=/usr/share/gconf/gnome-fallback.default.path","PVM_ARCH=LINUX64","XDG_CONFIG_DIRS=/etc/xdg/xdg-gnome-fallback:/etc/xdg","PATH=/home/jost/bin:/home/jost/bin:/usr/lib/lightdm/lightdm:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/home/jost/.cabal/bin","DESKTOP_SESSION=gnome-fallback","PWD=/opt/Eden/edentv/fixFor783","GNOME_KEYRING_PID=1770","LANG=en_US.UTF-8","MANDATORY_PATH=/usr/share/gconf/gnome-fallback.mandatory.path","UBUNTU_MENUPROXY=libappmenu.so","GDMSESSION=gnome-fallback","SHLVL=1","HOME=/home/jost","LANGUAGE=en_US:en","GNOME_DESKTOP_SESSION_ID=this-is-deprecated","LOGNAME=jost","PVM_EXPORT=DISPLAY","XDG_DATA_DIRS=/usr/share/gnome-fallback:/usr/share/gnome:/usr/local/share/:/usr/share/","DBUS_SESSION_BUS_ADDRESS=unix:abstract=/tmp/dbus-Mviy2n6D5M,guid=3677210ad991dc7e0dc3a1ae00000012","LESSOPEN=| /usr/bin/lesspipe %s","DISPLAY=:0.0","XDG_CURRENT_DESKTOP=GNOME","LESSCLOSE=/usr/bin/lesspipe %s %s","COLORTERM=gnome-terminal","XAUTHORITY=/home/jost/.Xauthority","_=./wrong782"] - 671062: task 0x10130c0 created on cap 0 with OS kernel thread 19951 - 699893: cap 0: creating thread 1 - 706834: cap 0: running thread 1 - 761740: cap 0: stopping thread 1 (heap overflow) - 4742525: cap 0: running thread 1 - 4987428: cap 0: stopping thread 1 (making a foreign call) - 4989828: cap 0: running thread 1 - 5098303: cap 0: forking child thread - 5129059: cap 0: creating thread 2 - 5130773: cap 0: stopping thread 1 (thread yielding) - 5132416: cap 0: running thread 2 - 5139072: cap 0: stopping thread 2 (heap overflow) - 5786180: cap 0: running thread 2 - 5798149: cap 0: child - 10666308: cap 0: stopping thread 2 (thread yielding) - 10667787: cap 0: running thread 1 - 10678973: cap 0: stopping thread 1 (blocked on black hole owned by thread 2) - 10679120: cap 0: running thread 2 +431075: startup: 1 capabilities +438021: created capset 0 of type CapsetOsProcess +438382: created capset 1 of type CapsetClockDomain +439886: created cap 0 +440061: assigned cap 0 to capset 0 +440191: assigned cap 0 to capset 1 +446866: capset 1: wall clock time 1405192655s 464811000ns (unix epoch) +447318: capset 0: pid 19951 +449452: capset 0: parent pid 18797 +453913: capset 0: RTS version "GHC-7.8.20140411 rts_l" +462067: capset 0: args: ["./wrong782","+RTS","-lsu-g-p","-K80m","-k10m","-H200m","-C1s"] +468191: capset 0: env: ["SSH_AGENT_PID=1817","PVM_RSH=/usr/bin/ssh","GPG_AGENT_INFO=/tmp/keyring-yTUMmt/gpg:0:1","TERM=xterm","SHELL=/bin/bash","XDG_SESSION_COOKIE=acf1c79e0e2de67643be755c00000003-1405160974.283591-1531347675","WINDOWID=58743399","OLDPWD=/opt/Eden/edentv/fixFor783/BLD-ghc-events-parallel","GNOME_KEYRING_CONTROL=/tmp/keyring-yTUMmt","USER=jost","LS_COLORS=rs=0:di=01;34:ln=01;36:mh=00:pi=40;33:so=01;35:do=01;35:bd=40;33;01:cd=40;33;01:or=40;31;01:su=37;41:sg=30;43:ca=30;41:tw=30;42:ow=34;42:st=37;44:ex=01;32:*.tar=01;31:*.tgz=01;31:*.arj=01;31:*.taz=01;31:*.lzh=01;31:*.lzma=01;31:*.tlz=01;31:*.txz=01;31:*.zip=01;31:*.z=01;31:*.Z=01;31:*.dz=01;31:*.gz=01;31:*.lz=01;31:*.xz=01;31:*.bz2=01;31:*.bz=01;31:*.tbz=01;31:*.tbz2=01;31:*.tz=01;31:*.deb=01;31:*.rpm=01;31:*.jar=01;31:*.war=01;31:*.ear=01;31:*.sar=01;31:*.rar=01;31:*.ace=01;31:*.zoo=01;31:*.cpio=01;31:*.7z=01;31:*.rz=01;31:*.jpg=01;35:*.jpeg=01;35:*.gif=01;35:*.bmp=01;35:*.pbm=01;35:*.pgm=01;35:*.ppm=01;35:*.tga=01;35:*.xbm=01;35:*.xpm=01;35:*.tif=01;35:*.tiff=01;35:*.png=01;35:*.svg=01;35:*.svgz=01;35:*.mng=01;35:*.pcx=01;35:*.mov=01;35:*.mpg=01;35:*.mpeg=01;35:*.m2v=01;35:*.mkv=01;35:*.webm=01;35:*.ogm=01;35:*.mp4=01;35:*.m4v=01;35:*.mp4v=01;35:*.vob=01;35:*.qt=01;35:*.nuv=01;35:*.wmv=01;35:*.asf=01;35:*.rm=01;35:*.rmvb=01;35:*.flc=01;35:*.avi=01;35:*.fli=01;35:*.flv=01;35:*.gl=01;35:*.dl=01;35:*.xcf=01;35:*.xwd=01;35:*.yuv=01;35:*.cgm=01;35:*.emf=01;35:*.axv=01;35:*.anx=01;35:*.ogv=01;35:*.ogx=01;35:*.aac=00;36:*.au=00;36:*.flac=00;36:*.mid=00;36:*.midi=00;36:*.mka=00;36:*.mp3=00;36:*.mpc=00;36:*.ogg=00;36:*.ra=00;36:*.wav=00;36:*.axa=00;36:*.oga=00;36:*.spx=00;36:*.xspf=00;36:","XDG_SESSION_PATH=/org/freedesktop/DisplayManager/Session0","XDG_SEAT_PATH=/org/freedesktop/DisplayManager/Seat0","PVM_ROOT=/usr/lib/pvm3","SSH_AUTH_SOCK=/tmp/keyring-yTUMmt/ssh","SESSION_MANAGER=local/onAir:@/tmp/.ICE-unix/1781,unix/onAir:/tmp/.ICE-unix/1781","DEFAULTS_PATH=/usr/share/gconf/gnome-fallback.default.path","PVM_ARCH=LINUX64","XDG_CONFIG_DIRS=/etc/xdg/xdg-gnome-fallback:/etc/xdg","PATH=/home/jost/bin:/home/jost/bin:/usr/lib/lightdm/lightdm:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/home/jost/.cabal/bin","DESKTOP_SESSION=gnome-fallback","PWD=/opt/Eden/edentv/fixFor783","GNOME_KEYRING_PID=1770","LANG=en_US.UTF-8","MANDATORY_PATH=/usr/share/gconf/gnome-fallback.mandatory.path","UBUNTU_MENUPROXY=libappmenu.so","GDMSESSION=gnome-fallback","SHLVL=1","HOME=/home/jost","LANGUAGE=en_US:en","GNOME_DESKTOP_SESSION_ID=this-is-deprecated","LOGNAME=jost","PVM_EXPORT=DISPLAY","XDG_DATA_DIRS=/usr/share/gnome-fallback:/usr/share/gnome:/usr/local/share/:/usr/share/","DBUS_SESSION_BUS_ADDRESS=unix:abstract=/tmp/dbus-Mviy2n6D5M,guid=3677210ad991dc7e0dc3a1ae00000012","LESSOPEN=| /usr/bin/lesspipe %s","DISPLAY=:0.0","XDG_CURRENT_DESKTOP=GNOME","LESSCLOSE=/usr/bin/lesspipe %s %s","COLORTERM=gnome-terminal","XAUTHORITY=/home/jost/.Xauthority","_=./wrong782"] +671062: task 0x10130c0 created on cap 0 with OS kernel thread 19951 +699893: cap 0: creating thread 1 +706834: cap 0: running thread 1 +761740: cap 0: stopping thread 1 (heap overflow) +4742525: cap 0: running thread 1 +4987428: cap 0: stopping thread 1 (making a foreign call) +4989828: cap 0: running thread 1 +5098303: cap 0: forking child thread +5129059: cap 0: creating thread 2 +5130773: cap 0: stopping thread 1 (thread yielding) +5132416: cap 0: running thread 2 +5139072: cap 0: stopping thread 2 (heap overflow) +5786180: cap 0: running thread 2 +5798149: cap 0: child +10666308: cap 0: stopping thread 2 (thread yielding) +10667787: cap 0: running thread 1 +10678973: cap 0: stopping thread 1 (blocked on black hole owned by thread 2) +10679120: cap 0: running thread 2 193941318: cap 0: stopping thread 2 (heap overflow) 194546751: cap 0: running thread 2 331983948: cap 0: stopping thread 2 (heap overflow) @@ -145,4 +145,3 @@ Events: 839458945: deleted capset 0 839458993: deleted capset 1 - diff --git a/test/783stop.eventlog.reference b/test/783stop.eventlog.reference index f34b2d7..3d50e4a 100644 --- a/test/783stop.eventlog.reference +++ b/test/783stop.eventlog.reference @@ -1,100 +1,100 @@ Event Types: - 0: Create thread (size 4) - 1: Run thread (size 4) - 2: Stop thread (size 10) - 3: Thread runnable (size 4) - 4: Migrate thread (size 6) - 8: Wakeup thread (size 6) - 9: Starting GC (size 0) - 10: Finished GC (size 0) - 11: Request sequential GC (size 0) - 12: Request parallel GC (size 0) - 15: Create spark thread (size 4) - 16: Log message (size variable) - 17: Create capabilities (size 2) - 18: Block marker (size 14) - 19: User message (size variable) - 20: GC idle (size 0) - 21: GC working (size 0) - 22: GC done (size 0) - 23: Version (size variable) - 24: Program invocation (size variable) - 25: Create capability set (size 6) - 26: Delete capability set (size 4) - 27: Add capability to capability set (size 6) - 28: Remove capability from capability set (size 6) - 29: RTS name and version (size variable) - 30: Program arguments (size variable) - 31: Program environment variables (size variable) - 32: Process ID (size 8) - 33: Parent process ID (size 8) - 34: Spark counters (size 56) - 35: Spark create (size 0) - 36: Spark dud (size 0) - 37: Spark overflow (size 0) - 38: Spark run (size 0) - 39: Spark steal (size 2) - 40: Spark fizzle (size 0) - 41: Spark GC (size 0) - 43: Wall clock time (size 16) - 44: Thread label (size variable) - 45: Create capability (size 2) - 46: Delete capability (size 2) - 47: Disable capability (size 2) - 48: Enable capability (size 2) - 49: Total heap mem ever allocated (size 12) - 50: Current heap size (size 12) - 51: Current heap live data (size 12) - 52: Heap static parameters (size 38) - 53: GC statistics (size 50) - 54: Synchronise stop-the-world GC (size 0) - 55: Task create (size 18) - 56: Task migrate (size 12) - 57: Task delete (size 8) - 58: User marker (size variable) - 59: Empty event for bug #9003 (size 0) - 60: Starting message receival (size 0) - 61: Finished message receival (size 0) - 62: Creating Process (size 4) - 63: Killing Process (size 4) - 64: Assigning thread to process (size 8) - 65: Creating machine (size 10) - 66: Killing machine (size 2) - 67: Sending message (size 19) - 68: Receiving message (size 23) - 69: Sending/Receiving local message (size 17) +0: Create thread (size 4) +1: Run thread (size 4) +2: Stop thread (size 10) +3: Thread runnable (size 4) +4: Migrate thread (size 6) +8: Wakeup thread (size 6) +9: Starting GC (size 0) +10: Finished GC (size 0) +11: Request sequential GC (size 0) +12: Request parallel GC (size 0) +15: Create spark thread (size 4) +16: Log message (size variable) +17: Create capabilities (size 2) +18: Block marker (size 14) +19: User message (size variable) +20: GC idle (size 0) +21: GC working (size 0) +22: GC done (size 0) +23: Version (size variable) +24: Program invocation (size variable) +25: Create capability set (size 6) +26: Delete capability set (size 4) +27: Add capability to capability set (size 6) +28: Remove capability from capability set (size 6) +29: RTS name and version (size variable) +30: Program arguments (size variable) +31: Program environment variables (size variable) +32: Process ID (size 8) +33: Parent process ID (size 8) +34: Spark counters (size 56) +35: Spark create (size 0) +36: Spark dud (size 0) +37: Spark overflow (size 0) +38: Spark run (size 0) +39: Spark steal (size 2) +40: Spark fizzle (size 0) +41: Spark GC (size 0) +43: Wall clock time (size 16) +44: Thread label (size variable) +45: Create capability (size 2) +46: Delete capability (size 2) +47: Disable capability (size 2) +48: Enable capability (size 2) +49: Total heap mem ever allocated (size 12) +50: Current heap size (size 12) +51: Current heap live data (size 12) +52: Heap static parameters (size 38) +53: GC statistics (size 50) +54: Synchronise stop-the-world GC (size 0) +55: Task create (size 18) +56: Task migrate (size 12) +57: Task delete (size 8) +58: User marker (size variable) +59: Empty event for bug #9003 (size 0) +60: Starting message receival (size 0) +61: Finished message receival (size 0) +62: Creating Process (size 4) +63: Killing Process (size 4) +64: Assigning thread to process (size 8) +65: Creating machine (size 10) +66: Killing machine (size 2) +67: Sending message (size 19) +68: Receiving message (size 23) +69: Sending/Receiving local message (size 17) Events: - 440074: startup: 1 capabilities - 446518: created capset 0 of type CapsetOsProcess - 446769: created capset 1 of type CapsetClockDomain - 448177: created cap 0 - 448347: assigned cap 0 to capset 0 - 448483: assigned cap 0 to capset 1 - 455484: capset 1: wall clock time 1405192714s 116018000ns (unix epoch) - 456191: capset 0: pid 19972 - 458325: capset 0: parent pid 18797 - 464895: capset 0: RTS version "GHC-7.8.3 rts_l" - 473314: capset 0: args: ["./wrong783","+RTS","-lsu-g-p","-K80m","-k10m","-H200m","-C1s"] - 479103: capset 0: env: ["SSH_AGENT_PID=1817","PVM_RSH=/usr/bin/ssh","GPG_AGENT_INFO=/tmp/keyring-yTUMmt/gpg:0:1","TERM=xterm","SHELL=/bin/bash","XDG_SESSION_COOKIE=acf1c79e0e2de67643be755c00000003-1405160974.283591-1531347675","WINDOWID=58743399","OLDPWD=/opt/Eden/edentv/fixFor783/BLD-ghc-events-parallel","GNOME_KEYRING_CONTROL=/tmp/keyring-yTUMmt","USER=jost","LS_COLORS=rs=0:di=01;34:ln=01;36:mh=00:pi=40;33:so=01;35:do=01;35:bd=40;33;01:cd=40;33;01:or=40;31;01:su=37;41:sg=30;43:ca=30;41:tw=30;42:ow=34;42:st=37;44:ex=01;32:*.tar=01;31:*.tgz=01;31:*.arj=01;31:*.taz=01;31:*.lzh=01;31:*.lzma=01;31:*.tlz=01;31:*.txz=01;31:*.zip=01;31:*.z=01;31:*.Z=01;31:*.dz=01;31:*.gz=01;31:*.lz=01;31:*.xz=01;31:*.bz2=01;31:*.bz=01;31:*.tbz=01;31:*.tbz2=01;31:*.tz=01;31:*.deb=01;31:*.rpm=01;31:*.jar=01;31:*.war=01;31:*.ear=01;31:*.sar=01;31:*.rar=01;31:*.ace=01;31:*.zoo=01;31:*.cpio=01;31:*.7z=01;31:*.rz=01;31:*.jpg=01;35:*.jpeg=01;35:*.gif=01;35:*.bmp=01;35:*.pbm=01;35:*.pgm=01;35:*.ppm=01;35:*.tga=01;35:*.xbm=01;35:*.xpm=01;35:*.tif=01;35:*.tiff=01;35:*.png=01;35:*.svg=01;35:*.svgz=01;35:*.mng=01;35:*.pcx=01;35:*.mov=01;35:*.mpg=01;35:*.mpeg=01;35:*.m2v=01;35:*.mkv=01;35:*.webm=01;35:*.ogm=01;35:*.mp4=01;35:*.m4v=01;35:*.mp4v=01;35:*.vob=01;35:*.qt=01;35:*.nuv=01;35:*.wmv=01;35:*.asf=01;35:*.rm=01;35:*.rmvb=01;35:*.flc=01;35:*.avi=01;35:*.fli=01;35:*.flv=01;35:*.gl=01;35:*.dl=01;35:*.xcf=01;35:*.xwd=01;35:*.yuv=01;35:*.cgm=01;35:*.emf=01;35:*.axv=01;35:*.anx=01;35:*.ogv=01;35:*.ogx=01;35:*.aac=00;36:*.au=00;36:*.flac=00;36:*.mid=00;36:*.midi=00;36:*.mka=00;36:*.mp3=00;36:*.mpc=00;36:*.ogg=00;36:*.ra=00;36:*.wav=00;36:*.axa=00;36:*.oga=00;36:*.spx=00;36:*.xspf=00;36:","XDG_SESSION_PATH=/org/freedesktop/DisplayManager/Session0","XDG_SEAT_PATH=/org/freedesktop/DisplayManager/Seat0","PVM_ROOT=/usr/lib/pvm3","SSH_AUTH_SOCK=/tmp/keyring-yTUMmt/ssh","SESSION_MANAGER=local/onAir:@/tmp/.ICE-unix/1781,unix/onAir:/tmp/.ICE-unix/1781","DEFAULTS_PATH=/usr/share/gconf/gnome-fallback.default.path","PVM_ARCH=LINUX64","XDG_CONFIG_DIRS=/etc/xdg/xdg-gnome-fallback:/etc/xdg","PATH=/home/jost/bin:/home/jost/bin:/usr/lib/lightdm/lightdm:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/home/jost/.cabal/bin","DESKTOP_SESSION=gnome-fallback","PWD=/opt/Eden/edentv/fixFor783","GNOME_KEYRING_PID=1770","LANG=en_US.UTF-8","MANDATORY_PATH=/usr/share/gconf/gnome-fallback.mandatory.path","UBUNTU_MENUPROXY=libappmenu.so","GDMSESSION=gnome-fallback","SHLVL=1","HOME=/home/jost","LANGUAGE=en_US:en","GNOME_DESKTOP_SESSION_ID=this-is-deprecated","LOGNAME=jost","PVM_EXPORT=DISPLAY","XDG_DATA_DIRS=/usr/share/gnome-fallback:/usr/share/gnome:/usr/local/share/:/usr/share/","DBUS_SESSION_BUS_ADDRESS=unix:abstract=/tmp/dbus-Mviy2n6D5M,guid=3677210ad991dc7e0dc3a1ae00000012","LESSOPEN=| /usr/bin/lesspipe %s","DISPLAY=:0.0","XDG_CURRENT_DESKTOP=GNOME","LESSCLOSE=/usr/bin/lesspipe %s %s","COLORTERM=gnome-terminal","XAUTHORITY=/home/jost/.Xauthority","_=./wrong783"] - 699793: task 0x12e70c0 created on cap 0 with OS kernel thread 19972 - 732448: cap 0: creating thread 1 - 739574: cap 0: running thread 1 - 793934: cap 0: stopping thread 1 (heap overflow) - 4798987: cap 0: running thread 1 - 5055994: cap 0: stopping thread 1 (making a foreign call) - 5058329: cap 0: running thread 1 - 5148943: cap 0: forking child thread - 5182260: cap 0: creating thread 2 - 5183843: cap 0: stopping thread 1 (thread yielding) - 5185547: cap 0: running thread 2 - 5192128: cap 0: stopping thread 2 (heap overflow) - 6603911: cap 0: running thread 2 - 6625740: cap 0: child - 10691075: cap 0: stopping thread 2 (thread yielding) - 10692575: cap 0: running thread 1 - 10700572: cap 0: stopping thread 1 (blocked on black hole owned by thread 2) - 10700759: cap 0: running thread 2 +440074: startup: 1 capabilities +446518: created capset 0 of type CapsetOsProcess +446769: created capset 1 of type CapsetClockDomain +448177: created cap 0 +448347: assigned cap 0 to capset 0 +448483: assigned cap 0 to capset 1 +455484: capset 1: wall clock time 1405192714s 116018000ns (unix epoch) +456191: capset 0: pid 19972 +458325: capset 0: parent pid 18797 +464895: capset 0: RTS version "GHC-7.8.3 rts_l" +473314: capset 0: args: ["./wrong783","+RTS","-lsu-g-p","-K80m","-k10m","-H200m","-C1s"] +479103: capset 0: env: ["SSH_AGENT_PID=1817","PVM_RSH=/usr/bin/ssh","GPG_AGENT_INFO=/tmp/keyring-yTUMmt/gpg:0:1","TERM=xterm","SHELL=/bin/bash","XDG_SESSION_COOKIE=acf1c79e0e2de67643be755c00000003-1405160974.283591-1531347675","WINDOWID=58743399","OLDPWD=/opt/Eden/edentv/fixFor783/BLD-ghc-events-parallel","GNOME_KEYRING_CONTROL=/tmp/keyring-yTUMmt","USER=jost","LS_COLORS=rs=0:di=01;34:ln=01;36:mh=00:pi=40;33:so=01;35:do=01;35:bd=40;33;01:cd=40;33;01:or=40;31;01:su=37;41:sg=30;43:ca=30;41:tw=30;42:ow=34;42:st=37;44:ex=01;32:*.tar=01;31:*.tgz=01;31:*.arj=01;31:*.taz=01;31:*.lzh=01;31:*.lzma=01;31:*.tlz=01;31:*.txz=01;31:*.zip=01;31:*.z=01;31:*.Z=01;31:*.dz=01;31:*.gz=01;31:*.lz=01;31:*.xz=01;31:*.bz2=01;31:*.bz=01;31:*.tbz=01;31:*.tbz2=01;31:*.tz=01;31:*.deb=01;31:*.rpm=01;31:*.jar=01;31:*.war=01;31:*.ear=01;31:*.sar=01;31:*.rar=01;31:*.ace=01;31:*.zoo=01;31:*.cpio=01;31:*.7z=01;31:*.rz=01;31:*.jpg=01;35:*.jpeg=01;35:*.gif=01;35:*.bmp=01;35:*.pbm=01;35:*.pgm=01;35:*.ppm=01;35:*.tga=01;35:*.xbm=01;35:*.xpm=01;35:*.tif=01;35:*.tiff=01;35:*.png=01;35:*.svg=01;35:*.svgz=01;35:*.mng=01;35:*.pcx=01;35:*.mov=01;35:*.mpg=01;35:*.mpeg=01;35:*.m2v=01;35:*.mkv=01;35:*.webm=01;35:*.ogm=01;35:*.mp4=01;35:*.m4v=01;35:*.mp4v=01;35:*.vob=01;35:*.qt=01;35:*.nuv=01;35:*.wmv=01;35:*.asf=01;35:*.rm=01;35:*.rmvb=01;35:*.flc=01;35:*.avi=01;35:*.fli=01;35:*.flv=01;35:*.gl=01;35:*.dl=01;35:*.xcf=01;35:*.xwd=01;35:*.yuv=01;35:*.cgm=01;35:*.emf=01;35:*.axv=01;35:*.anx=01;35:*.ogv=01;35:*.ogx=01;35:*.aac=00;36:*.au=00;36:*.flac=00;36:*.mid=00;36:*.midi=00;36:*.mka=00;36:*.mp3=00;36:*.mpc=00;36:*.ogg=00;36:*.ra=00;36:*.wav=00;36:*.axa=00;36:*.oga=00;36:*.spx=00;36:*.xspf=00;36:","XDG_SESSION_PATH=/org/freedesktop/DisplayManager/Session0","XDG_SEAT_PATH=/org/freedesktop/DisplayManager/Seat0","PVM_ROOT=/usr/lib/pvm3","SSH_AUTH_SOCK=/tmp/keyring-yTUMmt/ssh","SESSION_MANAGER=local/onAir:@/tmp/.ICE-unix/1781,unix/onAir:/tmp/.ICE-unix/1781","DEFAULTS_PATH=/usr/share/gconf/gnome-fallback.default.path","PVM_ARCH=LINUX64","XDG_CONFIG_DIRS=/etc/xdg/xdg-gnome-fallback:/etc/xdg","PATH=/home/jost/bin:/home/jost/bin:/usr/lib/lightdm/lightdm:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/home/jost/.cabal/bin","DESKTOP_SESSION=gnome-fallback","PWD=/opt/Eden/edentv/fixFor783","GNOME_KEYRING_PID=1770","LANG=en_US.UTF-8","MANDATORY_PATH=/usr/share/gconf/gnome-fallback.mandatory.path","UBUNTU_MENUPROXY=libappmenu.so","GDMSESSION=gnome-fallback","SHLVL=1","HOME=/home/jost","LANGUAGE=en_US:en","GNOME_DESKTOP_SESSION_ID=this-is-deprecated","LOGNAME=jost","PVM_EXPORT=DISPLAY","XDG_DATA_DIRS=/usr/share/gnome-fallback:/usr/share/gnome:/usr/local/share/:/usr/share/","DBUS_SESSION_BUS_ADDRESS=unix:abstract=/tmp/dbus-Mviy2n6D5M,guid=3677210ad991dc7e0dc3a1ae00000012","LESSOPEN=| /usr/bin/lesspipe %s","DISPLAY=:0.0","XDG_CURRENT_DESKTOP=GNOME","LESSCLOSE=/usr/bin/lesspipe %s %s","COLORTERM=gnome-terminal","XAUTHORITY=/home/jost/.Xauthority","_=./wrong783"] +699793: task 0x12e70c0 created on cap 0 with OS kernel thread 19972 +732448: cap 0: creating thread 1 +739574: cap 0: running thread 1 +793934: cap 0: stopping thread 1 (heap overflow) +4798987: cap 0: running thread 1 +5055994: cap 0: stopping thread 1 (making a foreign call) +5058329: cap 0: running thread 1 +5148943: cap 0: forking child thread +5182260: cap 0: creating thread 2 +5183843: cap 0: stopping thread 1 (thread yielding) +5185547: cap 0: running thread 2 +5192128: cap 0: stopping thread 2 (heap overflow) +6603911: cap 0: running thread 2 +6625740: cap 0: child +10691075: cap 0: stopping thread 2 (thread yielding) +10692575: cap 0: running thread 1 +10700572: cap 0: stopping thread 1 (blocked on black hole owned by thread 2) +10700759: cap 0: running thread 2 196062624: cap 0: stopping thread 2 (heap overflow) 196666678: cap 0: running thread 2 333935541: cap 0: stopping thread 2 (heap overflow) @@ -146,4 +146,3 @@ Events: 841729327: deleted capset 0 841729456: deleted capset 1 - diff --git a/test/mandelbrot-mmc-2011-06-14.eventlog.reference b/test/mandelbrot-mmc-2011-06-14.eventlog.reference index 8660ea9..1148b3b 100644 --- a/test/mandelbrot-mmc-2011-06-14.eventlog.reference +++ b/test/mandelbrot-mmc-2011-06-14.eventlog.reference @@ -1,2212 +1,2212 @@ Event Types: - 17: Startup (num_engines) (size 2) - 7: Shutdown (size 0) - 18: A block of events generated by a specific engine follows (size 14) - 0: A context is created or re-used (size 4) - 3: The context is being placed on the run queue (size 4) - 5: Run a spark from the local stack (size 8) - 6: Run a spark stolen from another engine (size 10) - 1: Run context (size 4) - 2: Context stopped (size 6) - 15: Create a context for executing a spark (size 4) - 16: A user-provided log message (size variable) - 9: Start GC (size 0) - 10: Stop GC (size 0) - 39: Register an id->string mapping (size variable) - 40: About to call main/2 (size 0) - 25: Create an engine set (size 6) - 26: Detete an engine set (size 4) - 27: Add an engine to an engine set (size 6) - 28: Add an engine to an engine set (size 6) - 29: The type of the runtime system for this capset (size variable) - 30: The command line arguments of this process (size variable) - 31: The environment variables this process inherited (size variable) - 32: The pid and parent pid of this process (size 8) - 103: A spark is being created (size 12) - 100: Start a parallel conjunction (dyn id, static id) (size 12) - 101: End a parallel conjunction (dyn id) (size 8) - 102: End a parallel conjunct (dyn id) (size 8) - 104: Create a future (future id) (size 12) - 105: Wait on a future without suspending (future id) (size 8) - 106: Wait on a future by suspending this thread (future id) (size 8) - 107: Signal a future (future id) (size 8) - 108: Engine begins looking for a context to execute (size 0) - 109: Engine begins attempt to steal work (size 0) - 110: Release this context to the free context pool (size 4) +17: Startup (num_engines) (size 2) +7: Shutdown (size 0) +18: A block of events generated by a specific engine follows (size 14) +0: A context is created or re-used (size 4) +3: The context is being placed on the run queue (size 4) +5: Run a spark from the local stack (size 8) +6: Run a spark stolen from another engine (size 10) +1: Run context (size 4) +2: Context stopped (size 6) +15: Create a context for executing a spark (size 4) +16: A user-provided log message (size variable) +9: Start GC (size 0) +10: Stop GC (size 0) +39: Register an id->string mapping (size variable) +40: About to call main/2 (size 0) +25: Create an engine set (size 6) +26: Detete an engine set (size 4) +27: Add an engine to an engine set (size 6) +28: Add an engine to an engine set (size 6) +29: The type of the runtime system for this capset (size variable) +30: The command line arguments of this process (size variable) +31: The environment variables this process inherited (size variable) +32: The pid and parent pid of this process (size 8) +103: A spark is being created (size 12) +100: Start a parallel conjunction (dyn id, static id) (size 12) +101: End a parallel conjunction (dyn id) (size 8) +102: End a parallel conjunct (dyn id) (size 8) +104: Create a future (future id) (size 12) +105: Wait on a future without suspending (future id) (size 8) +106: Wait on a future by suspending this thread (future id) (size 8) +107: Signal a future (future id) (size 8) +108: Engine begins looking for a context to execute (size 0) +109: Engine begins attempt to steal work (size 0) +110: Release this context to the free context pool (size 4) Events: - 0: created capset 0 of type CapsetOsProcess - 0: capset 0: RTS version "mmc-DEV" - 0: startup: 4 capabilities - 0: Register an id->string mapping - 0: Register an id->string mapping - 0: Register an id->string mapping - 0: Register an id->string mapping - 0: assigned cap 0 to capset 0 - 0: assigned cap 3 to capset 0 - 0: assigned cap 1 to capset 0 - 0: assigned cap 2 to capset 0 - 4198126: cap 0: creating thread 1 - 4199512: cap 0: running thread 1 - 9983902: cap 3: Looking for global thread to resume - 9987484: cap 3: Trying to steal a spark - 10575823: cap 1: Looking for global thread to resume - 10577452: cap 1: Trying to steal a spark - 10694043: cap 2: Looking for global thread to resume - 10694551: cap 2: Trying to steal a spark - 10852245: cap 0: spark fizzled - 11153997: cap 0: Start a parallel conjunction 0x2515150, static_id: 2 - 11155725: cap 0: Create spark for conjunction: 0x2515150 spark: 0x0 - 11165265: cap 0: Start a parallel conjunction 0x25151b0, static_id: 2 - 11165593: cap 0: Create spark for conjunction: 0x25151b0 spark: 0x1 - 11169886: cap 0: Start a parallel conjunction 0x2515210, static_id: 2 - 11170080: cap 0: Create spark for conjunction: 0x2515210 spark: 0x2 - 11172546: cap 0: Start a parallel conjunction 0x2515270, static_id: 2 - 11172730: cap 0: Create spark for conjunction: 0x2515270 spark: 0x3 - 11173041: cap 0: Start a parallel conjunction 0x25152d0, static_id: 2 - 11173338: cap 0: Create spark for conjunction: 0x25152d0 spark: 0x4 - 11173905: cap 0: Start a parallel conjunction 0x2515330, static_id: 2 - 11174107: cap 0: Create spark for conjunction: 0x2515330 spark: 0x5 - 11174143: cap 2: Trying to steal a spark - 11174413: cap 0: Start a parallel conjunction 0x2515390, static_id: 2 - 11174760: cap 0: Create spark for conjunction: 0x2515390 spark: 0x6 - 11175034: cap 0: Start a parallel conjunction 0x25153f0, static_id: 2 - 11175610: cap 0: Create spark for conjunction: 0x25153f0 spark: 0x7 - 11175853: cap 3: Trying to steal a spark - 11175885: cap 0: Start a parallel conjunction 0x2515450, static_id: 2 - 11177316: cap 2: stealing a spark from cap 0 - 11178108: cap 3: stealing a spark from cap 0 - 11198002: cap 0: Create spark for conjunction: 0x2515450 spark: 0x8 - 11198394: cap 0: Start a parallel conjunction 0x25154b0, static_id: 2 - 11198601: cap 0: Create spark for conjunction: 0x25154b0 spark: 0x9 - 11198880: cap 0: Start a parallel conjunction 0x2515510, static_id: 2 - 11199069: cap 0: Create spark for conjunction: 0x2515510 spark: 0xa - 11199352: cap 0: Start a parallel conjunction 0x2515570, static_id: 2 - 11199541: cap 0: Create spark for conjunction: 0x2515570 spark: 0xb - 11199829: cap 0: Start a parallel conjunction 0x25155d0, static_id: 2 - 11200014: cap 0: Create spark for conjunction: 0x25155d0 spark: 0xc - 11200275: cap 0: Start a parallel conjunction 0x2515630, static_id: 2 - 11200468: cap 0: Create spark for conjunction: 0x2515630 spark: 0xd - 11200743: cap 0: Start a parallel conjunction 0x2515690, static_id: 2 - 11200918: cap 0: Create spark for conjunction: 0x2515690 spark: 0xe - 11201206: cap 0: Start a parallel conjunction 0x25156f0, static_id: 2 - 11201418: cap 0: Create spark for conjunction: 0x25156f0 spark: 0xf - 11201719: cap 0: Start a parallel conjunction 0x2515750, static_id: 2 - 11201899: cap 0: Create spark for conjunction: 0x2515750 spark: 0x10 - 11202174: cap 0: Start a parallel conjunction 0x25157b0, static_id: 2 - 11220259: cap 0: Create spark for conjunction: 0x25157b0 spark: 0x11 - 11220592: cap 0: Start a parallel conjunction 0x2515810, static_id: 2 - 11220772: cap 0: Create spark for conjunction: 0x2515810 spark: 0x12 - 11221083: cap 0: Start a parallel conjunction 0x2515870, static_id: 2 - 11221272: cap 0: Create spark for conjunction: 0x2515870 spark: 0x13 - 11221533: cap 0: Start a parallel conjunction 0x25158d0, static_id: 2 - 11221731: cap 0: Create spark for conjunction: 0x25158d0 spark: 0x14 - 11222005: cap 0: Start a parallel conjunction 0x2515930, static_id: 2 - 11222199: cap 0: Create spark for conjunction: 0x2515930 spark: 0x15 - 11222478: cap 0: Start a parallel conjunction 0x2515990, static_id: 2 - 11222671: cap 0: Create spark for conjunction: 0x2515990 spark: 0x16 - 11222941: cap 0: Start a parallel conjunction 0x25159f0, static_id: 2 - 11223130: cap 0: Create spark for conjunction: 0x25159f0 spark: 0x17 - 11223400: cap 0: Start a parallel conjunction 0x2515a50, static_id: 2 - 11223580: cap 0: Create spark for conjunction: 0x2515a50 spark: 0x18 - 11223886: cap 0: Start a parallel conjunction 0x2515ab0, static_id: 2 - 11224066: cap 0: Create spark for conjunction: 0x2515ab0 spark: 0x19 - 11224336: cap 0: Start a parallel conjunction 0x2515b10, static_id: 2 - 11224543: cap 0: Create spark for conjunction: 0x2515b10 spark: 0x1a - 11224827: cap 0: Start a parallel conjunction 0x2515b70, static_id: 2 - 11225007: cap 0: Create spark for conjunction: 0x2515b70 spark: 0x1b - 11225286: cap 0: Start a parallel conjunction 0x2515bd0, static_id: 2 - 11225470: cap 0: Create spark for conjunction: 0x2515bd0 spark: 0x1c - 11225758: cap 0: Start a parallel conjunction 0x2515c30, static_id: 2 - 11225956: cap 0: Create spark for conjunction: 0x2515c30 spark: 0x1d - 11226240: cap 0: Start a parallel conjunction 0x2515c90, static_id: 2 - 11226424: cap 0: Create spark for conjunction: 0x2515c90 spark: 0x1e - 11226708: cap 0: Start a parallel conjunction 0x2515cf0, static_id: 2 - 11226892: cap 0: Create spark for conjunction: 0x2515cf0 spark: 0x1f - 11227176: cap 0: Start a parallel conjunction 0x2515d50, static_id: 2 - 11227374: cap 0: Create spark for conjunction: 0x2515d50 spark: 0x20 - 11227653: cap 0: Start a parallel conjunction 0x2515db0, static_id: 2 - 11299891: cap 0: Create spark for conjunction: 0x2515db0 spark: 0x21 - 11300346: cap 0: Start a parallel conjunction 0x2515e10, static_id: 2 - 11300535: cap 0: Create spark for conjunction: 0x2515e10 spark: 0x22 - 11300845: cap 0: Start a parallel conjunction 0x2515e70, static_id: 2 - 11301034: cap 0: Create spark for conjunction: 0x2515e70 spark: 0x23 - 11301291: cap 0: Start a parallel conjunction 0x2515ed0, static_id: 2 - 11301489: cap 0: Create spark for conjunction: 0x2515ed0 spark: 0x24 - 11301772: cap 0: Start a parallel conjunction 0x2515f30, static_id: 2 - 11301961: cap 0: Create spark for conjunction: 0x2515f30 spark: 0x25 - 11302245: cap 0: Start a parallel conjunction 0x2515f90, static_id: 2 - 11302438: cap 0: Create spark for conjunction: 0x2515f90 spark: 0x26 - 11302726: cap 0: Start a parallel conjunction 0x2515ff0, static_id: 2 - 11302929: cap 0: Create spark for conjunction: 0x2515ff0 spark: 0x27 - 11303212: cap 0: Start a parallel conjunction 0x2516050, static_id: 2 - 11303401: cap 0: Create spark for conjunction: 0x2516050 spark: 0x28 - 11303698: cap 0: Start a parallel conjunction 0x25160b0, static_id: 2 - 11303883: cap 0: Create spark for conjunction: 0x25160b0 spark: 0x29 - 11304162: cap 0: Start a parallel conjunction 0x2516110, static_id: 2 - 11304351: cap 0: Create spark for conjunction: 0x2516110 spark: 0x2a - 11304630: cap 0: Start a parallel conjunction 0x2516170, static_id: 2 - 11304814: cap 0: Create spark for conjunction: 0x2516170 spark: 0x2b - 11305093: cap 0: Start a parallel conjunction 0x25161d0, static_id: 2 - 11305287: cap 0: Create spark for conjunction: 0x25161d0 spark: 0x2c - 11305566: cap 0: Start a parallel conjunction 0x2516230, static_id: 2 - 11305759: cap 0: Create spark for conjunction: 0x2516230 spark: 0x2d - 11306034: cap 0: Start a parallel conjunction 0x2516290, static_id: 2 - 11306214: cap 0: Create spark for conjunction: 0x2516290 spark: 0x2e - 11306493: cap 0: Start a parallel conjunction 0x25162f0, static_id: 2 - 11306673: cap 0: Create spark for conjunction: 0x25162f0 spark: 0x2f - 11306943: cap 0: Start a parallel conjunction 0x2516350, static_id: 2 - 11307127: cap 0: Create spark for conjunction: 0x2516350 spark: 0x30 - 11307402: cap 0: Start a parallel conjunction 0x25163b0, static_id: 2 - 11307586: cap 0: Create spark for conjunction: 0x25163b0 spark: 0x31 - 11307852: cap 0: Start a parallel conjunction 0x2516410, static_id: 2 - 11308036: cap 0: Create spark for conjunction: 0x2516410 spark: 0x32 - 11308320: cap 0: Start a parallel conjunction 0x2516470, static_id: 2 - 11308509: cap 0: Create spark for conjunction: 0x2516470 spark: 0x33 - 11308788: cap 0: Start a parallel conjunction 0x25164d0, static_id: 2 - 11308990: cap 0: Create spark for conjunction: 0x25164d0 spark: 0x34 - 11309265: cap 0: Start a parallel conjunction 0x2516530, static_id: 2 - 11309445: cap 0: Create spark for conjunction: 0x2516530 spark: 0x35 - 11309751: cap 0: Start a parallel conjunction 0x2516590, static_id: 2 - 11309931: cap 0: Create spark for conjunction: 0x2516590 spark: 0x36 - 11310196: cap 0: Start a parallel conjunction 0x25165f0, static_id: 2 - 11310394: cap 0: Create spark for conjunction: 0x25165f0 spark: 0x37 - 11310678: cap 0: Start a parallel conjunction 0x2516650, static_id: 2 - 11310867: cap 0: Create spark for conjunction: 0x2516650 spark: 0x38 - 11311155: cap 0: Start a parallel conjunction 0x25166b0, static_id: 2 - 11311339: cap 0: Create spark for conjunction: 0x25166b0 spark: 0x39 - 11311609: cap 0: Start a parallel conjunction 0x2516710, static_id: 2 - 11311794: cap 0: Create spark for conjunction: 0x2516710 spark: 0x3a - 11312073: cap 0: Start a parallel conjunction 0x2516770, static_id: 2 - 11312253: cap 0: Create spark for conjunction: 0x2516770 spark: 0x3b - 11312532: cap 0: Start a parallel conjunction 0x25167d0, static_id: 2 - 11312721: cap 0: Create spark for conjunction: 0x25167d0 spark: 0x3c - 11313000: cap 0: Start a parallel conjunction 0x2516830, static_id: 2 - 11313211: cap 0: Create spark for conjunction: 0x2516830 spark: 0x3d - 11313490: cap 0: Start a parallel conjunction 0x2516890, static_id: 2 - 11313670: cap 0: Create spark for conjunction: 0x2516890 spark: 0x3e - 11313954: cap 0: Start a parallel conjunction 0x25168f0, static_id: 2 - 11314138: cap 0: Create spark for conjunction: 0x25168f0 spark: 0x3f - 11314399: cap 0: Start a parallel conjunction 0x2516950, static_id: 2 - 11314593: cap 0: Create spark for conjunction: 0x2516950 spark: 0x40 - 11314872: cap 0: Start a parallel conjunction 0x25169b0, static_id: 2 - 11358931: cap 0: Create spark for conjunction: 0x25169b0 spark: 0x41 - 11359269: cap 0: Start a parallel conjunction 0x2516a10, static_id: 2 - 11359453: cap 0: Create spark for conjunction: 0x2516a10 spark: 0x42 - 11359755: cap 0: Start a parallel conjunction 0x2516a70, static_id: 2 - 11359948: cap 0: Create spark for conjunction: 0x2516a70 spark: 0x43 - 11360232: cap 0: Start a parallel conjunction 0x2516ad0, static_id: 2 - 11360421: cap 0: Create spark for conjunction: 0x2516ad0 spark: 0x44 - 11360700: cap 0: Start a parallel conjunction 0x2516b30, static_id: 2 - 11360902: cap 0: Create spark for conjunction: 0x2516b30 spark: 0x45 - 11361181: cap 0: Start a parallel conjunction 0x2516b90, static_id: 2 - 11361370: cap 0: Create spark for conjunction: 0x2516b90 spark: 0x46 - 11361645: cap 0: Start a parallel conjunction 0x2516bf0, static_id: 2 - 11361843: cap 0: Create spark for conjunction: 0x2516bf0 spark: 0x47 - 11362117: cap 0: Start a parallel conjunction 0x2516c50, static_id: 2 - 11362302: cap 0: Create spark for conjunction: 0x2516c50 spark: 0x48 - 11362599: cap 0: Start a parallel conjunction 0x2516cb0, static_id: 2 - 11362810: cap 0: Create spark for conjunction: 0x2516cb0 spark: 0x49 - 11363089: cap 0: Start a parallel conjunction 0x2516d10, static_id: 2 - 11363274: cap 0: Create spark for conjunction: 0x2516d10 spark: 0x4a - 11363553: cap 0: Start a parallel conjunction 0x2516d70, static_id: 2 - 11363742: cap 0: Create spark for conjunction: 0x2516d70 spark: 0x4b - 11364021: cap 0: Start a parallel conjunction 0x2516dd0, static_id: 2 - 11364205: cap 0: Create spark for conjunction: 0x2516dd0 spark: 0x4c - 11364480: cap 0: Start a parallel conjunction 0x2516e30, static_id: 2 - 11364682: cap 0: Create spark for conjunction: 0x2516e30 spark: 0x4d - 11364948: cap 0: Start a parallel conjunction 0x2516e90, static_id: 2 - 11365128: cap 0: Create spark for conjunction: 0x2516e90 spark: 0x4e - 11365420: cap 0: Start a parallel conjunction 0x2516ef0, static_id: 2 - 11365609: cap 0: Create spark for conjunction: 0x2516ef0 spark: 0x4f - 11365879: cap 0: Start a parallel conjunction 0x2516f50, static_id: 2 - 11366059: cap 0: Create spark for conjunction: 0x2516f50 spark: 0x50 - 11366338: cap 0: Start a parallel conjunction 0x2516fb0, static_id: 2 - 11366527: cap 0: Create spark for conjunction: 0x2516fb0 spark: 0x51 - 11366833: cap 0: Start a parallel conjunction 0x2517010, static_id: 2 - 11367022: cap 0: Create spark for conjunction: 0x2517010 spark: 0x52 - 11367319: cap 0: Start a parallel conjunction 0x2517070, static_id: 2 - 11367513: cap 0: Create spark for conjunction: 0x2517070 spark: 0x53 - 11367778: cap 0: Start a parallel conjunction 0x25170d0, static_id: 2 - 11367972: cap 0: Create spark for conjunction: 0x25170d0 spark: 0x54 - 11368246: cap 0: Start a parallel conjunction 0x2517130, static_id: 2 - 11368444: cap 0: Create spark for conjunction: 0x2517130 spark: 0x55 - 11368723: cap 0: Start a parallel conjunction 0x2517190, static_id: 2 - 11368908: cap 0: Create spark for conjunction: 0x2517190 spark: 0x56 - 11369182: cap 0: Start a parallel conjunction 0x25171f0, static_id: 2 - 11369385: cap 0: Create spark for conjunction: 0x25171f0 spark: 0x57 - 11369664: cap 0: Start a parallel conjunction 0x2517250, static_id: 2 - 11369853: cap 0: Create spark for conjunction: 0x2517250 spark: 0x58 - 11370136: cap 0: Start a parallel conjunction 0x25172b0, static_id: 2 - 11370334: cap 0: Create spark for conjunction: 0x25172b0 spark: 0x59 - 11370609: cap 0: Start a parallel conjunction 0x2517310, static_id: 2 - 11370811: cap 0: Create spark for conjunction: 0x2517310 spark: 0x5a - 11371090: cap 0: Start a parallel conjunction 0x2517370, static_id: 2 - 11371297: cap 0: Create spark for conjunction: 0x2517370 spark: 0x5b - 11371702: cap 0: Start a parallel conjunction 0x25173d0, static_id: 2 - 11371887: cap 0: Create spark for conjunction: 0x25173d0 spark: 0x5c - 11372152: cap 0: Start a parallel conjunction 0x2517430, static_id: 2 - 11372463: cap 0: Create spark for conjunction: 0x2517430 spark: 0x5d - 11372746: cap 0: Start a parallel conjunction 0x2517490, static_id: 2 - 11372931: cap 0: Create spark for conjunction: 0x2517490 spark: 0x5e - 11373349: cap 0: Start a parallel conjunction 0x25174f0, static_id: 2 - 11373552: cap 0: Create spark for conjunction: 0x25174f0 spark: 0x5f - 11373831: cap 0: Start a parallel conjunction 0x2517550, static_id: 2 - 11374024: cap 0: Create spark for conjunction: 0x2517550 spark: 0x60 - 11374299: cap 0: Start a parallel conjunction 0x25175b0, static_id: 2 - 11374492: cap 0: Create spark for conjunction: 0x25175b0 spark: 0x61 - 11374758: cap 0: Start a parallel conjunction 0x2517610, static_id: 2 - 11374942: cap 0: Create spark for conjunction: 0x2517610 spark: 0x62 - 11375221: cap 0: Start a parallel conjunction 0x2517670, static_id: 2 - 11375415: cap 0: Create spark for conjunction: 0x2517670 spark: 0x63 - 11375671: cap 0: Start a parallel conjunction 0x25176d0, static_id: 2 - 11375865: cap 0: Create spark for conjunction: 0x25176d0 spark: 0x64 - 11376148: cap 0: Start a parallel conjunction 0x2517730, static_id: 2 - 11376342: cap 0: Create spark for conjunction: 0x2517730 spark: 0x65 - 11376616: cap 0: Start a parallel conjunction 0x2517790, static_id: 2 - 11376805: cap 0: Create spark for conjunction: 0x2517790 spark: 0x66 - 11377062: cap 0: Start a parallel conjunction 0x25177f0, static_id: 2 - 11377264: cap 0: Create spark for conjunction: 0x25177f0 spark: 0x67 - 11377539: cap 0: Start a parallel conjunction 0x2517850, static_id: 2 - 11377723: cap 0: Create spark for conjunction: 0x2517850 spark: 0x68 - 11378007: cap 0: Start a parallel conjunction 0x25178b0, static_id: 2 - 11378205: cap 0: Create spark for conjunction: 0x25178b0 spark: 0x69 - 11378484: cap 0: Start a parallel conjunction 0x2517910, static_id: 2 - 11378677: cap 0: Create spark for conjunction: 0x2517910 spark: 0x6a - 11378965: cap 0: Start a parallel conjunction 0x2517970, static_id: 2 - 11379168: cap 0: Create spark for conjunction: 0x2517970 spark: 0x6b - 11379465: cap 0: Start a parallel conjunction 0x25179d0, static_id: 2 - 11379649: cap 0: Create spark for conjunction: 0x25179d0 spark: 0x6c - 11379915: cap 0: Start a parallel conjunction 0x2517a30, static_id: 2 - 11380117: cap 0: Create spark for conjunction: 0x2517a30 spark: 0x6d - 11380378: cap 0: Start a parallel conjunction 0x2517a90, static_id: 2 - 11380558: cap 0: Create spark for conjunction: 0x2517a90 spark: 0x6e - 11380837: cap 0: Start a parallel conjunction 0x2517af0, static_id: 2 - 11381040: cap 0: Create spark for conjunction: 0x2517af0 spark: 0x6f - 11381296: cap 0: Start a parallel conjunction 0x2517b50, static_id: 2 - 11381481: cap 0: Create spark for conjunction: 0x2517b50 spark: 0x70 - 11381751: cap 0: Start a parallel conjunction 0x2517bb0, static_id: 2 - 11381953: cap 0: Create spark for conjunction: 0x2517bb0 spark: 0x71 - 11382219: cap 0: Start a parallel conjunction 0x2517c10, static_id: 2 - 11382412: cap 0: Create spark for conjunction: 0x2517c10 spark: 0x72 - 11382700: cap 0: Start a parallel conjunction 0x2517c70, static_id: 2 - 11382912: cap 0: Create spark for conjunction: 0x2517c70 spark: 0x73 - 11383195: cap 0: Start a parallel conjunction 0x2517cd0, static_id: 2 - 11383402: cap 0: Create spark for conjunction: 0x2517cd0 spark: 0x74 - 11383672: cap 0: Start a parallel conjunction 0x2517d30, static_id: 2 - 11383875: cap 0: Create spark for conjunction: 0x2517d30 spark: 0x75 - 11384163: cap 0: Start a parallel conjunction 0x2517d90, static_id: 2 - 11384352: cap 0: Create spark for conjunction: 0x2517d90 spark: 0x76 - 11384622: cap 0: Start a parallel conjunction 0x2517df0, static_id: 2 - 11384824: cap 0: Create spark for conjunction: 0x2517df0 spark: 0x77 - 11385099: cap 0: Start a parallel conjunction 0x2517e50, static_id: 2 - 11385288: cap 0: Create spark for conjunction: 0x2517e50 spark: 0x78 - 11385567: cap 0: Start a parallel conjunction 0x2517eb0, static_id: 2 - 11385765: cap 0: Create spark for conjunction: 0x2517eb0 spark: 0x79 - 11386021: cap 0: Start a parallel conjunction 0x2517f10, static_id: 2 - 11386210: cap 0: Create spark for conjunction: 0x2517f10 spark: 0x7a - 11386480: cap 0: Start a parallel conjunction 0x2517f70, static_id: 2 - 11386674: cap 0: Create spark for conjunction: 0x2517f70 spark: 0x7b - 11386971: cap 0: Start a parallel conjunction 0x2517fd0, static_id: 2 - 11387160: cap 0: Create spark for conjunction: 0x2517fd0 spark: 0x7c - 11387475: cap 0: Start a parallel conjunction 0x2518030, static_id: 2 - 11387695: cap 0: Create spark for conjunction: 0x2518030 spark: 0x7d - 11388001: cap 0: Start a parallel conjunction 0x2518090, static_id: 2 - 11388190: cap 0: Create spark for conjunction: 0x2518090 spark: 0x7e - 11388496: cap 0: Start a parallel conjunction 0x25180f0, static_id: 2 - 11388699: cap 0: Create spark for conjunction: 0x25180f0 spark: 0x7f - 11388960: cap 0: Start a parallel conjunction 0x2518150, static_id: 2 - 11389144: cap 0: Create spark for conjunction: 0x2518150 spark: 0x80 - 11389423: cap 0: Start a parallel conjunction 0x25181b0, static_id: 2 - 11409403: cap 0: Create spark for conjunction: 0x25181b0 spark: 0x81 - 11409732: cap 0: Start a parallel conjunction 0x2518210, static_id: 2 - 11409930: cap 0: Create spark for conjunction: 0x2518210 spark: 0x82 - 11410236: cap 0: Start a parallel conjunction 0x2518270, static_id: 2 - 11410425: cap 0: Create spark for conjunction: 0x2518270 spark: 0x83 - 11410699: cap 0: Start a parallel conjunction 0x25182d0, static_id: 2 - 11410947: cap 0: Create spark for conjunction: 0x25182d0 spark: 0x84 - 11411226: cap 0: Start a parallel conjunction 0x2518330, static_id: 2 - 11411406: cap 0: Create spark for conjunction: 0x2518330 spark: 0x85 - 11411694: cap 0: Start a parallel conjunction 0x2518390, static_id: 2 - 11411874: cap 0: Create spark for conjunction: 0x2518390 spark: 0x86 - 11412135: cap 0: Start a parallel conjunction 0x25183f0, static_id: 2 - 11412337: cap 0: Create spark for conjunction: 0x25183f0 spark: 0x87 - 11412621: cap 0: Start a parallel conjunction 0x2518450, static_id: 2 - 11412868: cap 0: Create spark for conjunction: 0x2518450 spark: 0x88 - 11413170: cap 0: Start a parallel conjunction 0x25184b0, static_id: 2 - 11413363: cap 0: Create spark for conjunction: 0x25184b0 spark: 0x89 - 11413638: cap 0: Start a parallel conjunction 0x2518510, static_id: 2 - 11413822: cap 0: Create spark for conjunction: 0x2518510 spark: 0x8a - 11414218: cap 0: Start a parallel conjunction 0x2518570, static_id: 2 - 11414461: cap 0: Create spark for conjunction: 0x2518570 spark: 0x8b - 11414758: cap 0: Start a parallel conjunction 0x25185d0, static_id: 2 - 11414938: cap 0: Create spark for conjunction: 0x25185d0 spark: 0x8c - 11415213: cap 0: Start a parallel conjunction 0x2518630, static_id: 2 - 11415415: cap 0: Create spark for conjunction: 0x2518630 spark: 0x8d - 11415685: cap 0: Start a parallel conjunction 0x2518690, static_id: 2 - 11415865: cap 0: Create spark for conjunction: 0x2518690 spark: 0x8e - 11416149: cap 0: Start a parallel conjunction 0x25186f0, static_id: 2 - 11416333: cap 0: Create spark for conjunction: 0x25186f0 spark: 0x8f - 11416603: cap 0: Start a parallel conjunction 0x2518750, static_id: 2 - 11416788: cap 0: Create spark for conjunction: 0x2518750 spark: 0x90 - 11417067: cap 0: Start a parallel conjunction 0x25187b0, static_id: 2 - 11417256: cap 0: Create spark for conjunction: 0x25187b0 spark: 0x91 - 11417530: cap 0: Start a parallel conjunction 0x2518810, static_id: 2 - 11417715: cap 0: Create spark for conjunction: 0x2518810 spark: 0x92 - 11418012: cap 0: Start a parallel conjunction 0x2518870, static_id: 2 - 11418205: cap 0: Create spark for conjunction: 0x2518870 spark: 0x93 - 11418471: cap 0: Start a parallel conjunction 0x25188d0, static_id: 2 - 11418669: cap 0: Create spark for conjunction: 0x25188d0 spark: 0x94 - 11418961: cap 0: Start a parallel conjunction 0x2518930, static_id: 2 - 11419150: cap 0: Create spark for conjunction: 0x2518930 spark: 0x95 - 11419434: cap 0: Start a parallel conjunction 0x2518990, static_id: 2 - 11419618: cap 0: Create spark for conjunction: 0x2518990 spark: 0x96 - 11419879: cap 0: Start a parallel conjunction 0x25189f0, static_id: 2 - 11420077: cap 0: Create spark for conjunction: 0x25189f0 spark: 0x97 - 11420352: cap 0: Start a parallel conjunction 0x2518a50, static_id: 2 - 11420536: cap 0: Create spark for conjunction: 0x2518a50 spark: 0x98 - 11420838: cap 0: Start a parallel conjunction 0x2518ab0, static_id: 2 - 11421036: cap 0: Create spark for conjunction: 0x2518ab0 spark: 0x99 - 11421315: cap 0: Start a parallel conjunction 0x2518b10, static_id: 2 - 11421513: cap 0: Create spark for conjunction: 0x2518b10 spark: 0x9a - 11421792: cap 0: Start a parallel conjunction 0x2518b70, static_id: 2 - 11421985: cap 0: Create spark for conjunction: 0x2518b70 spark: 0x9b - 11422264: cap 0: Start a parallel conjunction 0x2518bd0, static_id: 2 - 11422449: cap 0: Create spark for conjunction: 0x2518bd0 spark: 0x9c - 11422737: cap 0: Start a parallel conjunction 0x2518c30, static_id: 2 - 11422939: cap 0: Create spark for conjunction: 0x2518c30 spark: 0x9d - 11423209: cap 0: Start a parallel conjunction 0x2518c90, static_id: 2 - 11423403: cap 0: Create spark for conjunction: 0x2518c90 spark: 0x9e - 11423686: cap 0: Start a parallel conjunction 0x2518cf0, static_id: 2 - 11423871: cap 0: Create spark for conjunction: 0x2518cf0 spark: 0x9f - 11424136: cap 0: Start a parallel conjunction 0x2518d50, static_id: 2 - 11424316: cap 0: Create spark for conjunction: 0x2518d50 spark: 0xa0 - 11424586: cap 0: Start a parallel conjunction 0x2518db0, static_id: 2 - 11424780: cap 0: Create spark for conjunction: 0x2518db0 spark: 0xa1 - 11425050: cap 0: Start a parallel conjunction 0x2518e10, static_id: 2 - 11425234: cap 0: Create spark for conjunction: 0x2518e10 spark: 0xa2 - 11425536: cap 0: Start a parallel conjunction 0x2518e70, static_id: 2 - 11425725: cap 0: Create spark for conjunction: 0x2518e70 spark: 0xa3 - 11425995: cap 0: Start a parallel conjunction 0x2518ed0, static_id: 2 - 11426184: cap 0: Create spark for conjunction: 0x2518ed0 spark: 0xa4 - 11426458: cap 0: Start a parallel conjunction 0x2518f30, static_id: 2 - 11426643: cap 0: Create spark for conjunction: 0x2518f30 spark: 0xa5 - 11426935: cap 0: Start a parallel conjunction 0x2518f90, static_id: 2 - 11427151: cap 0: Create spark for conjunction: 0x2518f90 spark: 0xa6 - 11427466: cap 0: Start a parallel conjunction 0x2518ff0, static_id: 2 - 11427673: cap 0: Create spark for conjunction: 0x2518ff0 spark: 0xa7 - 11427952: cap 0: Start a parallel conjunction 0x2519050, static_id: 2 - 11428141: cap 0: Create spark for conjunction: 0x2519050 spark: 0xa8 - 11428429: cap 0: Start a parallel conjunction 0x25190b0, static_id: 2 - 11428609: cap 0: Create spark for conjunction: 0x25190b0 spark: 0xa9 - 11428875: cap 0: Start a parallel conjunction 0x2519110, static_id: 2 - 11429064: cap 0: Create spark for conjunction: 0x2519110 spark: 0xaa - 11429365: cap 0: Start a parallel conjunction 0x2519170, static_id: 2 - 11429554: cap 0: Create spark for conjunction: 0x2519170 spark: 0xab - 11429842: cap 0: Start a parallel conjunction 0x25191d0, static_id: 2 - 11430036: cap 0: Create spark for conjunction: 0x25191d0 spark: 0xac - 11430310: cap 0: Start a parallel conjunction 0x2519230, static_id: 2 - 11430504: cap 0: Create spark for conjunction: 0x2519230 spark: 0xad - 11430774: cap 0: Start a parallel conjunction 0x2519290, static_id: 2 - 11430954: cap 0: Create spark for conjunction: 0x2519290 spark: 0xae - 11431246: cap 0: Start a parallel conjunction 0x25192f0, static_id: 2 - 11431431: cap 0: Create spark for conjunction: 0x25192f0 spark: 0xaf - 11431696: cap 0: Start a parallel conjunction 0x2519350, static_id: 2 - 11431885: cap 0: Create spark for conjunction: 0x2519350 spark: 0xb0 - 11432164: cap 0: Start a parallel conjunction 0x25193b0, static_id: 2 - 11432358: cap 0: Create spark for conjunction: 0x25193b0 spark: 0xb1 - 11432632: cap 0: Start a parallel conjunction 0x2519410, static_id: 2 - 11432821: cap 0: Create spark for conjunction: 0x2519410 spark: 0xb2 - 11433213: cap 0: Start a parallel conjunction 0x2519470, static_id: 2 - 11433406: cap 0: Create spark for conjunction: 0x2519470 spark: 0xb3 - 11433681: cap 0: Start a parallel conjunction 0x25194d0, static_id: 2 - 11433892: cap 0: Create spark for conjunction: 0x25194d0 spark: 0xb4 - 11434185: cap 0: Start a parallel conjunction 0x2519530, static_id: 2 - 11434378: cap 0: Create spark for conjunction: 0x2519530 spark: 0xb5 - 11434657: cap 0: Start a parallel conjunction 0x2519590, static_id: 2 - 11434842: cap 0: Create spark for conjunction: 0x2519590 spark: 0xb6 - 11435107: cap 0: Start a parallel conjunction 0x25195f0, static_id: 2 - 11435323: cap 0: Create spark for conjunction: 0x25195f0 spark: 0xb7 - 11435611: cap 0: Start a parallel conjunction 0x2519650, static_id: 2 - 11435805: cap 0: Create spark for conjunction: 0x2519650 spark: 0xb8 - 11436237: cap 0: Start a parallel conjunction 0x25196b0, static_id: 2 - 11436421: cap 0: Create spark for conjunction: 0x25196b0 spark: 0xb9 - 11436682: cap 0: Start a parallel conjunction 0x2519710, static_id: 2 - 11436979: cap 0: Create spark for conjunction: 0x2519710 spark: 0xba - 11437285: cap 0: Start a parallel conjunction 0x2519770, static_id: 2 - 11437488: cap 0: Create spark for conjunction: 0x2519770 spark: 0xbb - 11437834: cap 0: Start a parallel conjunction 0x25197d0, static_id: 2 - 11438028: cap 0: Create spark for conjunction: 0x25197d0 spark: 0xbc - 11438311: cap 0: Start a parallel conjunction 0x2519830, static_id: 2 - 11438500: cap 0: Create spark for conjunction: 0x2519830 spark: 0xbd - 11438770: cap 0: Start a parallel conjunction 0x2519890, static_id: 2 - 11438959: cap 0: Create spark for conjunction: 0x2519890 spark: 0xbe - 11439243: cap 0: Start a parallel conjunction 0x25198f0, static_id: 2 - 11439432: cap 0: Create spark for conjunction: 0x25198f0 spark: 0xbf - 11439693: cap 0: Start a parallel conjunction 0x2519950, static_id: 2 - 11439886: cap 0: Create spark for conjunction: 0x2519950 spark: 0xc0 - 11440170: cap 0: Start a parallel conjunction 0x25199b0, static_id: 2 - 11440363: cap 0: Create spark for conjunction: 0x25199b0 spark: 0xc1 - 11440633: cap 0: Start a parallel conjunction 0x2519a10, static_id: 2 - 11440818: cap 0: Create spark for conjunction: 0x2519a10 spark: 0xc2 - 11441097: cap 0: Start a parallel conjunction 0x2519a70, static_id: 2 - 11441290: cap 0: Create spark for conjunction: 0x2519a70 spark: 0xc3 - 11441560: cap 0: Start a parallel conjunction 0x2519ad0, static_id: 2 - 11441749: cap 0: Create spark for conjunction: 0x2519ad0 spark: 0xc4 - 11442037: cap 0: Start a parallel conjunction 0x2519b30, static_id: 2 - 11442235: cap 0: Create spark for conjunction: 0x2519b30 spark: 0xc5 - 11442514: cap 0: Start a parallel conjunction 0x2519b90, static_id: 2 - 11442699: cap 0: Create spark for conjunction: 0x2519b90 spark: 0xc6 - 11442964: cap 0: Start a parallel conjunction 0x2519bf0, static_id: 2 - 11443167: cap 0: Create spark for conjunction: 0x2519bf0 spark: 0xc7 - 11443446: cap 0: Start a parallel conjunction 0x2519c50, static_id: 2 - 11443635: cap 0: Create spark for conjunction: 0x2519c50 spark: 0xc8 - 11444053: cap 0: Start a parallel conjunction 0x2519cb0, static_id: 2 - 11444251: cap 0: Create spark for conjunction: 0x2519cb0 spark: 0xc9 - 11444517: cap 0: Start a parallel conjunction 0x2519d10, static_id: 2 - 11444701: cap 0: Create spark for conjunction: 0x2519d10 spark: 0xca - 11444971: cap 0: Start a parallel conjunction 0x2519d70, static_id: 2 - 11445165: cap 0: Create spark for conjunction: 0x2519d70 spark: 0xcb - 11445453: cap 0: Start a parallel conjunction 0x2519dd0, static_id: 2 - 11445637: cap 0: Create spark for conjunction: 0x2519dd0 spark: 0xcc - 11445912: cap 0: Start a parallel conjunction 0x2519e30, static_id: 2 - 11446101: cap 0: Create spark for conjunction: 0x2519e30 spark: 0xcd - 11446380: cap 0: Start a parallel conjunction 0x2519e90, static_id: 2 - 11446564: cap 0: Create spark for conjunction: 0x2519e90 spark: 0xce - 11446848: cap 0: Start a parallel conjunction 0x2519ef0, static_id: 2 - 11447041: cap 0: Create spark for conjunction: 0x2519ef0 spark: 0xcf - 11447316: cap 0: Start a parallel conjunction 0x2519f50, static_id: 2 - 11447505: cap 0: Create spark for conjunction: 0x2519f50 spark: 0xd0 - 11447793: cap 0: Start a parallel conjunction 0x2519fb0, static_id: 2 - 11447991: cap 0: Create spark for conjunction: 0x2519fb0 spark: 0xd1 - 11448544: cap 0: Start a parallel conjunction 0x251a010, static_id: 2 - 11448729: cap 0: Create spark for conjunction: 0x251a010 spark: 0xd2 - 11449026: cap 0: Start a parallel conjunction 0x251a070, static_id: 2 - 11449206: cap 0: Create spark for conjunction: 0x251a070 spark: 0xd3 - 11449480: cap 0: Start a parallel conjunction 0x251a0d0, static_id: 2 - 11449678: cap 0: Create spark for conjunction: 0x251a0d0 spark: 0xd4 - 11449957: cap 0: Start a parallel conjunction 0x251a130, static_id: 2 - 11450155: cap 0: Create spark for conjunction: 0x251a130 spark: 0xd5 - 11450443: cap 0: Start a parallel conjunction 0x251a190, static_id: 2 - 11450623: cap 0: Create spark for conjunction: 0x251a190 spark: 0xd6 - 11450884: cap 0: Start a parallel conjunction 0x251a1f0, static_id: 2 - 11451087: cap 0: Create spark for conjunction: 0x251a1f0 spark: 0xd7 - 11451370: cap 0: Start a parallel conjunction 0x251a250, static_id: 2 - 11451555: cap 0: Create spark for conjunction: 0x251a250 spark: 0xd8 - 11451852: cap 0: Start a parallel conjunction 0x251a2b0, static_id: 2 - 11452041: cap 0: Create spark for conjunction: 0x251a2b0 spark: 0xd9 - 11452311: cap 0: Start a parallel conjunction 0x251a310, static_id: 2 - 11452500: cap 0: Create spark for conjunction: 0x251a310 spark: 0xda - 11452779: cap 0: Start a parallel conjunction 0x251a370, static_id: 2 - 11452968: cap 0: Create spark for conjunction: 0x251a370 spark: 0xdb - 11453247: cap 0: Start a parallel conjunction 0x251a3d0, static_id: 2 - 11453427: cap 0: Create spark for conjunction: 0x251a3d0 spark: 0xdc - 11453701: cap 0: Start a parallel conjunction 0x251a430, static_id: 2 - 11453904: cap 0: Create spark for conjunction: 0x251a430 spark: 0xdd - 11454174: cap 0: Start a parallel conjunction 0x251a490, static_id: 2 - 11454354: cap 0: Create spark for conjunction: 0x251a490 spark: 0xde - 11454637: cap 0: Start a parallel conjunction 0x251a4f0, static_id: 2 - 11454826: cap 0: Create spark for conjunction: 0x251a4f0 spark: 0xdf - 11455092: cap 0: Start a parallel conjunction 0x251a550, static_id: 2 - 11455272: cap 0: Create spark for conjunction: 0x251a550 spark: 0xe0 - 11455546: cap 0: Start a parallel conjunction 0x251a5b0, static_id: 2 - 11455731: cap 0: Create spark for conjunction: 0x251a5b0 spark: 0xe1 - 11456014: cap 0: Start a parallel conjunction 0x251a610, static_id: 2 - 11456199: cap 0: Create spark for conjunction: 0x251a610 spark: 0xe2 - 11456487: cap 0: Start a parallel conjunction 0x251a670, static_id: 2 - 11456676: cap 0: Create spark for conjunction: 0x251a670 spark: 0xe3 - 11456946: cap 0: Start a parallel conjunction 0x251a6d0, static_id: 2 - 11457148: cap 0: Create spark for conjunction: 0x251a6d0 spark: 0xe4 - 11457445: cap 0: Start a parallel conjunction 0x251a730, static_id: 2 - 11457639: cap 0: Create spark for conjunction: 0x251a730 spark: 0xe5 - 11457927: cap 0: Start a parallel conjunction 0x251a790, static_id: 2 - 11458107: cap 0: Create spark for conjunction: 0x251a790 spark: 0xe6 - 11458372: cap 0: Start a parallel conjunction 0x251a7f0, static_id: 2 - 11458566: cap 0: Create spark for conjunction: 0x251a7f0 spark: 0xe7 - 11458836: cap 0: Start a parallel conjunction 0x251a850, static_id: 2 - 11459020: cap 0: Create spark for conjunction: 0x251a850 spark: 0xe8 - 11459299: cap 0: Start a parallel conjunction 0x251a8b0, static_id: 2 - 11459493: cap 0: Create spark for conjunction: 0x251a8b0 spark: 0xe9 - 11459758: cap 0: Start a parallel conjunction 0x251a910, static_id: 2 - 11466868: cap 0: Create spark for conjunction: 0x251a910 spark: 0xea - 11467057: cap 0: Start a parallel conjunction 0x251a970, static_id: 2 - 11467179: cap 0: Create spark for conjunction: 0x251a970 spark: 0xeb - 11467372: cap 0: Start a parallel conjunction 0x251a9d0, static_id: 2 - 11467494: cap 0: Create spark for conjunction: 0x251a9d0 spark: 0xec - 11467683: cap 0: Start a parallel conjunction 0x251aa30, static_id: 2 - 11467809: cap 0: Create spark for conjunction: 0x251aa30 spark: 0xed - 11467993: cap 0: Start a parallel conjunction 0x251aa90, static_id: 2 - 11468115: cap 0: Create spark for conjunction: 0x251aa90 spark: 0xee - 11468304: cap 0: Start a parallel conjunction 0x251aaf0, static_id: 2 - 11468434: cap 0: Create spark for conjunction: 0x251aaf0 spark: 0xef - 11468619: cap 0: Start a parallel conjunction 0x251ab50, static_id: 2 - 11468740: cap 0: Create spark for conjunction: 0x251ab50 spark: 0xf0 - 11468920: cap 0: Start a parallel conjunction 0x251abb0, static_id: 2 - 11469046: cap 0: Create spark for conjunction: 0x251abb0 spark: 0xf1 - 11469226: cap 0: Start a parallel conjunction 0x251ac10, static_id: 2 - 11469348: cap 0: Create spark for conjunction: 0x251ac10 spark: 0xf2 - 11469532: cap 0: Start a parallel conjunction 0x251ac70, static_id: 2 - 11469658: cap 0: Create spark for conjunction: 0x251ac70 spark: 0xf3 - 11469834: cap 0: Start a parallel conjunction 0x251acd0, static_id: 2 - 11469960: cap 0: Create spark for conjunction: 0x251acd0 spark: 0xf4 - 11470144: cap 0: Start a parallel conjunction 0x251ad30, static_id: 2 - 11470270: cap 0: Create spark for conjunction: 0x251ad30 spark: 0xf5 - 11470464: cap 0: Start a parallel conjunction 0x251ad90, static_id: 2 - 11470585: cap 0: Create spark for conjunction: 0x251ad90 spark: 0xf6 - 11470761: cap 0: Start a parallel conjunction 0x251adf0, static_id: 2 - 11470887: cap 0: Create spark for conjunction: 0x251adf0 spark: 0xf7 - 11471071: cap 0: Start a parallel conjunction 0x251ae50, static_id: 2 - 11471193: cap 0: Create spark for conjunction: 0x251ae50 spark: 0xf8 - 11471391: cap 0: Start a parallel conjunction 0x251aeb0, static_id: 2 - 11471512: cap 0: Create spark for conjunction: 0x251aeb0 spark: 0xf9 - 11471692: cap 0: Start a parallel conjunction 0x251af10, static_id: 2 - 11471818: cap 0: Create spark for conjunction: 0x251af10 spark: 0xfa - 11472223: cap 0: Start a parallel conjunction 0x251af70, static_id: 2 - 11472349: cap 0: Create spark for conjunction: 0x251af70 spark: 0xfb - 11472718: cap 0: Start a parallel conjunction 0x251afd0, static_id: 2 - 11472844: cap 0: Create spark for conjunction: 0x251afd0 spark: 0xfc - 11473209: cap 0: Start a parallel conjunction 0x251b030, static_id: 2 - 11473339: cap 0: Create spark for conjunction: 0x251b030 spark: 0xfd - 11473524: cap 0: Start a parallel conjunction 0x251b090, static_id: 2 - 11473645: cap 0: Create spark for conjunction: 0x251b090 spark: 0xfe - 11473834: cap 0: Start a parallel conjunction 0x251b0f0, static_id: 2 - 11473956: cap 0: Create spark for conjunction: 0x251b0f0 spark: 0xff - 11474136: cap 0: Start a parallel conjunction 0x251b150, static_id: 2 - 11474257: cap 0: Create spark for conjunction: 0x251b150 spark: 0x100 - 11474446: cap 0: Start a parallel conjunction 0x251b1b0, static_id: 2 - 11497689: cap 0: Create spark for conjunction: 0x251b1b0 spark: 0x101 - 11497918: cap 0: Start a parallel conjunction 0x251b210, static_id: 2 - 11498053: cap 0: Create spark for conjunction: 0x251b210 spark: 0x102 - 11498256: cap 0: Start a parallel conjunction 0x251b270, static_id: 2 - 11498391: cap 0: Create spark for conjunction: 0x251b270 spark: 0x103 - 11498566: cap 0: Start a parallel conjunction 0x251b2d0, static_id: 2 - 11498742: cap 0: Create spark for conjunction: 0x251b2d0 spark: 0x104 - 11498926: cap 0: Start a parallel conjunction 0x251b330, static_id: 2 - 11499057: cap 0: Create spark for conjunction: 0x251b330 spark: 0x105 - 11499246: cap 0: Start a parallel conjunction 0x251b390, static_id: 2 - 11499372: cap 0: Create spark for conjunction: 0x251b390 spark: 0x106 - 11499561: cap 0: Start a parallel conjunction 0x251b3f0, static_id: 2 - 11499696: cap 0: Create spark for conjunction: 0x251b3f0 spark: 0x107 - 11499876: cap 0: Start a parallel conjunction 0x251b450, static_id: 2 - 11500042: cap 0: Create spark for conjunction: 0x251b450 spark: 0x108 - 11500245: cap 0: Start a parallel conjunction 0x251b4b0, static_id: 2 - 11500375: cap 0: Create spark for conjunction: 0x251b4b0 spark: 0x109 - 11500555: cap 0: Start a parallel conjunction 0x251b510, static_id: 2 - 11500681: cap 0: Create spark for conjunction: 0x251b510 spark: 0x10a - 11500866: cap 0: Start a parallel conjunction 0x251b570, static_id: 2 - 11500987: cap 0: Create spark for conjunction: 0x251b570 spark: 0x10b - 11501176: cap 0: Start a parallel conjunction 0x251b5d0, static_id: 2 - 11501307: cap 0: Create spark for conjunction: 0x251b5d0 spark: 0x10c - 11501496: cap 0: Start a parallel conjunction 0x251b630, static_id: 2 - 11501631: cap 0: Create spark for conjunction: 0x251b630 spark: 0x10d - 11501815: cap 0: Start a parallel conjunction 0x251b690, static_id: 2 - 11501937: cap 0: Create spark for conjunction: 0x251b690 spark: 0x10e - 11502135: cap 0: Start a parallel conjunction 0x251b6f0, static_id: 2 - 11502274: cap 0: Create spark for conjunction: 0x251b6f0 spark: 0x10f - 11502445: cap 0: Start a parallel conjunction 0x251b750, static_id: 2 - 11502567: cap 0: Create spark for conjunction: 0x251b750 spark: 0x110 - 11502769: cap 0: Start a parallel conjunction 0x251b7b0, static_id: 2 - 11502895: cap 0: Create spark for conjunction: 0x251b7b0 spark: 0x111 - 11503075: cap 0: Start a parallel conjunction 0x251b810, static_id: 2 - 11503192: cap 0: Create spark for conjunction: 0x251b810 spark: 0x112 - 11503377: cap 0: Start a parallel conjunction 0x251b870, static_id: 2 - 11503507: cap 0: Create spark for conjunction: 0x251b870 spark: 0x113 - 11503687: cap 0: Start a parallel conjunction 0x251b8d0, static_id: 2 - 11503818: cap 0: Create spark for conjunction: 0x251b8d0 spark: 0x114 - 11504007: cap 0: Start a parallel conjunction 0x251b930, static_id: 2 - 11504137: cap 0: Create spark for conjunction: 0x251b930 spark: 0x115 - 11504470: cap 0: Start a parallel conjunction 0x251b990, static_id: 2 - 11504592: cap 0: Create spark for conjunction: 0x251b990 spark: 0x116 - 11504790: cap 0: Start a parallel conjunction 0x251b9f0, static_id: 2 - 11505217: cap 0: Create spark for conjunction: 0x251b9f0 spark: 0x117 - 11505402: cap 0: Start a parallel conjunction 0x251ba50, static_id: 2 - 11505523: cap 0: Create spark for conjunction: 0x251ba50 spark: 0x118 - 11505721: cap 0: Start a parallel conjunction 0x251bab0, static_id: 2 - 11505852: cap 0: Create spark for conjunction: 0x251bab0 spark: 0x119 - 11506041: cap 0: Start a parallel conjunction 0x251bb10, static_id: 2 - 11506167: cap 0: Create spark for conjunction: 0x251bb10 spark: 0x11a - 11506369: cap 0: Start a parallel conjunction 0x251bb70, static_id: 2 - 11506500: cap 0: Create spark for conjunction: 0x251bb70 spark: 0x11b - 11506689: cap 0: Start a parallel conjunction 0x251bbd0, static_id: 2 - 11506810: cap 0: Create spark for conjunction: 0x251bbd0 spark: 0x11c - 11506990: cap 0: Start a parallel conjunction 0x251bc30, static_id: 2 - 11507130: cap 0: Create spark for conjunction: 0x251bc30 spark: 0x11d - 11507310: cap 0: Start a parallel conjunction 0x251bc90, static_id: 2 - 11507431: cap 0: Create spark for conjunction: 0x251bc90 spark: 0x11e - 11507620: cap 0: Start a parallel conjunction 0x251bcf0, static_id: 2 - 11507751: cap 0: Create spark for conjunction: 0x251bcf0 spark: 0x11f - 11507926: cap 0: Start a parallel conjunction 0x251bd50, static_id: 2 - 11508052: cap 0: Create spark for conjunction: 0x251bd50 spark: 0x120 - 11508237: cap 0: Start a parallel conjunction 0x251bdb0, static_id: 2 - 11508363: cap 0: Create spark for conjunction: 0x251bdb0 spark: 0x121 - 11508556: cap 0: Start a parallel conjunction 0x251be10, static_id: 2 - 11508682: cap 0: Create spark for conjunction: 0x251be10 spark: 0x122 - 11508889: cap 0: Start a parallel conjunction 0x251be70, static_id: 2 - 11509020: cap 0: Create spark for conjunction: 0x251be70 spark: 0x123 - 11509200: cap 0: Start a parallel conjunction 0x251bed0, static_id: 2 - 11509326: cap 0: Create spark for conjunction: 0x251bed0 spark: 0x124 - 11509510: cap 0: Start a parallel conjunction 0x251bf30, static_id: 2 - 11509636: cap 0: Create spark for conjunction: 0x251bf30 spark: 0x125 - 11509929: cap 0: Start a parallel conjunction 0x251bf90, static_id: 2 - 11510050: cap 0: Create spark for conjunction: 0x251bf90 spark: 0x126 - 11510361: cap 0: Start a parallel conjunction 0x251bff0, static_id: 2 - 11510496: cap 0: Create spark for conjunction: 0x251bff0 spark: 0x127 - 11510685: cap 0: Start a parallel conjunction 0x251c050, static_id: 2 - 11510811: cap 0: Create spark for conjunction: 0x251c050 spark: 0x128 - 11511000: cap 0: Start a parallel conjunction 0x251c0b0, static_id: 2 - 11511126: cap 0: Create spark for conjunction: 0x251c0b0 spark: 0x129 - 11511301: cap 0: Start a parallel conjunction 0x251c110, static_id: 2 - 11511427: cap 0: Create spark for conjunction: 0x251c110 spark: 0x12a - 11511612: cap 0: Start a parallel conjunction 0x251c170, static_id: 2 - 11511733: cap 0: Create spark for conjunction: 0x251c170 spark: 0x12b - 11511918: cap 0: Start a parallel conjunction 0x251c1d0, static_id: 2 - 11512039: cap 0: Create spark for conjunction: 0x251c1d0 spark: 0x12c - 11512219: cap 0: Start a parallel conjunction 0x251c230, static_id: 2 - 11512345: cap 0: Create spark for conjunction: 0x251c230 spark: 0x12d - 11512530: cap 0: Start a parallel conjunction 0x251c290, static_id: 2 - 11512647: cap 0: Create spark for conjunction: 0x251c290 spark: 0x12e - 11512939: cap 0: Start a parallel conjunction 0x251c2f0, static_id: 2 - 11513061: cap 0: Create spark for conjunction: 0x251c2f0 spark: 0x12f - 11513232: cap 0: Start a parallel conjunction 0x251c350, static_id: 2 - 11513353: cap 0: Create spark for conjunction: 0x251c350 spark: 0x130 - 11513538: cap 0: Start a parallel conjunction 0x251c3b0, static_id: 2 - 11513664: cap 0: Create spark for conjunction: 0x251c3b0 spark: 0x131 - 11513839: cap 0: Start a parallel conjunction 0x251c410, static_id: 2 - 11513961: cap 0: Create spark for conjunction: 0x251c410 spark: 0x132 - 11514267: cap 0: Start a parallel conjunction 0x251c470, static_id: 2 - 11514397: cap 0: Create spark for conjunction: 0x251c470 spark: 0x133 - 11514568: cap 0: Start a parallel conjunction 0x251c4d0, static_id: 2 - 11514699: cap 0: Create spark for conjunction: 0x251c4d0 spark: 0x134 - 11514892: cap 0: Start a parallel conjunction 0x251c530, static_id: 2 - 11515027: cap 0: Create spark for conjunction: 0x251c530 spark: 0x135 - 11515225: cap 0: Start a parallel conjunction 0x251c590, static_id: 2 - 11515351: cap 0: Create spark for conjunction: 0x251c590 spark: 0x136 - 11515531: cap 0: Start a parallel conjunction 0x251c5f0, static_id: 2 - 11515662: cap 0: Create spark for conjunction: 0x251c5f0 spark: 0x137 - 11515846: cap 0: Start a parallel conjunction 0x251c650, static_id: 2 - 11515972: cap 0: Create spark for conjunction: 0x251c650 spark: 0x138 - 11516175: cap 0: Start a parallel conjunction 0x251c6b0, static_id: 2 - 11516296: cap 0: Create spark for conjunction: 0x251c6b0 spark: 0x139 - 11516476: cap 0: Start a parallel conjunction 0x251c710, static_id: 2 - 11516598: cap 0: Create spark for conjunction: 0x251c710 spark: 0x13a - 11516782: cap 0: Start a parallel conjunction 0x251c770, static_id: 2 - 11516908: cap 0: Create spark for conjunction: 0x251c770 spark: 0x13b - 11517093: cap 0: Start a parallel conjunction 0x251c7d0, static_id: 2 - 11517214: cap 0: Create spark for conjunction: 0x251c7d0 spark: 0x13c - 11517394: cap 0: Start a parallel conjunction 0x251c830, static_id: 2 - 11517529: cap 0: Create spark for conjunction: 0x251c830 spark: 0x13d - 11517705: cap 0: Start a parallel conjunction 0x251c890, static_id: 2 - 11517826: cap 0: Create spark for conjunction: 0x251c890 spark: 0x13e - 11518011: cap 0: Start a parallel conjunction 0x251c8f0, static_id: 2 - 11518141: cap 0: Create spark for conjunction: 0x251c8f0 spark: 0x13f - 11518317: cap 0: Start a parallel conjunction 0x251c950, static_id: 2 - 11518443: cap 0: Create spark for conjunction: 0x251c950 spark: 0x140 - 11518627: cap 0: Start a parallel conjunction 0x251c9b0, static_id: 2 - 11518758: cap 0: Create spark for conjunction: 0x251c9b0 spark: 0x141 - 11518942: cap 0: Start a parallel conjunction 0x251ca10, static_id: 2 - 11519068: cap 0: Create spark for conjunction: 0x251ca10 spark: 0x142 - 11519257: cap 0: Start a parallel conjunction 0x251ca70, static_id: 2 - 11519383: cap 0: Create spark for conjunction: 0x251ca70 spark: 0x143 - 11519563: cap 0: Start a parallel conjunction 0x251cad0, static_id: 2 - 11519694: cap 0: Create spark for conjunction: 0x251cad0 spark: 0x144 - 11519878: cap 0: Start a parallel conjunction 0x251cb30, static_id: 2 - 11520009: cap 0: Create spark for conjunction: 0x251cb30 spark: 0x145 - 11520198: cap 0: Start a parallel conjunction 0x251cb90, static_id: 2 - 11520319: cap 0: Create spark for conjunction: 0x251cb90 spark: 0x146 - 11520490: cap 0: Start a parallel conjunction 0x251cbf0, static_id: 2 - 11520621: cap 0: Create spark for conjunction: 0x251cbf0 spark: 0x147 - 11520801: cap 0: Start a parallel conjunction 0x251cc50, static_id: 2 - 11520922: cap 0: Create spark for conjunction: 0x251cc50 spark: 0x148 - 11521111: cap 0: Start a parallel conjunction 0x251ccb0, static_id: 2 - 11521251: cap 0: Create spark for conjunction: 0x251ccb0 spark: 0x149 - 11521422: cap 0: Start a parallel conjunction 0x251cd10, static_id: 2 - 11521548: cap 0: Create spark for conjunction: 0x251cd10 spark: 0x14a - 11521741: cap 0: Start a parallel conjunction 0x251cd70, static_id: 2 - 11521876: cap 0: Create spark for conjunction: 0x251cd70 spark: 0x14b - 11522065: cap 0: Start a parallel conjunction 0x251cdd0, static_id: 2 - 11522187: cap 0: Create spark for conjunction: 0x251cdd0 spark: 0x14c - 11522371: cap 0: Start a parallel conjunction 0x251ce30, static_id: 2 - 11522506: cap 0: Create spark for conjunction: 0x251ce30 spark: 0x14d - 11522686: cap 0: Start a parallel conjunction 0x251ce90, static_id: 2 - 11522808: cap 0: Create spark for conjunction: 0x251ce90 spark: 0x14e - 11522992: cap 0: Start a parallel conjunction 0x251cef0, static_id: 2 - 11523118: cap 0: Create spark for conjunction: 0x251cef0 spark: 0x14f - 11523298: cap 0: Start a parallel conjunction 0x251cf50, static_id: 2 - 11523424: cap 0: Create spark for conjunction: 0x251cf50 spark: 0x150 - 11523609: cap 0: Start a parallel conjunction 0x251cfb0, static_id: 2 - 11523739: cap 0: Create spark for conjunction: 0x251cfb0 spark: 0x151 - 11524059: cap 0: Start a parallel conjunction 0x251d010, static_id: 2 - 11524180: cap 0: Create spark for conjunction: 0x251d010 spark: 0x152 - 11524378: cap 0: Start a parallel conjunction 0x251d070, static_id: 2 - 11524518: cap 0: Create spark for conjunction: 0x251d070 spark: 0x153 - 11524698: cap 0: Start a parallel conjunction 0x251d0d0, static_id: 2 - 11524828: cap 0: Create spark for conjunction: 0x251d0d0 spark: 0x154 - 11525013: cap 0: Start a parallel conjunction 0x251d130, static_id: 2 - 11525134: cap 0: Create spark for conjunction: 0x251d130 spark: 0x155 - 11525319: cap 0: Start a parallel conjunction 0x251d190, static_id: 2 - 11525449: cap 0: Create spark for conjunction: 0x251d190 spark: 0x156 - 11525625: cap 0: Start a parallel conjunction 0x251d1f0, static_id: 2 - 11525760: cap 0: Create spark for conjunction: 0x251d1f0 spark: 0x157 - 11525940: cap 0: Start a parallel conjunction 0x251d250, static_id: 2 - 11526061: cap 0: Create spark for conjunction: 0x251d250 spark: 0x158 - 11526250: cap 0: Start a parallel conjunction 0x251d2b0, static_id: 2 - 11526381: cap 0: Create spark for conjunction: 0x251d2b0 spark: 0x159 - 11526556: cap 0: Start a parallel conjunction 0x251d310, static_id: 2 - 11526678: cap 0: Create spark for conjunction: 0x251d310 spark: 0x15a - 11527038: cap 0: Start a parallel conjunction 0x251d370, static_id: 2 - 11527168: cap 0: Create spark for conjunction: 0x251d370 spark: 0x15b - 11527357: cap 0: Start a parallel conjunction 0x251d3d0, static_id: 2 - 11527479: cap 0: Create spark for conjunction: 0x251d3d0 spark: 0x15c - 11527659: cap 0: Start a parallel conjunction 0x251d430, static_id: 2 - 11527794: cap 0: Create spark for conjunction: 0x251d430 spark: 0x15d - 11527974: cap 0: Start a parallel conjunction 0x251d490, static_id: 2 - 11528095: cap 0: Create spark for conjunction: 0x251d490 spark: 0x15e - 11528293: cap 0: Start a parallel conjunction 0x251d4f0, static_id: 2 - 11528424: cap 0: Create spark for conjunction: 0x251d4f0 spark: 0x15f - 11528608: cap 0: Start a parallel conjunction 0x251d550, static_id: 2 - 11528730: cap 0: Create spark for conjunction: 0x251d550 spark: 0x160 - 11528914: cap 0: Start a parallel conjunction 0x251d5b0, static_id: 2 - 11529049: cap 0: Create spark for conjunction: 0x251d5b0 spark: 0x161 - 11529234: cap 0: Start a parallel conjunction 0x251d610, static_id: 2 - 11529355: cap 0: Create spark for conjunction: 0x251d610 spark: 0x162 - 11529567: cap 0: Start a parallel conjunction 0x251d670, static_id: 2 - 11529693: cap 0: Create spark for conjunction: 0x251d670 spark: 0x163 - 11529877: cap 0: Start a parallel conjunction 0x251d6d0, static_id: 2 - 11530003: cap 0: Create spark for conjunction: 0x251d6d0 spark: 0x164 - 11530197: cap 0: Start a parallel conjunction 0x251d730, static_id: 2 - 11530323: cap 0: Create spark for conjunction: 0x251d730 spark: 0x165 - 11530512: cap 0: Start a parallel conjunction 0x251d790, static_id: 2 - 11530633: cap 0: Create spark for conjunction: 0x251d790 spark: 0x166 - 11530809: cap 0: Start a parallel conjunction 0x251d7f0, static_id: 2 - 11530944: cap 0: Create spark for conjunction: 0x251d7f0 spark: 0x167 - 11531124: cap 0: Start a parallel conjunction 0x251d850, static_id: 2 - 11531245: cap 0: Create spark for conjunction: 0x251d850 spark: 0x168 - 11531430: cap 0: Start a parallel conjunction 0x251d8b0, static_id: 2 - 11531556: cap 0: Create spark for conjunction: 0x251d8b0 spark: 0x169 - 11531731: cap 0: Start a parallel conjunction 0x251d910, static_id: 2 - 11531853: cap 0: Create spark for conjunction: 0x251d910 spark: 0x16a - 11532033: cap 0: Start a parallel conjunction 0x251d970, static_id: 2 - 11532163: cap 0: Create spark for conjunction: 0x251d970 spark: 0x16b - 11532348: cap 0: Start a parallel conjunction 0x251d9d0, static_id: 2 - 11532469: cap 0: Create spark for conjunction: 0x251d9d0 spark: 0x16c - 11532649: cap 0: Start a parallel conjunction 0x251da30, static_id: 2 - 11532784: cap 0: Create spark for conjunction: 0x251da30 spark: 0x16d - 11532969: cap 0: Start a parallel conjunction 0x251da90, static_id: 2 - 11533090: cap 0: Create spark for conjunction: 0x251da90 spark: 0x16e - 11533279: cap 0: Start a parallel conjunction 0x251daf0, static_id: 2 - 11533405: cap 0: Create spark for conjunction: 0x251daf0 spark: 0x16f - 11533590: cap 0: Start a parallel conjunction 0x251db50, static_id: 2 - 11533711: cap 0: Create spark for conjunction: 0x251db50 spark: 0x170 - 11533887: cap 0: Start a parallel conjunction 0x251dbb0, static_id: 2 - 11534017: cap 0: Create spark for conjunction: 0x251dbb0 spark: 0x171 - 11534202: cap 0: Start a parallel conjunction 0x251dc10, static_id: 2 - 11534323: cap 0: Create spark for conjunction: 0x251dc10 spark: 0x172 - 11534656: cap 0: Start a parallel conjunction 0x251dc70, static_id: 2 - 11534787: cap 0: Create spark for conjunction: 0x251dc70 spark: 0x173 - 11534962: cap 0: Start a parallel conjunction 0x251dcd0, static_id: 2 - 11535309: cap 0: Create spark for conjunction: 0x251dcd0 spark: 0x174 - 11535507: cap 0: Start a parallel conjunction 0x251dd30, static_id: 2 - 11535633: cap 0: Create spark for conjunction: 0x251dd30 spark: 0x175 - 11535817: cap 0: Start a parallel conjunction 0x251dd90, static_id: 2 - 11535939: cap 0: Create spark for conjunction: 0x251dd90 spark: 0x176 - 11536114: cap 0: Start a parallel conjunction 0x251ddf0, static_id: 2 - 11536249: cap 0: Create spark for conjunction: 0x251ddf0 spark: 0x177 - 11536443: cap 0: Start a parallel conjunction 0x251de50, static_id: 2 - 11536569: cap 0: Create spark for conjunction: 0x251de50 spark: 0x178 - 11536771: cap 0: Start a parallel conjunction 0x251deb0, static_id: 2 - 11536902: cap 0: Create spark for conjunction: 0x251deb0 spark: 0x179 - 11537091: cap 0: Start a parallel conjunction 0x251df10, static_id: 2 - 11537212: cap 0: Create spark for conjunction: 0x251df10 spark: 0x17a - 11537397: cap 0: Start a parallel conjunction 0x251df70, static_id: 2 - 11537523: cap 0: Create spark for conjunction: 0x251df70 spark: 0x17b - 11537820: cap 0: Start a parallel conjunction 0x251dfd0, static_id: 2 - 11537941: cap 0: Create spark for conjunction: 0x251dfd0 spark: 0x17c - 11538261: cap 0: Start a parallel conjunction 0x251e030, static_id: 2 - 11538396: cap 0: Create spark for conjunction: 0x251e030 spark: 0x17d - 11538576: cap 0: Start a parallel conjunction 0x251e090, static_id: 2 - 11538697: cap 0: Create spark for conjunction: 0x251e090 spark: 0x17e - 11538882: cap 0: Start a parallel conjunction 0x251e0f0, static_id: 2 - 11539012: cap 0: Create spark for conjunction: 0x251e0f0 spark: 0x17f - 11539188: cap 0: Start a parallel conjunction 0x251e150, static_id: 2 - 11539314: cap 0: Create spark for conjunction: 0x251e150 spark: 0x180 - 11539507: cap 0: Start a parallel conjunction 0x251e1b0, static_id: 2 - 11539638: cap 0: Create spark for conjunction: 0x251e1b0 spark: 0x181 - 11539822: cap 0: Start a parallel conjunction 0x251e210, static_id: 2 - 11539944: cap 0: Create spark for conjunction: 0x251e210 spark: 0x182 - 11540137: cap 0: Start a parallel conjunction 0x251e270, static_id: 2 - 11540272: cap 0: Create spark for conjunction: 0x251e270 spark: 0x183 - 11540448: cap 0: Start a parallel conjunction 0x251e2d0, static_id: 2 - 11540614: cap 0: Create spark for conjunction: 0x251e2d0 spark: 0x184 - 11540803: cap 0: Start a parallel conjunction 0x251e330, static_id: 2 - 11540929: cap 0: Create spark for conjunction: 0x251e330 spark: 0x185 - 11541118: cap 0: Start a parallel conjunction 0x251e390, static_id: 2 - 11541240: cap 0: Create spark for conjunction: 0x251e390 spark: 0x186 - 11541577: cap 0: Start a parallel conjunction 0x251e3f0, static_id: 2 - 11541712: cap 0: Create spark for conjunction: 0x251e3f0 spark: 0x187 - 11541897: cap 0: Start a parallel conjunction 0x251e450, static_id: 2 - 11542059: cap 0: Create spark for conjunction: 0x251e450 spark: 0x188 - 11542261: cap 0: Start a parallel conjunction 0x251e4b0, static_id: 2 - 11542383: cap 0: Create spark for conjunction: 0x251e4b0 spark: 0x189 - 11542558: cap 0: Start a parallel conjunction 0x251e510, static_id: 2 - 11542680: cap 0: Create spark for conjunction: 0x251e510 spark: 0x18a - 11542864: cap 0: Start a parallel conjunction 0x251e570, static_id: 2 - 11542990: cap 0: Create spark for conjunction: 0x251e570 spark: 0x18b - 11543175: cap 0: Start a parallel conjunction 0x251e5d0, static_id: 2 - 11543296: cap 0: Create spark for conjunction: 0x251e5d0 spark: 0x18c - 11543476: cap 0: Start a parallel conjunction 0x251e630, static_id: 2 - 11543620: cap 0: Create spark for conjunction: 0x251e630 spark: 0x18d - 11543800: cap 0: Start a parallel conjunction 0x251e690, static_id: 2 - 11543922: cap 0: Create spark for conjunction: 0x251e690 spark: 0x18e - 11544111: cap 0: Start a parallel conjunction 0x251e6f0, static_id: 2 - 11544241: cap 0: Create spark for conjunction: 0x251e6f0 spark: 0x18f - 11544417: cap 0: Start a parallel conjunction 0x251e750, static_id: 2 - 11544547: cap 0: Create spark for conjunction: 0x251e750 spark: 0x190 - 11544732: cap 0: Start a parallel conjunction 0x251e7b0, static_id: 2 - 11544858: cap 0: Create spark for conjunction: 0x251e7b0 spark: 0x191 - 11545042: cap 0: Start a parallel conjunction 0x251e810, static_id: 2 - 11545164: cap 0: Create spark for conjunction: 0x251e810 spark: 0x192 - 11545353: cap 0: Start a parallel conjunction 0x251e870, static_id: 2 - 11545479: cap 0: Create spark for conjunction: 0x251e870 spark: 0x193 - 11545659: cap 0: Start a parallel conjunction 0x251e8d0, static_id: 2 - 11545785: cap 0: Create spark for conjunction: 0x251e8d0 spark: 0x194 - 11545974: cap 0: Start a parallel conjunction 0x251e930, static_id: 2 - 11546100: cap 0: Create spark for conjunction: 0x251e930 spark: 0x195 - 11546293: cap 0: Start a parallel conjunction 0x251e990, static_id: 2 - 11546415: cap 0: Create spark for conjunction: 0x251e990 spark: 0x196 - 11546590: cap 0: Start a parallel conjunction 0x251e9f0, static_id: 2 - 11546725: cap 0: Create spark for conjunction: 0x251e9f0 spark: 0x197 - 11546910: cap 0: Start a parallel conjunction 0x251ea50, static_id: 2 - 11547036: cap 0: Create spark for conjunction: 0x251ea50 spark: 0x198 - 11547243: cap 0: Start a parallel conjunction 0x251eab0, static_id: 2 - 11547378: cap 0: Create spark for conjunction: 0x251eab0 spark: 0x199 - 11547562: cap 0: Start a parallel conjunction 0x251eb10, static_id: 2 - 11547684: cap 0: Create spark for conjunction: 0x251eb10 spark: 0x19a - 11547868: cap 0: Start a parallel conjunction 0x251eb70, static_id: 2 - 11547990: cap 0: Create spark for conjunction: 0x251eb70 spark: 0x19b - 11548174: cap 0: Start a parallel conjunction 0x251ebd0, static_id: 2 - 11548296: cap 0: Create spark for conjunction: 0x251ebd0 spark: 0x19c - 11548476: cap 0: Start a parallel conjunction 0x251ec30, static_id: 2 - 11548602: cap 0: Create spark for conjunction: 0x251ec30 spark: 0x19d - 11548782: cap 0: Start a parallel conjunction 0x251ec90, static_id: 2 - 11548903: cap 0: Create spark for conjunction: 0x251ec90 spark: 0x19e - 11549092: cap 0: Start a parallel conjunction 0x251ecf0, static_id: 2 - 11549223: cap 0: Create spark for conjunction: 0x251ecf0 spark: 0x19f - 11549403: cap 0: Start a parallel conjunction 0x251ed50, static_id: 2 - 11549524: cap 0: Create spark for conjunction: 0x251ed50 spark: 0x1a0 - 11549709: cap 0: Start a parallel conjunction 0x251edb0, static_id: 2 - 11549839: cap 0: Create spark for conjunction: 0x251edb0 spark: 0x1a1 - 11550019: cap 0: Start a parallel conjunction 0x251ee10, static_id: 2 - 11550141: cap 0: Create spark for conjunction: 0x251ee10 spark: 0x1a2 - 11550330: cap 0: Start a parallel conjunction 0x251ee70, static_id: 2 - 11550465: cap 0: Create spark for conjunction: 0x251ee70 spark: 0x1a3 - 11550658: cap 0: Start a parallel conjunction 0x251eed0, static_id: 2 - 11550784: cap 0: Create spark for conjunction: 0x251eed0 spark: 0x1a4 - 11550982: cap 0: Start a parallel conjunction 0x251ef30, static_id: 2 - 11551108: cap 0: Create spark for conjunction: 0x251ef30 spark: 0x1a5 - 11551293: cap 0: Start a parallel conjunction 0x251ef90, static_id: 2 - 11551419: cap 0: Create spark for conjunction: 0x251ef90 spark: 0x1a6 - 11551752: cap 0: Start a parallel conjunction 0x251eff0, static_id: 2 - 11551887: cap 0: Create spark for conjunction: 0x251eff0 spark: 0x1a7 - 11552076: cap 0: Start a parallel conjunction 0x251f050, static_id: 2 - 11552197: cap 0: Create spark for conjunction: 0x251f050 spark: 0x1a8 - 11552386: cap 0: Start a parallel conjunction 0x251f0b0, static_id: 2 - 11552517: cap 0: Create spark for conjunction: 0x251f0b0 spark: 0x1a9 - 11552755: cap 0: Start a parallel conjunction 0x251f110, static_id: 2 - 11552886: cap 0: Create spark for conjunction: 0x251f110 spark: 0x1aa - 11553066: cap 0: Start a parallel conjunction 0x251f170, static_id: 2 - 11553196: cap 0: Create spark for conjunction: 0x251f170 spark: 0x1ab - 11553390: cap 0: Start a parallel conjunction 0x251f1d0, static_id: 2 - 11553511: cap 0: Create spark for conjunction: 0x251f1d0 spark: 0x1ac - 11553696: cap 0: Start a parallel conjunction 0x251f230, static_id: 2 - 11553835: cap 0: Create spark for conjunction: 0x251f230 spark: 0x1ad - 11554015: cap 0: Start a parallel conjunction 0x251f290, static_id: 2 - 11554146: cap 0: Create spark for conjunction: 0x251f290 spark: 0x1ae - 11554330: cap 0: Start a parallel conjunction 0x251f2f0, static_id: 2 - 11554465: cap 0: Create spark for conjunction: 0x251f2f0 spark: 0x1af - 11554645: cap 0: Start a parallel conjunction 0x251f350, static_id: 2 - 11554767: cap 0: Create spark for conjunction: 0x251f350 spark: 0x1b0 - 11554956: cap 0: Start a parallel conjunction 0x251f3b0, static_id: 2 - 11555082: cap 0: Create spark for conjunction: 0x251f3b0 spark: 0x1b1 - 11555262: cap 0: Start a parallel conjunction 0x251f410, static_id: 2 - 11555383: cap 0: Create spark for conjunction: 0x251f410 spark: 0x1b2 - 11555662: cap 0: Start a parallel conjunction 0x251f470, static_id: 2 - 11555788: cap 0: Create spark for conjunction: 0x251f470 spark: 0x1b3 - 11555964: cap 0: Start a parallel conjunction 0x251f4d0, static_id: 2 - 11556090: cap 0: Create spark for conjunction: 0x251f4d0 spark: 0x1b4 - 11556270: cap 0: Start a parallel conjunction 0x251f530, static_id: 2 - 11556391: cap 0: Create spark for conjunction: 0x251f530 spark: 0x1b5 - 11556576: cap 0: Start a parallel conjunction 0x251f590, static_id: 2 - 11556697: cap 0: Create spark for conjunction: 0x251f590 spark: 0x1b6 - 11556877: cap 0: Start a parallel conjunction 0x251f5f0, static_id: 2 - 11557008: cap 0: Create spark for conjunction: 0x251f5f0 spark: 0x1b7 - 11557188: cap 0: Start a parallel conjunction 0x251f650, static_id: 2 - 11557309: cap 0: Create spark for conjunction: 0x251f650 spark: 0x1b8 - 11557503: cap 0: Start a parallel conjunction 0x251f6b0, static_id: 2 - 11557638: cap 0: Create spark for conjunction: 0x251f6b0 spark: 0x1b9 - 11557818: cap 0: Start a parallel conjunction 0x251f710, static_id: 2 - 11557944: cap 0: Create spark for conjunction: 0x251f710 spark: 0x1ba - 11558137: cap 0: Start a parallel conjunction 0x251f770, static_id: 2 - 11558268: cap 0: Create spark for conjunction: 0x251f770 spark: 0x1bb - 11558452: cap 0: Start a parallel conjunction 0x251f7d0, static_id: 2 - 11558578: cap 0: Create spark for conjunction: 0x251f7d0 spark: 0x1bc - 11558754: cap 0: Start a parallel conjunction 0x251f830, static_id: 2 - 11558893: cap 0: Create spark for conjunction: 0x251f830 spark: 0x1bd - 11559069: cap 0: Start a parallel conjunction 0x251f890, static_id: 2 - 11559190: cap 0: Create spark for conjunction: 0x251f890 spark: 0x1be - 11559375: cap 0: Start a parallel conjunction 0x251f8f0, static_id: 2 - 11559505: cap 0: Create spark for conjunction: 0x251f8f0 spark: 0x1bf - 11559681: cap 0: Start a parallel conjunction 0x251f950, static_id: 2 - 11559802: cap 0: Create spark for conjunction: 0x251f950 spark: 0x1c0 - 11559982: cap 0: Start a parallel conjunction 0x251f9b0, static_id: 2 - 11560099: cap 0: Create spark for conjunction: 0x251f9b0 spark: 0x1c1 - 11560279: cap 0: Start a parallel conjunction 0x251fa10, static_id: 2 - 11560396: cap 0: Create spark for conjunction: 0x251fa10 spark: 0x1c2 - 11560581: cap 0: Start a parallel conjunction 0x251fa70, static_id: 2 - 11560711: cap 0: Create spark for conjunction: 0x251fa70 spark: 0x1c3 - 11560896: cap 0: Start a parallel conjunction 0x251fad0, static_id: 2 - 11561026: cap 0: Create spark for conjunction: 0x251fad0 spark: 0x1c4 - 11561215: cap 0: Start a parallel conjunction 0x251fb30, static_id: 2 - 11561350: cap 0: Create spark for conjunction: 0x251fb30 spark: 0x1c5 - 11561539: cap 0: Start a parallel conjunction 0x251fb90, static_id: 2 - 11561665: cap 0: Create spark for conjunction: 0x251fb90 spark: 0x1c6 - 11561836: cap 0: Start a parallel conjunction 0x251fbf0, static_id: 2 - 11561971: cap 0: Create spark for conjunction: 0x251fbf0 spark: 0x1c7 - 11562151: cap 0: Start a parallel conjunction 0x251fc50, static_id: 2 - 11562277: cap 0: Create spark for conjunction: 0x251fc50 spark: 0x1c8 - 11562466: cap 0: Start a parallel conjunction 0x251fcb0, static_id: 2 - 11562606: cap 0: Create spark for conjunction: 0x251fcb0 spark: 0x1c9 - 11562781: cap 0: Start a parallel conjunction 0x251fd10, static_id: 2 - 11562907: cap 0: Create spark for conjunction: 0x251fd10 spark: 0x1ca - 11563087: cap 0: Start a parallel conjunction 0x251fd70, static_id: 2 - 11563209: cap 0: Create spark for conjunction: 0x251fd70 spark: 0x1cb - 11563402: cap 0: Start a parallel conjunction 0x251fdd0, static_id: 2 - 11563524: cap 0: Create spark for conjunction: 0x251fdd0 spark: 0x1cc - 11563713: cap 0: Start a parallel conjunction 0x251fe30, static_id: 2 - 11563848: cap 0: Create spark for conjunction: 0x251fe30 spark: 0x1cd - 11564032: cap 0: Start a parallel conjunction 0x251fe90, static_id: 2 - 11564154: cap 0: Create spark for conjunction: 0x251fe90 spark: 0x1ce - 11564338: cap 0: Start a parallel conjunction 0x251fef0, static_id: 2 - 11564469: cap 0: Create spark for conjunction: 0x251fef0 spark: 0x1cf - 11564640: cap 0: Start a parallel conjunction 0x251ff50, static_id: 2 - 11564874: cap 0: Create spark for conjunction: 0x251ff50 spark: 0x1d0 - 11565175: cap 0: Start a parallel conjunction 0x251ffb0, static_id: 2 - 11565301: cap 0: Create spark for conjunction: 0x251ffb0 spark: 0x1d1 - 11565711: cap 0: Start a parallel conjunction 0x2520010, static_id: 2 - 11565832: cap 0: Create spark for conjunction: 0x2520010 spark: 0x1d2 - 11566026: cap 0: Start a parallel conjunction 0x2520070, static_id: 2 - 11566152: cap 0: Create spark for conjunction: 0x2520070 spark: 0x1d3 - 11566327: cap 0: Start a parallel conjunction 0x25200d0, static_id: 2 - 11566453: cap 0: Create spark for conjunction: 0x25200d0 spark: 0x1d4 - 11566638: cap 0: Start a parallel conjunction 0x2520130, static_id: 2 - 11566768: cap 0: Create spark for conjunction: 0x2520130 spark: 0x1d5 - 11566966: cap 0: Start a parallel conjunction 0x2520190, static_id: 2 - 11567088: cap 0: Create spark for conjunction: 0x2520190 spark: 0x1d6 - 11567461: cap 0: Start a parallel conjunction 0x25201f0, static_id: 2 - 11567596: cap 0: Create spark for conjunction: 0x25201f0 spark: 0x1d7 - 11567781: cap 0: Start a parallel conjunction 0x2520250, static_id: 2 - 11567907: cap 0: Create spark for conjunction: 0x2520250 spark: 0x1d8 - 11568105: cap 0: Start a parallel conjunction 0x25202b0, static_id: 2 - 11568226: cap 0: Create spark for conjunction: 0x25202b0 spark: 0x1d9 - 11568397: cap 0: Start a parallel conjunction 0x2520310, static_id: 2 - 11568523: cap 0: Create spark for conjunction: 0x2520310 spark: 0x1da - 11568708: cap 0: Start a parallel conjunction 0x2520370, static_id: 2 - 11568834: cap 0: Create spark for conjunction: 0x2520370 spark: 0x1db - 11569018: cap 0: Start a parallel conjunction 0x25203d0, static_id: 2 - 11569140: cap 0: Create spark for conjunction: 0x25203d0 spark: 0x1dc - 11569320: cap 0: Start a parallel conjunction 0x2520430, static_id: 2 - 11569455: cap 0: Create spark for conjunction: 0x2520430 spark: 0x1dd - 11569630: cap 0: Start a parallel conjunction 0x2520490, static_id: 2 - 11569752: cap 0: Create spark for conjunction: 0x2520490 spark: 0x1de - 11569936: cap 0: Start a parallel conjunction 0x25204f0, static_id: 2 - 11570067: cap 0: Create spark for conjunction: 0x25204f0 spark: 0x1df - 11570242: cap 0: Start a parallel conjunction 0x2520550, static_id: 2 - 11570364: cap 0: Create spark for conjunction: 0x2520550 spark: 0x1e0 - 11570544: cap 0: Start a parallel conjunction 0x25205b0, static_id: 2 - 11570670: cap 0: Create spark for conjunction: 0x25205b0 spark: 0x1e1 - 11570850: cap 0: Start a parallel conjunction 0x2520610, static_id: 2 - 11570971: cap 0: Create spark for conjunction: 0x2520610 spark: 0x1e2 - 11571160: cap 0: Start a parallel conjunction 0x2520670, static_id: 2 - 11571295: cap 0: Create spark for conjunction: 0x2520670 spark: 0x1e3 - 11571466: cap 0: Start a parallel conjunction 0x25206d0, static_id: 2 - 11571601: cap 0: Create spark for conjunction: 0x25206d0 spark: 0x1e4 - 11571795: cap 0: Start a parallel conjunction 0x2520730, static_id: 2 - 11571921: cap 0: Create spark for conjunction: 0x2520730 spark: 0x1e5 - 11572114: cap 0: Start a parallel conjunction 0x2520790, static_id: 2 - 11572240: cap 0: Create spark for conjunction: 0x2520790 spark: 0x1e6 - 11572416: cap 0: Start a parallel conjunction 0x25207f0, static_id: 2 - 11572546: cap 0: Create spark for conjunction: 0x25207f0 spark: 0x1e7 - 11572735: cap 0: Start a parallel conjunction 0x2520850, static_id: 2 - 11572861: cap 0: Create spark for conjunction: 0x2520850 spark: 0x1e8 - 11573055: cap 0: Start a parallel conjunction 0x25208b0, static_id: 2 - 11573190: cap 0: Create spark for conjunction: 0x25208b0 spark: 0x1e9 - 11573365: cap 0: Start a parallel conjunction 0x2520910, static_id: 2 - 11573487: cap 0: Create spark for conjunction: 0x2520910 spark: 0x1ea - 11573676: cap 0: Start a parallel conjunction 0x2520970, static_id: 2 - 11573802: cap 0: Create spark for conjunction: 0x2520970 spark: 0x1eb - 11573986: cap 0: Start a parallel conjunction 0x25209d0, static_id: 2 - 11574112: cap 0: Create spark for conjunction: 0x25209d0 spark: 0x1ec - 11574288: cap 0: Start a parallel conjunction 0x2520a30, static_id: 2 - 11574427: cap 0: Create spark for conjunction: 0x2520a30 spark: 0x1ed - 11574603: cap 0: Start a parallel conjunction 0x2520a90, static_id: 2 - 11574724: cap 0: Create spark for conjunction: 0x2520a90 spark: 0x1ee - 11574909: cap 0: Start a parallel conjunction 0x2520af0, static_id: 2 - 11575039: cap 0: Create spark for conjunction: 0x2520af0 spark: 0x1ef - 11575219: cap 0: Start a parallel conjunction 0x2520b50, static_id: 2 - 11575341: cap 0: Create spark for conjunction: 0x2520b50 spark: 0x1f0 - 11575521: cap 0: Start a parallel conjunction 0x2520bb0, static_id: 2 - 11575647: cap 0: Create spark for conjunction: 0x2520bb0 spark: 0x1f1 - 11575827: cap 0: Start a parallel conjunction 0x2520c10, static_id: 2 - 11575948: cap 0: Create spark for conjunction: 0x2520c10 spark: 0x1f2 - 11576137: cap 0: Start a parallel conjunction 0x2520c70, static_id: 2 - 11576277: cap 0: Create spark for conjunction: 0x2520c70 spark: 0x1f3 - 11576452: cap 0: Start a parallel conjunction 0x2520cd0, static_id: 2 - 11576578: cap 0: Create spark for conjunction: 0x2520cd0 spark: 0x1f4 - 11576772: cap 0: Start a parallel conjunction 0x2520d30, static_id: 2 - 11576898: cap 0: Create spark for conjunction: 0x2520d30 spark: 0x1f5 - 11577087: cap 0: Start a parallel conjunction 0x2520d90, static_id: 2 - 11577208: cap 0: Create spark for conjunction: 0x2520d90 spark: 0x1f6 - 11577393: cap 0: Start a parallel conjunction 0x2520df0, static_id: 2 - 11577523: cap 0: Create spark for conjunction: 0x2520df0 spark: 0x1f7 - 11577712: cap 0: Start a parallel conjunction 0x2520e50, static_id: 2 - 11577834: cap 0: Create spark for conjunction: 0x2520e50 spark: 0x1f8 - 11578032: cap 0: Start a parallel conjunction 0x2520eb0, static_id: 2 - 11578153: cap 0: Create spark for conjunction: 0x2520eb0 spark: 0x1f9 - 11578324: cap 0: Start a parallel conjunction 0x2520f10, static_id: 2 - 11578450: cap 0: Create spark for conjunction: 0x2520f10 spark: 0x1fa - 11578635: cap 0: Start a parallel conjunction 0x2520f70, static_id: 2 - 11578765: cap 0: Create spark for conjunction: 0x2520f70 spark: 0x1fb - 11579089: cap 0: Start a parallel conjunction 0x2520fd0, static_id: 2 - 11579211: cap 0: Create spark for conjunction: 0x2520fd0 spark: 0x1fc - 11579530: cap 0: Start a parallel conjunction 0x2521030, static_id: 2 - 11579670: cap 0: Create spark for conjunction: 0x2521030 spark: 0x1fd - 11579850: cap 0: Start a parallel conjunction 0x2521090, static_id: 2 - 11579971: cap 0: Create spark for conjunction: 0x2521090 spark: 0x1fe - 11580160: cap 0: Start a parallel conjunction 0x25210f0, static_id: 2 - 11580291: cap 0: Create spark for conjunction: 0x25210f0 spark: 0x1ff - 11580466: cap 0: Start a parallel conjunction 0x2521150, static_id: 2 - 11580588: cap 0: Create spark for conjunction: 0x2521150 spark: 0x200 - 11580772: cap 0: Start a parallel conjunction 0x25211b0, static_id: 2 - 11625201: cap 1: Trying to steal a spark - 11626915: cap 1: stealing a spark from cap 0 - 11631217: cap 0: Create spark for conjunction: 0x25211b0 spark: 0x201 - 11631456: cap 0: Start a parallel conjunction 0x2521210, static_id: 2 - 11631586: cap 0: Create spark for conjunction: 0x2521210 spark: 0x202 - 11631789: cap 0: Start a parallel conjunction 0x2521270, static_id: 2 - 11631924: cap 0: Create spark for conjunction: 0x2521270 spark: 0x203 - 11632104: cap 0: Start a parallel conjunction 0x25212d0, static_id: 2 - 11632243: cap 0: Create spark for conjunction: 0x25212d0 spark: 0x204 - 11632437: cap 0: Start a parallel conjunction 0x2521330, static_id: 2 - 11632567: cap 0: Create spark for conjunction: 0x2521330 spark: 0x205 - 11632756: cap 0: Start a parallel conjunction 0x2521390, static_id: 2 - 11632882: cap 0: Create spark for conjunction: 0x2521390 spark: 0x206 - 11633062: cap 0: Start a parallel conjunction 0x25213f0, static_id: 2 - 11633206: cap 0: Create spark for conjunction: 0x25213f0 spark: 0x207 - 11633395: cap 0: Start a parallel conjunction 0x2521450, static_id: 2 - 11633526: cap 0: Create spark for conjunction: 0x2521450 spark: 0x208 - 11633737: cap 0: Start a parallel conjunction 0x25214b0, static_id: 2 - 11633872: cap 0: Create spark for conjunction: 0x25214b0 spark: 0x209 - 11634057: cap 0: Start a parallel conjunction 0x2521510, static_id: 2 - 11634183: cap 0: Create spark for conjunction: 0x2521510 spark: 0x20a - 11634381: cap 0: Start a parallel conjunction 0x2521570, static_id: 2 - 11634511: cap 0: Create spark for conjunction: 0x2521570 spark: 0x20b - 11634705: cap 0: Start a parallel conjunction 0x25215d0, static_id: 2 - 11634831: cap 0: Create spark for conjunction: 0x25215d0 spark: 0x20c - 11635015: cap 0: Start a parallel conjunction 0x2521630, static_id: 2 - 11635159: cap 0: Create spark for conjunction: 0x2521630 spark: 0x20d - 11635344: cap 0: Start a parallel conjunction 0x2521690, static_id: 2 - 11635465: cap 0: Create spark for conjunction: 0x2521690 spark: 0x20e - 11635659: cap 0: Start a parallel conjunction 0x25216f0, static_id: 2 - 11635789: cap 0: Create spark for conjunction: 0x25216f0 spark: 0x20f - 11636037: cap 0: Start a parallel conjunction 0x2521750, static_id: 2 - 11636158: cap 0: Create spark for conjunction: 0x2521750 spark: 0x210 - 11636343: cap 0: Start a parallel conjunction 0x25217b0, static_id: 2 - 11636473: cap 0: Create spark for conjunction: 0x25217b0 spark: 0x211 - 11636649: cap 0: Start a parallel conjunction 0x2521810, static_id: 2 - 11636770: cap 0: Create spark for conjunction: 0x2521810 spark: 0x212 - 11636964: cap 0: Start a parallel conjunction 0x2521870, static_id: 2 - 11637099: cap 0: Create spark for conjunction: 0x2521870 spark: 0x213 - 11637283: cap 0: Start a parallel conjunction 0x25218d0, static_id: 2 - 11637409: cap 0: Create spark for conjunction: 0x25218d0 spark: 0x214 - 11637589: cap 0: Start a parallel conjunction 0x2521930, static_id: 2 - 11637729: cap 0: Create spark for conjunction: 0x2521930 spark: 0x215 - 11637931: cap 0: Start a parallel conjunction 0x2521990, static_id: 2 - 11638062: cap 0: Create spark for conjunction: 0x2521990 spark: 0x216 - 11638246: cap 0: Start a parallel conjunction 0x25219f0, static_id: 2 - 11638377: cap 0: Create spark for conjunction: 0x25219f0 spark: 0x217 - 11638845: cap 0: Start a parallel conjunction 0x2521a50, static_id: 2 - 11638971: cap 0: Create spark for conjunction: 0x2521a50 spark: 0x218 - 11639173: cap 0: Start a parallel conjunction 0x2521ab0, static_id: 2 - 11639304: cap 0: Create spark for conjunction: 0x2521ab0 spark: 0x219 - 11639488: cap 0: Start a parallel conjunction 0x2521b10, static_id: 2 - 11639614: cap 0: Create spark for conjunction: 0x2521b10 spark: 0x21a - 11639799: cap 0: Start a parallel conjunction 0x2521b70, static_id: 2 - 11639929: cap 0: Create spark for conjunction: 0x2521b70 spark: 0x21b - 11640118: cap 0: Start a parallel conjunction 0x2521bd0, static_id: 2 - 11640249: cap 0: Create spark for conjunction: 0x2521bd0 spark: 0x21c - 11640438: cap 0: Start a parallel conjunction 0x2521c30, static_id: 2 - 11640573: cap 0: Create spark for conjunction: 0x2521c30 spark: 0x21d - 11640753: cap 0: Start a parallel conjunction 0x2521c90, static_id: 2 - 11640874: cap 0: Create spark for conjunction: 0x2521c90 spark: 0x21e - 11641063: cap 0: Start a parallel conjunction 0x2521cf0, static_id: 2 - 11641194: cap 0: Create spark for conjunction: 0x2521cf0 spark: 0x21f - 11641374: cap 0: Start a parallel conjunction 0x2521d50, static_id: 2 - 11641495: cap 0: Create spark for conjunction: 0x2521d50 spark: 0x220 - 11641675: cap 0: Start a parallel conjunction 0x2521db0, static_id: 2 - 11641810: cap 0: Create spark for conjunction: 0x2521db0 spark: 0x221 - 11641990: cap 0: Start a parallel conjunction 0x2521e10, static_id: 2 - 11642121: cap 0: Create spark for conjunction: 0x2521e10 spark: 0x222 - 11642305: cap 0: Start a parallel conjunction 0x2521e70, static_id: 2 - 11642436: cap 0: Create spark for conjunction: 0x2521e70 spark: 0x223 - 11642616: cap 0: Start a parallel conjunction 0x2521ed0, static_id: 2 - 11642742: cap 0: Create spark for conjunction: 0x2521ed0 spark: 0x224 - 11642926: cap 0: Start a parallel conjunction 0x2521f30, static_id: 2 - 11643057: cap 0: Create spark for conjunction: 0x2521f30 spark: 0x225 - 11643241: cap 0: Start a parallel conjunction 0x2521f90, static_id: 2 - 11643367: cap 0: Create spark for conjunction: 0x2521f90 spark: 0x226 - 11643691: cap 0: Start a parallel conjunction 0x2521ff0, static_id: 2 - 11643826: cap 0: Create spark for conjunction: 0x2521ff0 spark: 0x227 - 11644011: cap 0: Start a parallel conjunction 0x2522050, static_id: 2 - 11644137: cap 0: Create spark for conjunction: 0x2522050 spark: 0x228 - 11644335: cap 0: Start a parallel conjunction 0x25220b0, static_id: 2 - 11644461: cap 0: Create spark for conjunction: 0x25220b0 spark: 0x229 - 11644645: cap 0: Start a parallel conjunction 0x2522110, static_id: 2 - 11644771: cap 0: Create spark for conjunction: 0x2522110 spark: 0x22a - 11644960: cap 0: Start a parallel conjunction 0x2522170, static_id: 2 - 11645100: cap 0: Create spark for conjunction: 0x2522170 spark: 0x22b - 11645293: cap 0: Start a parallel conjunction 0x25221d0, static_id: 2 - 11645419: cap 0: Create spark for conjunction: 0x25221d0 spark: 0x22c - 11645599: cap 0: Start a parallel conjunction 0x2522230, static_id: 2 - 11646090: cap 0: Create spark for conjunction: 0x2522230 spark: 0x22d - 11646274: cap 0: Start a parallel conjunction 0x2522290, static_id: 2 - 11646391: cap 0: Create spark for conjunction: 0x2522290 spark: 0x22e - 11646841: cap 0: Start a parallel conjunction 0x25222f0, static_id: 2 - 11646972: cap 0: Create spark for conjunction: 0x25222f0 spark: 0x22f - 11647147: cap 0: Start a parallel conjunction 0x2522350, static_id: 2 - 11647269: cap 0: Create spark for conjunction: 0x2522350 spark: 0x230 - 11647453: cap 0: Start a parallel conjunction 0x25223b0, static_id: 2 - 11647579: cap 0: Create spark for conjunction: 0x25223b0 spark: 0x231 - 11647759: cap 0: Start a parallel conjunction 0x2522410, static_id: 2 - 11647881: cap 0: Create spark for conjunction: 0x2522410 spark: 0x232 - 11648070: cap 0: Start a parallel conjunction 0x2522470, static_id: 2 - 11648196: cap 0: Create spark for conjunction: 0x2522470 spark: 0x233 - 11648380: cap 0: Start a parallel conjunction 0x25224d0, static_id: 2 - 11648506: cap 0: Create spark for conjunction: 0x25224d0 spark: 0x234 - 11648691: cap 0: Start a parallel conjunction 0x2522530, static_id: 2 - 11648826: cap 0: Create spark for conjunction: 0x2522530 spark: 0x235 - 11649024: cap 0: Start a parallel conjunction 0x2522590, static_id: 2 - 11649150: cap 0: Create spark for conjunction: 0x2522590 spark: 0x236 - 11649339: cap 0: Start a parallel conjunction 0x25225f0, static_id: 2 - 11649483: cap 0: Create spark for conjunction: 0x25225f0 spark: 0x237 - 11649672: cap 0: Start a parallel conjunction 0x2522650, static_id: 2 - 11649793: cap 0: Create spark for conjunction: 0x2522650 spark: 0x238 - 11649991: cap 0: Start a parallel conjunction 0x25226b0, static_id: 2 - 11650117: cap 0: Create spark for conjunction: 0x25226b0 spark: 0x239 - 11650302: cap 0: Start a parallel conjunction 0x2522710, static_id: 2 - 11650428: cap 0: Create spark for conjunction: 0x2522710 spark: 0x23a - 11650612: cap 0: Start a parallel conjunction 0x2522770, static_id: 2 - 11650738: cap 0: Create spark for conjunction: 0x2522770 spark: 0x23b - 11650936: cap 0: Start a parallel conjunction 0x25227d0, static_id: 2 - 11651058: cap 0: Create spark for conjunction: 0x25227d0 spark: 0x23c - 11651247: cap 0: Start a parallel conjunction 0x2522830, static_id: 2 - 11651386: cap 0: Create spark for conjunction: 0x2522830 spark: 0x23d - 11651562: cap 0: Start a parallel conjunction 0x2522890, static_id: 2 - 11651688: cap 0: Create spark for conjunction: 0x2522890 spark: 0x23e - 11651877: cap 0: Start a parallel conjunction 0x25228f0, static_id: 2 - 11652007: cap 0: Create spark for conjunction: 0x25228f0 spark: 0x23f - 11652183: cap 0: Start a parallel conjunction 0x2522950, static_id: 2 - 11652304: cap 0: Create spark for conjunction: 0x2522950 spark: 0x240 - 11652660: cap 0: Start a parallel conjunction 0x25229b0, static_id: 2 - 11652786: cap 0: Create spark for conjunction: 0x25229b0 spark: 0x241 - 11652966: cap 0: Start a parallel conjunction 0x2522a10, static_id: 2 - 11653087: cap 0: Create spark for conjunction: 0x2522a10 spark: 0x242 - 11653276: cap 0: Start a parallel conjunction 0x2522a70, static_id: 2 - 11653402: cap 0: Create spark for conjunction: 0x2522a70 spark: 0x243 - 11653587: cap 0: Start a parallel conjunction 0x2522ad0, static_id: 2 - 11653713: cap 0: Create spark for conjunction: 0x2522ad0 spark: 0x244 - 11653897: cap 0: Start a parallel conjunction 0x2522b30, static_id: 2 - 11654028: cap 0: Create spark for conjunction: 0x2522b30 spark: 0x245 - 11654221: cap 0: Start a parallel conjunction 0x2522b90, static_id: 2 - 11654347: cap 0: Create spark for conjunction: 0x2522b90 spark: 0x246 - 11654532: cap 0: Start a parallel conjunction 0x2522bf0, static_id: 2 - 11654676: cap 0: Create spark for conjunction: 0x2522bf0 spark: 0x247 - 11654865: cap 0: Start a parallel conjunction 0x2522c50, static_id: 2 - 11654986: cap 0: Create spark for conjunction: 0x2522c50 spark: 0x248 - 11655189: cap 0: Start a parallel conjunction 0x2522cb0, static_id: 2 - 11655328: cap 0: Create spark for conjunction: 0x2522cb0 spark: 0x249 - 11655504: cap 0: Start a parallel conjunction 0x2522d10, static_id: 2 - 11655630: cap 0: Create spark for conjunction: 0x2522d10 spark: 0x24a - 11655828: cap 0: Start a parallel conjunction 0x2522d70, static_id: 2 - 11655958: cap 0: Create spark for conjunction: 0x2522d70 spark: 0x24b - 11656152: cap 0: Start a parallel conjunction 0x2522dd0, static_id: 2 - 11656278: cap 0: Create spark for conjunction: 0x2522dd0 spark: 0x24c - 11656462: cap 0: Start a parallel conjunction 0x2522e30, static_id: 2 - 11656602: cap 0: Create spark for conjunction: 0x2522e30 spark: 0x24d - 11656786: cap 0: Start a parallel conjunction 0x2522e90, static_id: 2 - 11656908: cap 0: Create spark for conjunction: 0x2522e90 spark: 0x24e - 11657097: cap 0: Start a parallel conjunction 0x2522ef0, static_id: 2 - 11657227: cap 0: Create spark for conjunction: 0x2522ef0 spark: 0x24f - 11657407: cap 0: Start a parallel conjunction 0x2522f50, static_id: 2 - 11657524: cap 0: Create spark for conjunction: 0x2522f50 spark: 0x250 - 11657857: cap 0: Start a parallel conjunction 0x2522fb0, static_id: 2 - 11657983: cap 0: Create spark for conjunction: 0x2522fb0 spark: 0x251 - 11658172: cap 0: Start a parallel conjunction 0x2523010, static_id: 2 - 11658294: cap 0: Create spark for conjunction: 0x2523010 spark: 0x252 - 11658487: cap 0: Start a parallel conjunction 0x2523070, static_id: 2 - 11658618: cap 0: Create spark for conjunction: 0x2523070 spark: 0x253 - 11658802: cap 0: Start a parallel conjunction 0x25230d0, static_id: 2 - 11658933: cap 0: Create spark for conjunction: 0x25230d0 spark: 0x254 - 11659126: cap 0: Start a parallel conjunction 0x2523130, static_id: 2 - 11659252: cap 0: Create spark for conjunction: 0x2523130 spark: 0x255 - 11659446: cap 0: Start a parallel conjunction 0x2523190, static_id: 2 - 11659567: cap 0: Create spark for conjunction: 0x2523190 spark: 0x256 - 11659752: cap 0: Start a parallel conjunction 0x25231f0, static_id: 2 - 11659896: cap 0: Create spark for conjunction: 0x25231f0 spark: 0x257 - 11660076: cap 0: Start a parallel conjunction 0x2523250, static_id: 2 - 11660202: cap 0: Create spark for conjunction: 0x2523250 spark: 0x258 - 11660395: cap 0: Start a parallel conjunction 0x25232b0, static_id: 2 - 11660530: cap 0: Create spark for conjunction: 0x25232b0 spark: 0x259 - 11660710: cap 0: Start a parallel conjunction 0x2523310, static_id: 2 - 11660832: cap 0: Create spark for conjunction: 0x2523310 spark: 0x25a - 11661183: cap 0: Start a parallel conjunction 0x2523370, static_id: 2 - 11661313: cap 0: Create spark for conjunction: 0x2523370 spark: 0x25b - 11661507: cap 0: Start a parallel conjunction 0x25233d0, static_id: 2 - 11661633: cap 0: Create spark for conjunction: 0x25233d0 spark: 0x25c - 11661813: cap 0: Start a parallel conjunction 0x2523430, static_id: 2 - 11661952: cap 0: Create spark for conjunction: 0x2523430 spark: 0x25d - 11662132: cap 0: Start a parallel conjunction 0x2523490, static_id: 2 - 11662254: cap 0: Create spark for conjunction: 0x2523490 spark: 0x25e - 11662447: cap 0: Start a parallel conjunction 0x25234f0, static_id: 2 - 11662573: cap 0: Create spark for conjunction: 0x25234f0 spark: 0x25f - 11662753: cap 0: Start a parallel conjunction 0x2523550, static_id: 2 - 11662875: cap 0: Create spark for conjunction: 0x2523550 spark: 0x260 - 11663059: cap 0: Start a parallel conjunction 0x25235b0, static_id: 2 - 11663190: cap 0: Create spark for conjunction: 0x25235b0 spark: 0x261 - 11663374: cap 0: Start a parallel conjunction 0x2523610, static_id: 2 - 11663500: cap 0: Create spark for conjunction: 0x2523610 spark: 0x262 - 11663689: cap 0: Start a parallel conjunction 0x2523670, static_id: 2 - 11663824: cap 0: Create spark for conjunction: 0x2523670 spark: 0x263 - 11664018: cap 0: Start a parallel conjunction 0x25236d0, static_id: 2 - 11664157: cap 0: Create spark for conjunction: 0x25236d0 spark: 0x264 - 11664346: cap 0: Start a parallel conjunction 0x2523730, static_id: 2 - 11664481: cap 0: Create spark for conjunction: 0x2523730 spark: 0x265 - 11664675: cap 0: Start a parallel conjunction 0x2523790, static_id: 2 - 11664801: cap 0: Create spark for conjunction: 0x2523790 spark: 0x266 - 11664985: cap 0: Start a parallel conjunction 0x25237f0, static_id: 2 - 11665116: cap 0: Create spark for conjunction: 0x25237f0 spark: 0x267 - 11665300: cap 0: Start a parallel conjunction 0x2523850, static_id: 2 - 11665422: cap 0: Create spark for conjunction: 0x2523850 spark: 0x268 - 11665611: cap 0: Start a parallel conjunction 0x25238b0, static_id: 2 - 11665741: cap 0: Create spark for conjunction: 0x25238b0 spark: 0x269 - 11665921: cap 0: Start a parallel conjunction 0x2523910, static_id: 2 - 11666047: cap 0: Create spark for conjunction: 0x2523910 spark: 0x26a - 11666232: cap 0: Start a parallel conjunction 0x2523970, static_id: 2 - 11666367: cap 0: Create spark for conjunction: 0x2523970 spark: 0x26b - 11666556: cap 0: Start a parallel conjunction 0x25239d0, static_id: 2 - 11666677: cap 0: Create spark for conjunction: 0x25239d0 spark: 0x26c - 11666862: cap 0: Start a parallel conjunction 0x2523a30, static_id: 2 - 11666997: cap 0: Create spark for conjunction: 0x2523a30 spark: 0x26d - 11667172: cap 0: Start a parallel conjunction 0x2523a90, static_id: 2 - 11667294: cap 0: Create spark for conjunction: 0x2523a90 spark: 0x26e - 11667483: cap 0: Start a parallel conjunction 0x2523af0, static_id: 2 - 11667609: cap 0: Create spark for conjunction: 0x2523af0 spark: 0x26f - 11667793: cap 0: Start a parallel conjunction 0x2523b50, static_id: 2 - 11667915: cap 0: Create spark for conjunction: 0x2523b50 spark: 0x270 - 11668099: cap 0: Start a parallel conjunction 0x2523bb0, static_id: 2 - 11668252: cap 0: Create spark for conjunction: 0x2523bb0 spark: 0x271 - 11668432: cap 0: Start a parallel conjunction 0x2523c10, static_id: 2 - 11668554: cap 0: Create spark for conjunction: 0x2523c10 spark: 0x272 - 11668747: cap 0: Start a parallel conjunction 0x2523c70, static_id: 2 - 11668878: cap 0: Create spark for conjunction: 0x2523c70 spark: 0x273 - 11669058: cap 0: Start a parallel conjunction 0x2523cd0, static_id: 2 - 11669193: cap 0: Create spark for conjunction: 0x2523cd0 spark: 0x274 - 11669391: cap 0: Start a parallel conjunction 0x2523d30, static_id: 2 - 11669521: cap 0: Create spark for conjunction: 0x2523d30 spark: 0x275 - 11669710: cap 0: Start a parallel conjunction 0x2523d90, static_id: 2 - 11669836: cap 0: Create spark for conjunction: 0x2523d90 spark: 0x276 - 11670021: cap 0: Start a parallel conjunction 0x2523df0, static_id: 2 - 11670160: cap 0: Create spark for conjunction: 0x2523df0 spark: 0x277 - 11670340: cap 0: Start a parallel conjunction 0x2523e50, static_id: 2 - 11670466: cap 0: Create spark for conjunction: 0x2523e50 spark: 0x278 - 11670660: cap 0: Start a parallel conjunction 0x2523eb0, static_id: 2 - 11670790: cap 0: Create spark for conjunction: 0x2523eb0 spark: 0x279 - 11670970: cap 0: Start a parallel conjunction 0x2523f10, static_id: 2 - 11671096: cap 0: Create spark for conjunction: 0x2523f10 spark: 0x27a - 11671281: cap 0: Start a parallel conjunction 0x2523f70, static_id: 2 - 11671411: cap 0: Create spark for conjunction: 0x2523f70 spark: 0x27b - 11671744: cap 0: Start a parallel conjunction 0x2523fd0, static_id: 2 - 11671870: cap 0: Create spark for conjunction: 0x2523fd0 spark: 0x27c - 11672298: cap 0: Start a parallel conjunction 0x2524030, static_id: 2 - 11672446: cap 0: Create spark for conjunction: 0x2524030 spark: 0x27d - 11672631: cap 0: Start a parallel conjunction 0x2524090, static_id: 2 - 11672752: cap 0: Create spark for conjunction: 0x2524090 spark: 0x27e - 11672941: cap 0: Start a parallel conjunction 0x25240f0, static_id: 2 - 11673076: cap 0: Create spark for conjunction: 0x25240f0 spark: 0x27f - 11673256: cap 0: Start a parallel conjunction 0x2524150, static_id: 2 - 11673382: cap 0: Create spark for conjunction: 0x2524150 spark: 0x280 - 11673567: cap 0: Start a parallel conjunction 0x25241b0, static_id: 2 - 11673697: cap 0: Create spark for conjunction: 0x25241b0 spark: 0x281 - 11673873: cap 0: Start a parallel conjunction 0x2524210, static_id: 2 - 11673994: cap 0: Create spark for conjunction: 0x2524210 spark: 0x282 - 11674183: cap 0: Start a parallel conjunction 0x2524270, static_id: 2 - 11674318: cap 0: Create spark for conjunction: 0x2524270 spark: 0x283 - 11674503: cap 0: Start a parallel conjunction 0x25242d0, static_id: 2 - 11674674: cap 0: Create spark for conjunction: 0x25242d0 spark: 0x284 - 11674867: cap 0: Start a parallel conjunction 0x2524330, static_id: 2 - 11675002: cap 0: Create spark for conjunction: 0x2524330 spark: 0x285 - 11675196: cap 0: Start a parallel conjunction 0x2524390, static_id: 2 - 11675317: cap 0: Create spark for conjunction: 0x2524390 spark: 0x286 - 11675493: cap 0: Start a parallel conjunction 0x25243f0, static_id: 2 - 11675632: cap 0: Create spark for conjunction: 0x25243f0 spark: 0x287 - 11675817: cap 0: Start a parallel conjunction 0x2524450, static_id: 2 - 11675983: cap 0: Create spark for conjunction: 0x2524450 spark: 0x288 - 11676190: cap 0: Start a parallel conjunction 0x25244b0, static_id: 2 - 11676321: cap 0: Create spark for conjunction: 0x25244b0 spark: 0x289 - 11676505: cap 0: Start a parallel conjunction 0x2524510, static_id: 2 - 11676789: cap 0: Create spark for conjunction: 0x2524510 spark: 0x28a - 11676969: cap 0: Start a parallel conjunction 0x2524570, static_id: 2 - 11677131: cap 0: Create spark for conjunction: 0x2524570 spark: 0x28b - 11677720: cap 0: Start a parallel conjunction 0x25245d0, static_id: 2 - 11677842: cap 0: Create spark for conjunction: 0x25245d0 spark: 0x28c - 11678026: cap 0: Start a parallel conjunction 0x2524630, static_id: 2 - 11678166: cap 0: Create spark for conjunction: 0x2524630 spark: 0x28d - 11678346: cap 0: Start a parallel conjunction 0x2524690, static_id: 2 - 11678467: cap 0: Create spark for conjunction: 0x2524690 spark: 0x28e - 11678652: cap 0: Start a parallel conjunction 0x25246f0, static_id: 2 - 11678782: cap 0: Create spark for conjunction: 0x25246f0 spark: 0x28f - 11678967: cap 0: Start a parallel conjunction 0x2524750, static_id: 2 - 11679088: cap 0: Create spark for conjunction: 0x2524750 spark: 0x290 - 11679268: cap 0: Start a parallel conjunction 0x25247b0, static_id: 2 - 11679399: cap 0: Create spark for conjunction: 0x25247b0 spark: 0x291 - 11679583: cap 0: Start a parallel conjunction 0x2524810, static_id: 2 - 11679714: cap 0: Create spark for conjunction: 0x2524810 spark: 0x292 - 11679912: cap 0: Start a parallel conjunction 0x2524870, static_id: 2 - 11680042: cap 0: Create spark for conjunction: 0x2524870 spark: 0x293 - 11680231: cap 0: Start a parallel conjunction 0x25248d0, static_id: 2 - 11680366: cap 0: Create spark for conjunction: 0x25248d0 spark: 0x294 - 11680564: cap 0: Start a parallel conjunction 0x2524930, static_id: 2 - 11680695: cap 0: Create spark for conjunction: 0x2524930 spark: 0x295 - 11680888: cap 0: Start a parallel conjunction 0x2524990, static_id: 2 - 11681014: cap 0: Create spark for conjunction: 0x2524990 spark: 0x296 - 11681199: cap 0: Start a parallel conjunction 0x25249f0, static_id: 2 - 11681338: cap 0: Create spark for conjunction: 0x25249f0 spark: 0x297 - 11681518: cap 0: Start a parallel conjunction 0x2524a50, static_id: 2 - 11681644: cap 0: Create spark for conjunction: 0x2524a50 spark: 0x298 - 11681833: cap 0: Start a parallel conjunction 0x2524ab0, static_id: 2 - 11681959: cap 0: Create spark for conjunction: 0x2524ab0 spark: 0x299 - 11682139: cap 0: Start a parallel conjunction 0x2524b10, static_id: 2 - 11682261: cap 0: Create spark for conjunction: 0x2524b10 spark: 0x29a - 11682445: cap 0: Start a parallel conjunction 0x2524b70, static_id: 2 - 11682576: cap 0: Create spark for conjunction: 0x2524b70 spark: 0x29b - 11682760: cap 0: Start a parallel conjunction 0x2524bd0, static_id: 2 - 11682886: cap 0: Create spark for conjunction: 0x2524bd0 spark: 0x29c - 11683062: cap 0: Start a parallel conjunction 0x2524c30, static_id: 2 - 11683206: cap 0: Create spark for conjunction: 0x2524c30 spark: 0x29d - 11683386: cap 0: Start a parallel conjunction 0x2524c90, static_id: 2 - 11683512: cap 0: Create spark for conjunction: 0x2524c90 spark: 0x29e - 11683705: cap 0: Start a parallel conjunction 0x2524cf0, static_id: 2 - 11683836: cap 0: Create spark for conjunction: 0x2524cf0 spark: 0x29f - 11684011: cap 0: Start a parallel conjunction 0x2524d50, static_id: 2 - 11684133: cap 0: Create spark for conjunction: 0x2524d50 spark: 0x2a0 - 11684317: cap 0: Start a parallel conjunction 0x2524db0, static_id: 2 - 11684448: cap 0: Create spark for conjunction: 0x2524db0 spark: 0x2a1 - 11684628: cap 0: Start a parallel conjunction 0x2524e10, static_id: 2 - 11684749: cap 0: Create spark for conjunction: 0x2524e10 spark: 0x2a2 - 11684938: cap 0: Start a parallel conjunction 0x2524e70, static_id: 2 - 11685073: cap 0: Create spark for conjunction: 0x2524e70 spark: 0x2a3 - 11685253: cap 0: Start a parallel conjunction 0x2524ed0, static_id: 2 - 11685388: cap 0: Create spark for conjunction: 0x2524ed0 spark: 0x2a4 - 11685577: cap 0: Start a parallel conjunction 0x2524f30, static_id: 2 - 11685712: cap 0: Create spark for conjunction: 0x2524f30 spark: 0x2a5 - 11685901: cap 0: Start a parallel conjunction 0x2524f90, static_id: 2 - 11686027: cap 0: Create spark for conjunction: 0x2524f90 spark: 0x2a6 - 11686554: cap 0: Start a parallel conjunction 0x2524ff0, static_id: 2 - 11686693: cap 0: Create spark for conjunction: 0x2524ff0 spark: 0x2a7 - 11686882: cap 0: Start a parallel conjunction 0x2525050, static_id: 2 - 11687008: cap 0: Create spark for conjunction: 0x2525050 spark: 0x2a8 - 11687202: cap 0: Start a parallel conjunction 0x25250b0, static_id: 2 - 11687332: cap 0: Create spark for conjunction: 0x25250b0 spark: 0x2a9 - 11687512: cap 0: Start a parallel conjunction 0x2525110, static_id: 2 - 11687643: cap 0: Create spark for conjunction: 0x2525110 spark: 0x2aa - 11687827: cap 0: Start a parallel conjunction 0x2525170, static_id: 2 - 11687953: cap 0: Create spark for conjunction: 0x2525170 spark: 0x2ab - 11688142: cap 0: Start a parallel conjunction 0x25251d0, static_id: 2 - 11688264: cap 0: Create spark for conjunction: 0x25251d0 spark: 0x2ac - 11688448: cap 0: Start a parallel conjunction 0x2525230, static_id: 2 - 11688583: cap 0: Create spark for conjunction: 0x2525230 spark: 0x2ad - 11688763: cap 0: Start a parallel conjunction 0x2525290, static_id: 2 - 11688885: cap 0: Create spark for conjunction: 0x2525290 spark: 0x2ae - 11689074: cap 0: Start a parallel conjunction 0x25252f0, static_id: 2 - 11689209: cap 0: Create spark for conjunction: 0x25252f0 spark: 0x2af - 11689389: cap 0: Start a parallel conjunction 0x2525350, static_id: 2 - 11689510: cap 0: Create spark for conjunction: 0x2525350 spark: 0x2b0 - 11689695: cap 0: Start a parallel conjunction 0x25253b0, static_id: 2 - 11689825: cap 0: Create spark for conjunction: 0x25253b0 spark: 0x2b1 - 11690005: cap 0: Start a parallel conjunction 0x2525410, static_id: 2 - 11690131: cap 0: Create spark for conjunction: 0x2525410 spark: 0x2b2 - 11690325: cap 0: Start a parallel conjunction 0x2525470, static_id: 2 - 11690455: cap 0: Create spark for conjunction: 0x2525470 spark: 0x2b3 - 11690631: cap 0: Start a parallel conjunction 0x25254d0, static_id: 2 - 11690766: cap 0: Create spark for conjunction: 0x25254d0 spark: 0x2b4 - 11690955: cap 0: Start a parallel conjunction 0x2525530, static_id: 2 - 11691090: cap 0: Create spark for conjunction: 0x2525530 spark: 0x2b5 - 11691279: cap 0: Start a parallel conjunction 0x2525590, static_id: 2 - 11691405: cap 0: Create spark for conjunction: 0x2525590 spark: 0x2b6 - 11691585: cap 0: Start a parallel conjunction 0x25255f0, static_id: 2 - 11691724: cap 0: Create spark for conjunction: 0x25255f0 spark: 0x2b7 - 11691904: cap 0: Start a parallel conjunction 0x2525650, static_id: 2 - 11692026: cap 0: Create spark for conjunction: 0x2525650 spark: 0x2b8 - 11692233: cap 0: Start a parallel conjunction 0x25256b0, static_id: 2 - 11692363: cap 0: Create spark for conjunction: 0x25256b0 spark: 0x2b9 - 11692539: cap 0: Start a parallel conjunction 0x2525710, static_id: 2 - 11692665: cap 0: Create spark for conjunction: 0x2525710 spark: 0x2ba - 11692849: cap 0: Start a parallel conjunction 0x2525770, static_id: 2 - 11692975: cap 0: Create spark for conjunction: 0x2525770 spark: 0x2bb - 11693164: cap 0: Start a parallel conjunction 0x25257d0, static_id: 2 - 11693290: cap 0: Create spark for conjunction: 0x25257d0 spark: 0x2bc - 11693475: cap 0: Start a parallel conjunction 0x2525830, static_id: 2 - 11693610: cap 0: Create spark for conjunction: 0x2525830 spark: 0x2bd - 11693794: cap 0: Start a parallel conjunction 0x2525890, static_id: 2 - 11693916: cap 0: Create spark for conjunction: 0x2525890 spark: 0x2be - 11694127: cap 0: Start a parallel conjunction 0x25258f0, static_id: 2 - 11694258: cap 0: Create spark for conjunction: 0x25258f0 spark: 0x2bf - 11694438: cap 0: Start a parallel conjunction 0x2525950, static_id: 2 - 11694564: cap 0: Create spark for conjunction: 0x2525950 spark: 0x2c0 - 11694753: cap 0: Start a parallel conjunction 0x25259b0, static_id: 2 - 11694892: cap 0: Create spark for conjunction: 0x25259b0 spark: 0x2c1 - 11695081: cap 0: Start a parallel conjunction 0x2525a10, static_id: 2 - 11695203: cap 0: Create spark for conjunction: 0x2525a10 spark: 0x2c2 - 11695401: cap 0: Start a parallel conjunction 0x2525a70, static_id: 2 - 11695531: cap 0: Create spark for conjunction: 0x2525a70 spark: 0x2c3 - 11695711: cap 0: Start a parallel conjunction 0x2525ad0, static_id: 2 - 11695842: cap 0: Create spark for conjunction: 0x2525ad0 spark: 0x2c4 - 11696031: cap 0: Start a parallel conjunction 0x2525b30, static_id: 2 - 11696161: cap 0: Create spark for conjunction: 0x2525b30 spark: 0x2c5 - 11696350: cap 0: Start a parallel conjunction 0x2525b90, static_id: 2 - 11696476: cap 0: Create spark for conjunction: 0x2525b90 spark: 0x2c6 - 11696656: cap 0: Start a parallel conjunction 0x2525bf0, static_id: 2 - 11696791: cap 0: Create spark for conjunction: 0x2525bf0 spark: 0x2c7 - 11696980: cap 0: Start a parallel conjunction 0x2525c50, static_id: 2 - 11697106: cap 0: Create spark for conjunction: 0x2525c50 spark: 0x2c8 - 11697300: cap 0: Start a parallel conjunction 0x2525cb0, static_id: 2 - 11697435: cap 0: Create spark for conjunction: 0x2525cb0 spark: 0x2c9 - 11697615: cap 0: Start a parallel conjunction 0x2525d10, static_id: 2 - 11697741: cap 0: Create spark for conjunction: 0x2525d10 spark: 0x2ca - 11697925: cap 0: Start a parallel conjunction 0x2525d70, static_id: 2 - 11698060: cap 0: Create spark for conjunction: 0x2525d70 spark: 0x2cb - 11698249: cap 0: Start a parallel conjunction 0x2525dd0, static_id: 2 - 11698380: cap 0: Create spark for conjunction: 0x2525dd0 spark: 0x2cc - 11698560: cap 0: Start a parallel conjunction 0x2525e30, static_id: 2 - 11698699: cap 0: Create spark for conjunction: 0x2525e30 spark: 0x2cd - 11698888: cap 0: Start a parallel conjunction 0x2525e90, static_id: 2 - 11699014: cap 0: Create spark for conjunction: 0x2525e90 spark: 0x2ce - 11699221: cap 0: Start a parallel conjunction 0x2525ef0, static_id: 2 - 11699356: cap 0: Create spark for conjunction: 0x2525ef0 spark: 0x2cf - 11699536: cap 0: Start a parallel conjunction 0x2525f50, static_id: 2 - 11699662: cap 0: Create spark for conjunction: 0x2525f50 spark: 0x2d0 - 11700009: cap 0: Start a parallel conjunction 0x2525fb0, static_id: 2 - 11700139: cap 0: Create spark for conjunction: 0x2525fb0 spark: 0x2d1 - 11700432: cap 0: Start a parallel conjunction 0x2526010, static_id: 2 - 11700558: cap 0: Create spark for conjunction: 0x2526010 spark: 0x2d2 - 11700751: cap 0: Start a parallel conjunction 0x2526070, static_id: 2 - 11700882: cap 0: Create spark for conjunction: 0x2526070 spark: 0x2d3 - 11701057: cap 0: Start a parallel conjunction 0x25260d0, static_id: 2 - 11701183: cap 0: Create spark for conjunction: 0x25260d0 spark: 0x2d4 - 11701372: cap 0: Start a parallel conjunction 0x2526130, static_id: 2 - 11701503: cap 0: Create spark for conjunction: 0x2526130 spark: 0x2d5 - 11701692: cap 0: Start a parallel conjunction 0x2526190, static_id: 2 - 11701818: cap 0: Create spark for conjunction: 0x2526190 spark: 0x2d6 - 11702133: cap 0: Start a parallel conjunction 0x25261f0, static_id: 2 - 11702272: cap 0: Create spark for conjunction: 0x25261f0 spark: 0x2d7 - 11702457: cap 0: Start a parallel conjunction 0x2526250, static_id: 2 - 11702578: cap 0: Create spark for conjunction: 0x2526250 spark: 0x2d8 - 11702763: cap 0: Start a parallel conjunction 0x25262b0, static_id: 2 - 11702893: cap 0: Create spark for conjunction: 0x25262b0 spark: 0x2d9 - 11703073: cap 0: Start a parallel conjunction 0x2526310, static_id: 2 - 11703199: cap 0: Create spark for conjunction: 0x2526310 spark: 0x2da - 11703384: cap 0: Start a parallel conjunction 0x2526370, static_id: 2 - 11703510: cap 0: Create spark for conjunction: 0x2526370 spark: 0x2db - 11703825: cap 0: Start a parallel conjunction 0x25263d0, static_id: 2 - 11703946: cap 0: Create spark for conjunction: 0x25263d0 spark: 0x2dc - 11704140: cap 0: Start a parallel conjunction 0x2526430, static_id: 2 - 11704275: cap 0: Create spark for conjunction: 0x2526430 spark: 0x2dd - 11704455: cap 0: Start a parallel conjunction 0x2526490, static_id: 2 - 11704576: cap 0: Create spark for conjunction: 0x2526490 spark: 0x2de - 11704761: cap 0: Start a parallel conjunction 0x25264f0, static_id: 2 - 11704891: cap 0: Create spark for conjunction: 0x25264f0 spark: 0x2df - 11705067: cap 0: Start a parallel conjunction 0x2526550, static_id: 2 - 11705188: cap 0: Create spark for conjunction: 0x2526550 spark: 0x2e0 - 11705373: cap 0: Start a parallel conjunction 0x25265b0, static_id: 2 - 11705499: cap 0: Create spark for conjunction: 0x25265b0 spark: 0x2e1 - 11705683: cap 0: Start a parallel conjunction 0x2526610, static_id: 2 - 11705814: cap 0: Create spark for conjunction: 0x2526610 spark: 0x2e2 - 11706003: cap 0: Start a parallel conjunction 0x2526670, static_id: 2 - 11706133: cap 0: Create spark for conjunction: 0x2526670 spark: 0x2e3 - 11706318: cap 0: Start a parallel conjunction 0x25266d0, static_id: 2 - 11706448: cap 0: Create spark for conjunction: 0x25266d0 spark: 0x2e4 - 11706642: cap 0: Start a parallel conjunction 0x2526730, static_id: 2 - 11706777: cap 0: Create spark for conjunction: 0x2526730 spark: 0x2e5 - 11706966: cap 0: Start a parallel conjunction 0x2526790, static_id: 2 - 11707092: cap 0: Create spark for conjunction: 0x2526790 spark: 0x2e6 - 11707272: cap 0: Start a parallel conjunction 0x25267f0, static_id: 2 - 11707551: cap 0: Create spark for conjunction: 0x25267f0 spark: 0x2e7 - 11707744: cap 0: Start a parallel conjunction 0x2526850, static_id: 2 - 11707866: cap 0: Create spark for conjunction: 0x2526850 spark: 0x2e8 - 11708185: cap 0: Start a parallel conjunction 0x25268b0, static_id: 2 - 11708316: cap 0: Create spark for conjunction: 0x25268b0 spark: 0x2e9 - 11708505: cap 0: Start a parallel conjunction 0x2526910, static_id: 2 - 11708626: cap 0: Create spark for conjunction: 0x2526910 spark: 0x2ea - 11708811: cap 0: Start a parallel conjunction 0x2526970, static_id: 2 - 11708937: cap 0: Create spark for conjunction: 0x2526970 spark: 0x2eb - 11709126: cap 0: Start a parallel conjunction 0x25269d0, static_id: 2 - 11709247: cap 0: Create spark for conjunction: 0x25269d0 spark: 0x2ec - 11709427: cap 0: Start a parallel conjunction 0x2526a30, static_id: 2 - 11709562: cap 0: Create spark for conjunction: 0x2526a30 spark: 0x2ed - 11709742: cap 0: Start a parallel conjunction 0x2526a90, static_id: 2 - 11709864: cap 0: Create spark for conjunction: 0x2526a90 spark: 0x2ee - 11710062: cap 0: Start a parallel conjunction 0x2526af0, static_id: 2 - 11710197: cap 0: Create spark for conjunction: 0x2526af0 spark: 0x2ef - 11710372: cap 0: Start a parallel conjunction 0x2526b50, static_id: 2 - 11710503: cap 0: Create spark for conjunction: 0x2526b50 spark: 0x2f0 - 11710696: cap 0: Start a parallel conjunction 0x2526bb0, static_id: 2 - 11710827: cap 0: Create spark for conjunction: 0x2526bb0 spark: 0x2f1 - 11711011: cap 0: Start a parallel conjunction 0x2526c10, static_id: 2 - 11711128: cap 0: Create spark for conjunction: 0x2526c10 spark: 0x2f2 - 11711322: cap 0: Start a parallel conjunction 0x2526c70, static_id: 2 - 11711457: cap 0: Create spark for conjunction: 0x2526c70 spark: 0x2f3 - 11711637: cap 0: Start a parallel conjunction 0x2526cd0, static_id: 2 - 11711763: cap 0: Create spark for conjunction: 0x2526cd0 spark: 0x2f4 - 11711952: cap 0: Start a parallel conjunction 0x2526d30, static_id: 2 - 11712082: cap 0: Create spark for conjunction: 0x2526d30 spark: 0x2f5 - 11712271: cap 0: Start a parallel conjunction 0x2526d90, static_id: 2 - 11712397: cap 0: Create spark for conjunction: 0x2526d90 spark: 0x2f6 - 11712577: cap 0: Start a parallel conjunction 0x2526df0, static_id: 2 - 11712712: cap 0: Create spark for conjunction: 0x2526df0 spark: 0x2f7 - 11712888: cap 0: Start a parallel conjunction 0x2526e50, static_id: 2 - 11713009: cap 0: Create spark for conjunction: 0x2526e50 spark: 0x2f8 - 11713198: cap 0: Start a parallel conjunction 0x2526eb0, static_id: 2 - 11713329: cap 0: Create spark for conjunction: 0x2526eb0 spark: 0x2f9 - 11713504: cap 0: Start a parallel conjunction 0x2526f10, static_id: 2 - 11713626: cap 0: Create spark for conjunction: 0x2526f10 spark: 0x2fa - 11713810: cap 0: Start a parallel conjunction 0x2526f70, static_id: 2 - 11713936: cap 0: Create spark for conjunction: 0x2526f70 spark: 0x2fb - 11714130: cap 0: Start a parallel conjunction 0x2526fd0, static_id: 2 - 11714256: cap 0: Create spark for conjunction: 0x2526fd0 spark: 0x2fc - 11714463: cap 0: Start a parallel conjunction 0x2527030, static_id: 2 - 11714598: cap 0: Create spark for conjunction: 0x2527030 spark: 0x2fd - 11714787: cap 0: Start a parallel conjunction 0x2527090, static_id: 2 - 11714908: cap 0: Create spark for conjunction: 0x2527090 spark: 0x2fe - 11715097: cap 0: Start a parallel conjunction 0x25270f0, static_id: 2 - 11715223: cap 0: Create spark for conjunction: 0x25270f0 spark: 0x2ff - 11715403: cap 0: Start a parallel conjunction 0x2527150, static_id: 2 - 11715525: cap 0: Create spark for conjunction: 0x2527150 spark: 0x300 - 11715705: cap 0: Start a parallel conjunction 0x25271b0, static_id: 2 - 11715835: cap 0: Create spark for conjunction: 0x25271b0 spark: 0x301 - 11716015: cap 0: Start a parallel conjunction 0x2527210, static_id: 2 - 11716137: cap 0: Create spark for conjunction: 0x2527210 spark: 0x302 - 11716321: cap 0: Start a parallel conjunction 0x2527270, static_id: 2 - 11716452: cap 0: Create spark for conjunction: 0x2527270 spark: 0x303 - 11716632: cap 0: Start a parallel conjunction 0x25272d0, static_id: 2 - 11716803: cap 0: Create spark for conjunction: 0x25272d0 spark: 0x304 - 11716987: cap 0: Start a parallel conjunction 0x2527330, static_id: 2 - 11717113: cap 0: Create spark for conjunction: 0x2527330 spark: 0x305 - 11717302: cap 0: Start a parallel conjunction 0x2527390, static_id: 2 - 11717424: cap 0: Create spark for conjunction: 0x2527390 spark: 0x306 - 11717604: cap 0: Start a parallel conjunction 0x25273f0, static_id: 2 - 11717743: cap 0: Create spark for conjunction: 0x25273f0 spark: 0x307 - 11717919: cap 0: Start a parallel conjunction 0x2527450, static_id: 2 - 11718085: cap 0: Create spark for conjunction: 0x2527450 spark: 0x308 - 11718288: cap 0: Start a parallel conjunction 0x25274b0, static_id: 2 - 11718418: cap 0: Create spark for conjunction: 0x25274b0 spark: 0x309 - 11718594: cap 0: Start a parallel conjunction 0x2527510, static_id: 2 - 11718720: cap 0: Create spark for conjunction: 0x2527510 spark: 0x30a - 11718904: cap 0: Start a parallel conjunction 0x2527570, static_id: 2 - 11719035: cap 0: Create spark for conjunction: 0x2527570 spark: 0x30b - 11719219: cap 0: Start a parallel conjunction 0x25275d0, static_id: 2 - 11719341: cap 0: Create spark for conjunction: 0x25275d0 spark: 0x30c - 11719525: cap 0: Start a parallel conjunction 0x2527630, static_id: 2 - 11719669: cap 0: Create spark for conjunction: 0x2527630 spark: 0x30d - 11719849: cap 0: Start a parallel conjunction 0x2527690, static_id: 2 - 11719971: cap 0: Create spark for conjunction: 0x2527690 spark: 0x30e - 11720155: cap 0: Start a parallel conjunction 0x25276f0, static_id: 2 - 11720290: cap 0: Create spark for conjunction: 0x25276f0 spark: 0x30f - 11720475: cap 0: Start a parallel conjunction 0x2527750, static_id: 2 - 11720601: cap 0: Create spark for conjunction: 0x2527750 spark: 0x310 - 11720776: cap 0: Start a parallel conjunction 0x25277b0, static_id: 2 - 11720907: cap 0: Create spark for conjunction: 0x25277b0 spark: 0x311 - 11721087: cap 0: Start a parallel conjunction 0x2527810, static_id: 2 - 11721204: cap 0: Create spark for conjunction: 0x2527810 spark: 0x312 - 11721393: cap 0: Start a parallel conjunction 0x2527870, static_id: 2 - 11721528: cap 0: Create spark for conjunction: 0x2527870 spark: 0x313 - 11721708: cap 0: Start a parallel conjunction 0x25278d0, static_id: 2 - 11721834: cap 0: Create spark for conjunction: 0x25278d0 spark: 0x314 - 11722149: cap 0: Start a parallel conjunction 0x2527930, static_id: 2 - 11722275: cap 0: Create spark for conjunction: 0x2527930 spark: 0x315 - 11722464: cap 0: Start a parallel conjunction 0x2527990, static_id: 2 - 11722590: cap 0: Create spark for conjunction: 0x2527990 spark: 0x316 - 11722770: cap 0: Start a parallel conjunction 0x25279f0, static_id: 2 - 11722905: cap 0: Create spark for conjunction: 0x25279f0 spark: 0x317 - 11723089: cap 0: Start a parallel conjunction 0x2527a50, static_id: 2 - 11723215: cap 0: Create spark for conjunction: 0x2527a50 spark: 0x318 - 11723400: cap 0: Start a parallel conjunction 0x2527ab0, static_id: 2 - 11723535: cap 0: Create spark for conjunction: 0x2527ab0 spark: 0x319 - 11723715: cap 0: Start a parallel conjunction 0x2527b10, static_id: 2 - 11723836: cap 0: Create spark for conjunction: 0x2527b10 spark: 0x31a - 11724021: cap 0: Start a parallel conjunction 0x2527b70, static_id: 2 - 11724151: cap 0: Create spark for conjunction: 0x2527b70 spark: 0x31b - 11724340: cap 0: Start a parallel conjunction 0x2527bd0, static_id: 2 - 11724462: cap 0: Create spark for conjunction: 0x2527bd0 spark: 0x31c - 11724642: cap 0: Start a parallel conjunction 0x2527c30, static_id: 2 - 11724781: cap 0: Create spark for conjunction: 0x2527c30 spark: 0x31d - 11724961: cap 0: Start a parallel conjunction 0x2527c90, static_id: 2 - 11725092: cap 0: Create spark for conjunction: 0x2527c90 spark: 0x31e - 11725285: cap 0: Start a parallel conjunction 0x2527cf0, static_id: 2 - 11725425: cap 0: Create spark for conjunction: 0x2527cf0 spark: 0x31f - 11728597: cap 0: End par conjunct: 0x2527cf0 - 11730312: cap 0: running a local spark - 12148717: cap 3: creating spark thread 3 - 12149284: cap 3: running thread 3 - 12335386: cap 2: creating spark thread 2 - 12336304: cap 2: running thread 2 - 12609625: cap 1: creating spark thread 4 - 12610075: cap 1: running thread 4 - 12877888: cap 3: End par conjunct: 0x25151b0 - 12878455: cap 3: Trying to steal a spark - 12879013: cap 3: stealing a spark from cap 0 - 13341195: cap 2: End par conjunct: 0x2515150 - 13342090: cap 2: Trying to steal a spark - 13343094: cap 2: stealing a spark from cap 0 - 13501534: cap 3: End par conjunct: 0x2515270 - 13501827: cap 3: Trying to steal a spark - 13502322: cap 3: stealing a spark from cap 0 - 13596930: cap 1: End par conjunct: 0x2515210 - 13597681: cap 1: Trying to steal a spark - 13598401: cap 1: stealing a spark from cap 0 - 14083335: cap 1: stopping thread 4 (heap overflow) - 14083542: cap 1: starting GC - 14136727: cap 0: stopping thread 1 (thread yielding) - 14140219: cap 3: stopping thread 3 (thread yielding) - 14149165: cap 2: stopping thread 2 (thread yielding) - 23736676: cap 0: running thread 1 - 23740087: cap 3: running thread 3 - 23748079: cap 2: running thread 2 - 23783076: cap 1: finished GC - 23783292: cap 1: running thread 4 - 24076197: cap 2: End par conjunct: 0x25152d0 - 24078132: cap 2: Trying to steal a spark - 24079986: cap 2: stealing a spark from cap 0 - 24232905: cap 3: End par conjunct: 0x2515330 - 24233566: cap 3: Trying to steal a spark - 24234601: cap 3: stealing a spark from cap 0 - 24254811: cap 1: End par conjunct: 0x2515390 - 24255621: cap 1: Trying to steal a spark - 24256161: cap 1: stealing a spark from cap 0 - 24726721: cap 2: End par conjunct: 0x25153f0 - 24726996: cap 2: Trying to steal a spark - 24727351: cap 2: stealing a spark from cap 0 - 24884374: cap 1: End par conjunct: 0x25154b0 - 24884775: cap 1: Trying to steal a spark - 24884995: cap 1: stealing a spark from cap 0 - 25181676: cap 3: End par conjunct: 0x2515450 - 25182256: cap 3: Trying to steal a spark - 25182837: cap 3: stealing a spark from cap 0 - 25332556: cap 2: End par conjunct: 0x2515510 - 25332939: cap 2: Trying to steal a spark - 25333330: cap 2: stealing a spark from cap 0 - 25496014: cap 1: End par conjunct: 0x2515570 - 25496253: cap 1: Trying to steal a spark - 25496473: cap 1: stealing a spark from cap 0 - 25927915: cap 2: End par conjunct: 0x2515630 - 25928122: cap 2: Trying to steal a spark - 25928334: cap 2: stealing a spark from cap 0 - 26084745: cap 3: End par conjunct: 0x25155d0 - 26085249: cap 3: Trying to steal a spark - 26085843: cap 3: stealing a spark from cap 0 - 26090298: cap 1: End par conjunct: 0x2515690 - 26090689: cap 1: Trying to steal a spark - 26091085: cap 1: stealing a spark from cap 0 - 26536383: cap 2: End par conjunct: 0x25156f0 - 26536603: cap 2: Trying to steal a spark - 26536914: cap 2: stealing a spark from cap 0 - 26692762: cap 1: End par conjunct: 0x25157b0 - 26692992: cap 1: Trying to steal a spark - 26693203: cap 1: stealing a spark from cap 0 - 26979043: cap 3: End par conjunct: 0x2515750 - 26979642: cap 3: Trying to steal a spark - 26980258: cap 3: stealing a spark from cap 0 - 27137002: cap 2: End par conjunct: 0x2515810 - 27137416: cap 2: Trying to steal a spark - 27137952: cap 2: stealing a spark from cap 0 - 27307827: cap 1: End par conjunct: 0x2515870 - 27308056: cap 1: Trying to steal a spark - 27308272: cap 1: stealing a spark from cap 0 - 27746244: cap 2: End par conjunct: 0x2515930 - 27746469: cap 2: Trying to steal a spark - 27746680: cap 2: stealing a spark from cap 0 - 27876528: cap 3: End par conjunct: 0x25158d0 - 27877045: cap 3: Trying to steal a spark - 27877761: cap 3: stealing a spark from cap 0 - 27921861: cap 1: End par conjunct: 0x2515990 - 27922432: cap 1: Trying to steal a spark - 27922869: cap 1: stealing a spark from cap 0 - 28351957: cap 2: End par conjunct: 0x25159f0 - 28352187: cap 2: Trying to steal a spark - 28352407: cap 2: stealing a spark from cap 0 - 28533199: cap 1: End par conjunct: 0x2515ab0 - 28533424: cap 1: Trying to steal a spark - 28533631: cap 1: stealing a spark from cap 0 - 28780488: cap 3: End par conjunct: 0x2515a50 - 28780996: cap 3: Trying to steal a spark - 28781604: cap 3: stealing a spark from cap 0 - 28984594: cap 2: End par conjunct: 0x2515b10 - 28985049: cap 2: Trying to steal a spark - 28985485: cap 2: stealing a spark from cap 0 - 29173518: cap 1: End par conjunct: 0x2515b70 - 29173806: cap 1: Trying to steal a spark - 29174062: cap 1: stealing a spark from cap 0 - 29588274: cap 2: End par conjunct: 0x2515c30 - 29588494: cap 2: Trying to steal a spark - 29588706: cap 2: stealing a spark from cap 0 - 29705886: cap 3: End par conjunct: 0x2515bd0 - 29706475: cap 3: Trying to steal a spark - 29707047: cap 3: stealing a spark from cap 0 - 29788911: cap 1: End par conjunct: 0x2515c90 - 29789302: cap 1: Trying to steal a spark - 29789694: cap 1: stealing a spark from cap 0 - 30185464: cap 2: End par conjunct: 0x2515cf0 - 30185671: cap 2: Trying to steal a spark - 30185982: cap 2: stealing a spark from cap 0 - 30392149: cap 1: End par conjunct: 0x2515db0 - 30392374: cap 1: Trying to steal a spark - 30392590: cap 1: stealing a spark from cap 0 - 30611209: cap 3: End par conjunct: 0x2515d50 - 30611916: cap 3: Trying to steal a spark - 30612640: cap 3: stealing a spark from cap 0 - 30809916: cap 2: End par conjunct: 0x2515e10 - 30810312: cap 2: Trying to steal a spark - 30810712: cap 2: stealing a spark from cap 0 - 31008384: cap 1: End par conjunct: 0x2515e70 - 31008600: cap 1: Trying to steal a spark - 31008901: cap 1: stealing a spark from cap 0 - 31420368: cap 2: End par conjunct: 0x2515f30 - 31420593: cap 2: Trying to steal a spark - 31420809: cap 2: stealing a spark from cap 0 - 31533394: cap 3: End par conjunct: 0x2515ed0 - 31533984: cap 3: Trying to steal a spark - 31534591: cap 3: stealing a spark from cap 0 - 31615168: cap 1: End par conjunct: 0x2515f90 - 31615596: cap 1: Trying to steal a spark - 31615992: cap 1: stealing a spark from cap 0 - 32033641: cap 2: End par conjunct: 0x2515ff0 - 32033866: cap 2: Trying to steal a spark - 32034177: cap 2: stealing a spark from cap 0 - 32268591: cap 1: End par conjunct: 0x25160b0 - 32268874: cap 1: Trying to steal a spark - 32269131: cap 1: stealing a spark from cap 0 - 32468868: cap 3: End par conjunct: 0x2516050 - 32469426: cap 3: Trying to steal a spark - 32470078: cap 3: stealing a spark from cap 0 - 32677348: cap 2: End par conjunct: 0x2516110 - 32677776: cap 2: Trying to steal a spark - 32678208: cap 2: stealing a spark from cap 0 - 32876379: cap 1: End par conjunct: 0x2516170 - 32876590: cap 1: Trying to steal a spark - 32876811: cap 1: stealing a spark from cap 0 - 33304153: cap 2: End par conjunct: 0x2516230 - 33304374: cap 2: Trying to steal a spark - 33304684: cap 2: stealing a spark from cap 0 - 33398968: cap 3: End par conjunct: 0x25161d0 - 33399441: cap 3: Trying to steal a spark - 33399936: cap 3: stealing a spark from cap 0 - 33498414: cap 1: End par conjunct: 0x2516290 - 33498900: cap 1: Trying to steal a spark - 33499372: cap 1: stealing a spark from cap 0 - 33926773: cap 2: End par conjunct: 0x25162f0 - 33927003: cap 2: Trying to steal a spark - 33927219: cap 2: stealing a spark from cap 0 - 34125759: cap 1: End par conjunct: 0x25163b0 - 34125984: cap 1: Trying to steal a spark - 34126200: cap 1: stealing a spark from cap 0 - 34343518: cap 3: End par conjunct: 0x2516350 - 34344018: cap 3: Trying to steal a spark - 34344841: cap 3: stealing a spark from cap 0 - 34555158: cap 2: End par conjunct: 0x2516410 - 34555585: cap 2: Trying to steal a spark - 34555999: cap 2: stealing a spark from cap 0 - 34755426: cap 1: End par conjunct: 0x2516470 - 34755651: cap 1: Trying to steal a spark - 34755885: cap 1: stealing a spark from cap 0 - 35181679: cap 2: End par conjunct: 0x2516530 - 35181904: cap 2: Trying to steal a spark - 35182219: cap 2: stealing a spark from cap 0 - 35299462: cap 3: End par conjunct: 0x25164d0 - 35300011: cap 3: Trying to steal a spark - 35300614: cap 3: stealing a spark from cap 0 - 35403894: cap 1: End par conjunct: 0x2516590 - 35404425: cap 1: Trying to steal a spark - 35404992: cap 1: stealing a spark from cap 0 - 35817421: cap 2: End par conjunct: 0x25165f0 - 35817651: cap 2: Trying to steal a spark - 35817867: cap 2: stealing a spark from cap 0 - 36025614: cap 1: End par conjunct: 0x25166b0 - 36025843: cap 1: Trying to steal a spark - 36026055: cap 1: stealing a spark from cap 0 - 36222511: cap 3: End par conjunct: 0x2516650 - 36223024: cap 3: Trying to steal a spark - 36223618: cap 3: stealing a spark from cap 0 - 36455044: cap 2: End par conjunct: 0x2516710 - 36455602: cap 2: Trying to steal a spark - 36456102: cap 2: stealing a spark from cap 0 - 36668988: cap 1: End par conjunct: 0x2516770 - 36669204: cap 1: Trying to steal a spark - 36669415: cap 1: stealing a spark from cap 0 - 37113880: cap 2: End par conjunct: 0x2516830 - 37114330: cap 2: Trying to steal a spark - 37114650: cap 2: stealing a spark from cap 0 - 37175854: cap 3: End par conjunct: 0x25167d0 - 37176363: cap 3: Trying to steal a spark - 37176957: cap 3: stealing a spark from cap 0 - 37328764: cap 1: End par conjunct: 0x2516890 - 37329291: cap 1: Trying to steal a spark - 37329781: cap 1: stealing a spark from cap 0 - 37769184: cap 2: End par conjunct: 0x25168f0 - 37769454: cap 2: Trying to steal a spark - 37769818: cap 2: stealing a spark from cap 0 - 37969281: cap 1: End par conjunct: 0x25169b0 - 37969506: cap 1: Trying to steal a spark - 37969722: cap 1: stealing a spark from cap 0 - 38118726: cap 3: End par conjunct: 0x2516950 - 38119275: cap 3: Trying to steal a spark - 38119873: cap 3: stealing a spark from cap 0 - 38409223: cap 2: End par conjunct: 0x2516a10 - 38409628: cap 2: Trying to steal a spark - 38410029: cap 2: stealing a spark from cap 0 - 38624274: cap 1: End par conjunct: 0x2516a70 - 38624539: cap 1: Trying to steal a spark - 38624760: cap 1: stealing a spark from cap 0 - 39093678: cap 2: End par conjunct: 0x2516b30 - 39093957: cap 2: Trying to steal a spark - 39094204: cap 2: stealing a spark from cap 0 - 39133138: cap 3: End par conjunct: 0x2516ad0 - 39133723: cap 3: Trying to steal a spark - 39134574: cap 3: stealing a spark from cap 0 - 39276504: cap 1: End par conjunct: 0x2516b90 - 39276913: cap 1: Trying to steal a spark - 39277332: cap 1: stealing a spark from cap 0 - 39746497: cap 2: End par conjunct: 0x2516bf0 - 39746718: cap 2: Trying to steal a spark - 39746938: cap 2: stealing a spark from cap 0 - 39951765: cap 1: End par conjunct: 0x2516cb0 - 39952062: cap 1: Trying to steal a spark - 39952341: cap 1: stealing a spark from cap 0 - 40113454: cap 3: End par conjunct: 0x2516c50 - 40113999: cap 3: Trying to steal a spark - 40114507: cap 3: stealing a spark from cap 0 - 40408366: cap 2: End par conjunct: 0x2516d10 - 40408816: cap 2: Trying to steal a spark - 40409239: cap 2: stealing a spark from cap 0 - 40619043: cap 1: End par conjunct: 0x2516d70 - 40619268: cap 1: Trying to steal a spark - 40619488: cap 1: stealing a spark from cap 0 - 41067765: cap 2: End par conjunct: 0x2516e30 - 41068017: cap 2: Trying to steal a spark - 41068260: cap 2: stealing a spark from cap 0 - 41114754: cap 3: End par conjunct: 0x2516dd0 - 41115456: cap 3: Trying to steal a spark - 41116095: cap 3: stealing a spark from cap 0 - 41283873: cap 1: End par conjunct: 0x2516e90 - 41284156: cap 1: Trying to steal a spark - 41284548: cap 1: stealing a spark from cap 0 - 41730048: cap 2: End par conjunct: 0x2516ef0 - 41730273: cap 2: Trying to steal a spark - 41730583: cap 2: stealing a spark from cap 0 - 41952546: cap 1: End par conjunct: 0x2516fb0 - 41952771: cap 1: Trying to steal a spark - 41952982: cap 1: stealing a spark from cap 0 - 42100420: cap 3: End par conjunct: 0x2516f50 - 42100924: cap 3: Trying to steal a spark - 42101577: cap 3: stealing a spark from cap 0 - 42400962: cap 2: End par conjunct: 0x2517010 - 42401286: cap 2: Trying to steal a spark - 42401709: cap 2: stealing a spark from cap 0 - 42633526: cap 1: End par conjunct: 0x2517070 - 42633801: cap 1: Trying to steal a spark - 42634035: cap 1: stealing a spark from cap 0 - 43071579: cap 2: End par conjunct: 0x2517130 - 43071804: cap 2: Trying to steal a spark - 43072141: cap 2: stealing a spark from cap 0 - 43098408: cap 3: End par conjunct: 0x25170d0 - 43099047: cap 3: Trying to steal a spark - 43099650: cap 3: stealing a spark from cap 0 - 43299085: cap 1: End par conjunct: 0x2517190 - 43299540: cap 1: Trying to steal a spark - 43299994: cap 1: stealing a spark from cap 0 - 43749342: cap 2: End par conjunct: 0x25171f0 - 43749675: cap 2: Trying to steal a spark - 43749981: cap 2: stealing a spark from cap 0 - 43987482: cap 1: End par conjunct: 0x25172b0 - 43987711: cap 1: Trying to steal a spark - 43987927: cap 1: stealing a spark from cap 0 - 44106511: cap 3: End par conjunct: 0x2517250 - 44107020: cap 3: Trying to steal a spark - 44107524: cap 3: stealing a spark from cap 0 - 44435862: cap 2: End par conjunct: 0x2517310 - 44436258: cap 2: Trying to steal a spark - 44436654: cap 2: stealing a spark from cap 0 - 44685877: cap 1: End par conjunct: 0x2517370 - 44686093: cap 1: Trying to steal a spark - 44686305: cap 1: stealing a spark from cap 0 - 45133911: cap 2: End par conjunct: 0x2517430 - 45134136: cap 2: Trying to steal a spark - 45134446: cap 2: stealing a spark from cap 0 - 45154615: cap 3: End par conjunct: 0x25173d0 - 45155164: cap 3: Trying to steal a spark - 45155763: cap 3: stealing a spark from cap 0 - 45397935: cap 1: End par conjunct: 0x2517490 - 45398326: cap 1: Trying to steal a spark - 45398718: cap 1: stealing a spark from cap 0 - 45836001: cap 2: End par conjunct: 0x25174f0 - 45836226: cap 2: Trying to steal a spark - 45836541: cap 2: stealing a spark from cap 0 - 46110154: cap 1: End par conjunct: 0x25175b0 - 46110379: cap 1: Trying to steal a spark - 46110595: cap 1: stealing a spark from cap 0 - 46221808: cap 3: End par conjunct: 0x2517550 - 46222308: cap 3: Trying to steal a spark - 46222902: cap 3: stealing a spark from cap 0 - 46588792: cap 2: End par conjunct: 0x2517610 - 46589211: cap 2: Trying to steal a spark - 46589625: cap 2: stealing a spark from cap 0 - 46844860: cap 1: End par conjunct: 0x2517670 - 46845072: cap 1: Trying to steal a spark - 46845288: cap 1: stealing a spark from cap 0 - 47312941: cap 2: End par conjunct: 0x2517730 - 47313166: cap 2: Trying to steal a spark - 47313477: cap 2: stealing a spark from cap 0 - 47330820: cap 3: End par conjunct: 0x25176d0 - 47331400: cap 3: Trying to steal a spark - 47332035: cap 3: stealing a spark from cap 0 - 47604280: cap 1: End par conjunct: 0x2517790 - 47604735: cap 1: Trying to steal a spark - 47605203: cap 1: stealing a spark from cap 0 - 48060094: cap 2: End par conjunct: 0x25177f0 - 48060297: cap 2: Trying to steal a spark - 48060603: cap 2: stealing a spark from cap 0 - 48358003: cap 1: End par conjunct: 0x25178b0 - 48358228: cap 1: Trying to steal a spark - 48358458: cap 1: stealing a spark from cap 0 - 48437491: cap 3: End par conjunct: 0x2517850 - 48437964: cap 3: Trying to steal a spark - 48438558: cap 3: stealing a spark from cap 0 - 48805825: cap 2: End par conjunct: 0x2517910 - 48806239: cap 2: Trying to steal a spark - 48806824: cap 2: stealing a spark from cap 0 - 49100440: cap 1: End par conjunct: 0x2517970 - 49100665: cap 1: Trying to steal a spark - 49100886: cap 1: stealing a spark from cap 0 - 49579861: cap 3: End par conjunct: 0x25179d0 - 49580419: cap 3: Trying to steal a spark - 49581022: cap 3: stealing a spark from cap 0 - 49636854: cap 2: End par conjunct: 0x2517a30 - 49637754: cap 2: Trying to steal a spark - 49638730: cap 2: stealing a spark from cap 0 - 49870381: cap 1: End par conjunct: 0x2517a90 - 49870705: cap 1: Trying to steal a spark - 49870917: cap 1: stealing a spark from cap 0 - 50426550: cap 2: End par conjunct: 0x2517b50 - 50426932: cap 2: Trying to steal a spark - 50427261: cap 2: stealing a spark from cap 0 - 50665230: cap 1: End par conjunct: 0x2517bb0 - 50665441: cap 1: Trying to steal a spark - 50665653: cap 1: stealing a spark from cap 0 - 50830560: cap 3: End par conjunct: 0x2517af0 - 50831068: cap 3: Trying to steal a spark - 50831662: cap 3: stealing a spark from cap 0 - 51224148: cap 2: End par conjunct: 0x2517c10 - 51224454: cap 2: Trying to steal a spark - 51225012: cap 2: stealing a spark from cap 0 - 51483465: cap 1: End par conjunct: 0x2517c70 - 51483685: cap 1: Trying to steal a spark - 51483906: cap 1: stealing a spark from cap 0 - 52064626: cap 3: End par conjunct: 0x2517cd0 - 52065135: cap 3: Trying to steal a spark - 52065729: cap 3: stealing a spark from cap 0 - 52247997: cap 2: End par conjunct: 0x2517d30 - 52248433: cap 2: Trying to steal a spark - 52248924: cap 2: stealing a spark from cap 0 - 52314489: cap 1: End par conjunct: 0x2517d90 - 52314921: cap 1: Trying to steal a spark - 52315168: cap 1: stealing a spark from cap 0 - 53089573: cap 2: End par conjunct: 0x2517e50 - 53089983: cap 2: Trying to steal a spark - 53090334: cap 2: stealing a spark from cap 0 - 53148744: cap 1: End par conjunct: 0x2517eb0 - 53148991: cap 1: Trying to steal a spark - 53149203: cap 1: stealing a spark from cap 0 - 53306419: cap 3: End par conjunct: 0x2517df0 - 53306928: cap 3: Trying to steal a spark - 53307544: cap 3: stealing a spark from cap 0 - 53907304: cap 2: End par conjunct: 0x2517f10 - 53907579: cap 2: Trying to steal a spark - 53907961: cap 2: stealing a spark from cap 0 - 54013536: cap 1: End par conjunct: 0x2517f70 - 54013806: cap 1: Trying to steal a spark - 54014022: cap 1: stealing a spark from cap 0 - 54337927: cap 3: End par conjunct: 0x2517fd0 - 54338431: cap 3: Trying to steal a spark - 54338931: cap 3: stealing a spark from cap 0 - 54762241: cap 2: End par conjunct: 0x2518030 - 54762664: cap 2: Trying to steal a spark - 54763177: cap 2: stealing a spark from cap 0 - 54909072: cap 1: End par conjunct: 0x2518090 - 54909450: cap 1: Trying to steal a spark - 54909684: cap 1: stealing a spark from cap 0 - 55878903: cap 2: End par conjunct: 0x2518150 - 55879249: cap 2: Trying to steal a spark - 55879465: cap 2: stealing a spark from cap 0 - 55923277: cap 3: End par conjunct: 0x25180f0 - 55923610: cap 3: Trying to steal a spark - 55924101: cap 3: stealing a spark from cap 0 - 56954371: cap 1: End par conjunct: 0x25181b0 - 56954632: cap 1: Trying to steal a spark - 56955096: cap 1: stealing a spark from cap 0 - 58131936: cap 2: End par conjunct: 0x2518210 - 58132260: cap 2: Trying to steal a spark - 58132476: cap 2: stealing a spark from cap 0 - 58232556: cap 3: End par conjunct: 0x2518270 - 58232889: cap 3: Trying to steal a spark - 58233262: cap 3: stealing a spark from cap 0 - 59230395: cap 1: End par conjunct: 0x25182d0 - 59231034: cap 1: Trying to steal a spark - 59231439: cap 1: stealing a spark from cap 0 - 59402803: cap 3: End par conjunct: 0x2518390 - 59403244: cap 3: Trying to steal a spark - 59403739: cap 3: stealing a spark from cap 0 - 59775511: cap 2: End par conjunct: 0x2518330 - 59775781: cap 2: Trying to steal a spark - 59776168: cap 2: stealing a spark from cap 0 - 60382269: cap 3: End par conjunct: 0x2518450 - 60382647: cap 3: Trying to steal a spark - 60383133: cap 3: stealing a spark from cap 0 - 60445363: cap 1: End par conjunct: 0x25183f0 - 60445737: cap 1: Trying to steal a spark - 60446155: cap 1: stealing a spark from cap 0 - 61507039: cap 2: End par conjunct: 0x25184b0 - 61507665: cap 2: Trying to steal a spark - 61508101: cap 2: stealing a spark from cap 0 - 62346784: cap 1: End par conjunct: 0x2518570 - 62347000: cap 1: Trying to steal a spark - 62347216: cap 1: stealing a spark from cap 0 - 62512888: cap 3: End par conjunct: 0x2518510 - 62513284: cap 3: Trying to steal a spark - 62513658: cap 3: stealing a spark from cap 0 - 63392238: cap 2: End par conjunct: 0x25185d0 - 63392625: cap 2: Trying to steal a spark - 63393111: cap 2: stealing a spark from cap 0 - 63590472: cap 3: End par conjunct: 0x2518690 - 63590904: cap 3: Trying to steal a spark - 63591385: cap 3: stealing a spark from cap 0 - 64123029: cap 1: End par conjunct: 0x2518630 - 64123375: cap 1: Trying to steal a spark - 64123893: cap 1: stealing a spark from cap 0 - 64477633: cap 2: End par conjunct: 0x25186f0 - 64477975: cap 2: Trying to steal a spark - 64478223: cap 2: stealing a spark from cap 0 - 64722933: cap 3: End par conjunct: 0x2518750 - 64723369: cap 3: Trying to steal a spark - 64723851: cap 3: stealing a spark from cap 0 - 65542941: cap 1: End par conjunct: 0x25187b0 - 65543301: cap 1: Trying to steal a spark - 65543782: cap 1: stealing a spark from cap 0 - 65650234: cap 2: End par conjunct: 0x2518810 - 65650576: cap 2: Trying to steal a spark - 65650788: cap 2: stealing a spark from cap 0 - 66578935: cap 3: End par conjunct: 0x2518870 - 66579484: cap 3: Trying to steal a spark - 66580056: cap 3: stealing a spark from cap 0 - 66854529: cap 2: End par conjunct: 0x2518930 - 66854853: cap 2: Trying to steal a spark - 66855343: cap 2: stealing a spark from cap 0 - 66946320: cap 1: End par conjunct: 0x25188d0 - 66946707: cap 1: Trying to steal a spark - 66946963: cap 1: stealing a spark from cap 0 - 67733041: cap 3: End par conjunct: 0x2518990 - 67733455: cap 3: Trying to steal a spark - 67733950: cap 3: stealing a spark from cap 0 - 68058499: cap 2: End par conjunct: 0x25189f0 - 68058882: cap 2: Trying to steal a spark - 68059377: cap 2: stealing a spark from cap 0 - 68678649: cap 1: End par conjunct: 0x2518a50 - 68678982: cap 1: Trying to steal a spark - 68679229: cap 1: stealing a spark from cap 0 - 69240861: cap 3: End par conjunct: 0x2518ab0 - 69241176: cap 3: Trying to steal a spark - 69241567: cap 3: stealing a spark from cap 0 - 69304954: cap 2: End par conjunct: 0x2518b10 - 69305319: cap 2: Trying to steal a spark - 69305692: cap 2: stealing a spark from cap 0 - 70140240: cap 1: End par conjunct: 0x2518b70 - 70140469: cap 1: Trying to steal a spark - 70140685: cap 1: stealing a spark from cap 0 - 70773511: cap 3: End par conjunct: 0x2518bd0 - 70773885: cap 3: Trying to steal a spark - 70774366: cap 3: stealing a spark from cap 0 - 70808850: cap 2: End par conjunct: 0x2518c30 - 70809367: cap 2: Trying to steal a spark - 70809768: cap 2: stealing a spark from cap 0 - 71873527: cap 1: End par conjunct: 0x2518c90 - 71873860: cap 1: Trying to steal a spark - 71874072: cap 1: stealing a spark from cap 0 - 72283689: cap 2: End par conjunct: 0x2518d50 - 72284017: cap 2: Trying to steal a spark - 72284233: cap 2: stealing a spark from cap 0 - 73054251: cap 3: End par conjunct: 0x2518cf0 - 73054732: cap 3: Trying to steal a spark - 73055466: cap 3: stealing a spark from cap 0 - 73159285: cap 1: End par conjunct: 0x2518db0 - 73159722: cap 1: Trying to steal a spark - 73160388: cap 1: stealing a spark from cap 0 - 74440966: cap 3: End par conjunct: 0x2518e70 - 74441227: cap 3: Trying to steal a spark - 74441610: cap 3: stealing a spark from cap 0 - 74785315: cap 2: End par conjunct: 0x2518e10 - 74786017: cap 2: Trying to steal a spark - 74787043: cap 2: stealing a spark from cap 0 - 75288483: cap 1: End par conjunct: 0x2518ed0 - 75288820: cap 1: Trying to steal a spark - 75289032: cap 1: stealing a spark from cap 0 - 77436747: cap 3: End par conjunct: 0x2518f30 - 77437134: cap 3: Trying to steal a spark - 77437759: cap 3: stealing a spark from cap 0 - 78004147: cap 2: End par conjunct: 0x2518f90 - 78004602: cap 2: Trying to steal a spark - 78005169: cap 2: stealing a spark from cap 0 - 78438784: cap 1: End par conjunct: 0x2518ff0 - 78439081: cap 1: Trying to steal a spark - 78439360: cap 1: stealing a spark from cap 0 - 80926996: cap 3: End par conjunct: 0x2519050 - 80927392: cap 3: Trying to steal a spark - 80927775: cap 3: stealing a spark from cap 0 - 82047559: cap 2: End par conjunct: 0x25190b0 - 82047987: cap 2: Trying to steal a spark - 82048459: cap 2: stealing a spark from cap 0 - 83968875: cap 1: End par conjunct: 0x2519110 - 83969217: cap 1: Trying to steal a spark - 83969428: cap 1: stealing a spark from cap 0 - 86729665: cap 3: End par conjunct: 0x2519170 - 86730021: cap 3: Trying to steal a spark - 86730417: cap 3: stealing a spark from cap 0 - 88351767: cap 2: End par conjunct: 0x25191d0 - 88352401: cap 2: Trying to steal a spark - 88353040: cap 2: stealing a spark from cap 0 - 91559997: cap 1: End par conjunct: 0x2519230 - 91560532: cap 1: Trying to steal a spark - 91560888: cap 1: stealing a spark from cap 0 - 94191606: cap 3: End par conjunct: 0x2519290 - 94192038: cap 3: Trying to steal a spark - 94192447: cap 3: stealing a spark from cap 0 - 96909921: cap 2: End par conjunct: 0x25192f0 - 96910249: cap 2: Trying to steal a spark - 96910677: cap 2: stealing a spark from cap 0 +0: created capset 0 of type CapsetOsProcess +0: capset 0: RTS version "mmc-DEV" +0: startup: 4 capabilities +0: Register an id->string mapping +0: Register an id->string mapping +0: Register an id->string mapping +0: Register an id->string mapping +0: assigned cap 0 to capset 0 +0: assigned cap 3 to capset 0 +0: assigned cap 1 to capset 0 +0: assigned cap 2 to capset 0 +4198126: cap 0: creating thread 1 +4199512: cap 0: running thread 1 +9983902: cap 3: Looking for global thread to resume +9987484: cap 3: Trying to steal a spark +10575823: cap 1: Looking for global thread to resume +10577452: cap 1: Trying to steal a spark +10694043: cap 2: Looking for global thread to resume +10694551: cap 2: Trying to steal a spark +10852245: cap 0: spark fizzled +11153997: cap 0: Start a parallel conjunction 0x2515150, static_id: 2 +11155725: cap 0: Create spark for conjunction: 0x2515150 spark: 0x0 +11165265: cap 0: Start a parallel conjunction 0x25151b0, static_id: 2 +11165593: cap 0: Create spark for conjunction: 0x25151b0 spark: 0x1 +11169886: cap 0: Start a parallel conjunction 0x2515210, static_id: 2 +11170080: cap 0: Create spark for conjunction: 0x2515210 spark: 0x2 +11172546: cap 0: Start a parallel conjunction 0x2515270, static_id: 2 +11172730: cap 0: Create spark for conjunction: 0x2515270 spark: 0x3 +11173041: cap 0: Start a parallel conjunction 0x25152d0, static_id: 2 +11173338: cap 0: Create spark for conjunction: 0x25152d0 spark: 0x4 +11173905: cap 0: Start a parallel conjunction 0x2515330, static_id: 2 +11174107: cap 0: Create spark for conjunction: 0x2515330 spark: 0x5 +11174143: cap 2: Trying to steal a spark +11174413: cap 0: Start a parallel conjunction 0x2515390, static_id: 2 +11174760: cap 0: Create spark for conjunction: 0x2515390 spark: 0x6 +11175034: cap 0: Start a parallel conjunction 0x25153f0, static_id: 2 +11175610: cap 0: Create spark for conjunction: 0x25153f0 spark: 0x7 +11175853: cap 3: Trying to steal a spark +11175885: cap 0: Start a parallel conjunction 0x2515450, static_id: 2 +11177316: cap 2: stealing a spark from cap 0 +11178108: cap 3: stealing a spark from cap 0 +11198002: cap 0: Create spark for conjunction: 0x2515450 spark: 0x8 +11198394: cap 0: Start a parallel conjunction 0x25154b0, static_id: 2 +11198601: cap 0: Create spark for conjunction: 0x25154b0 spark: 0x9 +11198880: cap 0: Start a parallel conjunction 0x2515510, static_id: 2 +11199069: cap 0: Create spark for conjunction: 0x2515510 spark: 0xa +11199352: cap 0: Start a parallel conjunction 0x2515570, static_id: 2 +11199541: cap 0: Create spark for conjunction: 0x2515570 spark: 0xb +11199829: cap 0: Start a parallel conjunction 0x25155d0, static_id: 2 +11200014: cap 0: Create spark for conjunction: 0x25155d0 spark: 0xc +11200275: cap 0: Start a parallel conjunction 0x2515630, static_id: 2 +11200468: cap 0: Create spark for conjunction: 0x2515630 spark: 0xd +11200743: cap 0: Start a parallel conjunction 0x2515690, static_id: 2 +11200918: cap 0: Create spark for conjunction: 0x2515690 spark: 0xe +11201206: cap 0: Start a parallel conjunction 0x25156f0, static_id: 2 +11201418: cap 0: Create spark for conjunction: 0x25156f0 spark: 0xf +11201719: cap 0: Start a parallel conjunction 0x2515750, static_id: 2 +11201899: cap 0: Create spark for conjunction: 0x2515750 spark: 0x10 +11202174: cap 0: Start a parallel conjunction 0x25157b0, static_id: 2 +11220259: cap 0: Create spark for conjunction: 0x25157b0 spark: 0x11 +11220592: cap 0: Start a parallel conjunction 0x2515810, static_id: 2 +11220772: cap 0: Create spark for conjunction: 0x2515810 spark: 0x12 +11221083: cap 0: Start a parallel conjunction 0x2515870, static_id: 2 +11221272: cap 0: Create spark for conjunction: 0x2515870 spark: 0x13 +11221533: cap 0: Start a parallel conjunction 0x25158d0, static_id: 2 +11221731: cap 0: Create spark for conjunction: 0x25158d0 spark: 0x14 +11222005: cap 0: Start a parallel conjunction 0x2515930, static_id: 2 +11222199: cap 0: Create spark for conjunction: 0x2515930 spark: 0x15 +11222478: cap 0: Start a parallel conjunction 0x2515990, static_id: 2 +11222671: cap 0: Create spark for conjunction: 0x2515990 spark: 0x16 +11222941: cap 0: Start a parallel conjunction 0x25159f0, static_id: 2 +11223130: cap 0: Create spark for conjunction: 0x25159f0 spark: 0x17 +11223400: cap 0: Start a parallel conjunction 0x2515a50, static_id: 2 +11223580: cap 0: Create spark for conjunction: 0x2515a50 spark: 0x18 +11223886: cap 0: Start a parallel conjunction 0x2515ab0, static_id: 2 +11224066: cap 0: Create spark for conjunction: 0x2515ab0 spark: 0x19 +11224336: cap 0: Start a parallel conjunction 0x2515b10, static_id: 2 +11224543: cap 0: Create spark for conjunction: 0x2515b10 spark: 0x1a +11224827: cap 0: Start a parallel conjunction 0x2515b70, static_id: 2 +11225007: cap 0: Create spark for conjunction: 0x2515b70 spark: 0x1b +11225286: cap 0: Start a parallel conjunction 0x2515bd0, static_id: 2 +11225470: cap 0: Create spark for conjunction: 0x2515bd0 spark: 0x1c +11225758: cap 0: Start a parallel conjunction 0x2515c30, static_id: 2 +11225956: cap 0: Create spark for conjunction: 0x2515c30 spark: 0x1d +11226240: cap 0: Start a parallel conjunction 0x2515c90, static_id: 2 +11226424: cap 0: Create spark for conjunction: 0x2515c90 spark: 0x1e +11226708: cap 0: Start a parallel conjunction 0x2515cf0, static_id: 2 +11226892: cap 0: Create spark for conjunction: 0x2515cf0 spark: 0x1f +11227176: cap 0: Start a parallel conjunction 0x2515d50, static_id: 2 +11227374: cap 0: Create spark for conjunction: 0x2515d50 spark: 0x20 +11227653: cap 0: Start a parallel conjunction 0x2515db0, static_id: 2 +11299891: cap 0: Create spark for conjunction: 0x2515db0 spark: 0x21 +11300346: cap 0: Start a parallel conjunction 0x2515e10, static_id: 2 +11300535: cap 0: Create spark for conjunction: 0x2515e10 spark: 0x22 +11300845: cap 0: Start a parallel conjunction 0x2515e70, static_id: 2 +11301034: cap 0: Create spark for conjunction: 0x2515e70 spark: 0x23 +11301291: cap 0: Start a parallel conjunction 0x2515ed0, static_id: 2 +11301489: cap 0: Create spark for conjunction: 0x2515ed0 spark: 0x24 +11301772: cap 0: Start a parallel conjunction 0x2515f30, static_id: 2 +11301961: cap 0: Create spark for conjunction: 0x2515f30 spark: 0x25 +11302245: cap 0: Start a parallel conjunction 0x2515f90, static_id: 2 +11302438: cap 0: Create spark for conjunction: 0x2515f90 spark: 0x26 +11302726: cap 0: Start a parallel conjunction 0x2515ff0, static_id: 2 +11302929: cap 0: Create spark for conjunction: 0x2515ff0 spark: 0x27 +11303212: cap 0: Start a parallel conjunction 0x2516050, static_id: 2 +11303401: cap 0: Create spark for conjunction: 0x2516050 spark: 0x28 +11303698: cap 0: Start a parallel conjunction 0x25160b0, static_id: 2 +11303883: cap 0: Create spark for conjunction: 0x25160b0 spark: 0x29 +11304162: cap 0: Start a parallel conjunction 0x2516110, static_id: 2 +11304351: cap 0: Create spark for conjunction: 0x2516110 spark: 0x2a +11304630: cap 0: Start a parallel conjunction 0x2516170, static_id: 2 +11304814: cap 0: Create spark for conjunction: 0x2516170 spark: 0x2b +11305093: cap 0: Start a parallel conjunction 0x25161d0, static_id: 2 +11305287: cap 0: Create spark for conjunction: 0x25161d0 spark: 0x2c +11305566: cap 0: Start a parallel conjunction 0x2516230, static_id: 2 +11305759: cap 0: Create spark for conjunction: 0x2516230 spark: 0x2d +11306034: cap 0: Start a parallel conjunction 0x2516290, static_id: 2 +11306214: cap 0: Create spark for conjunction: 0x2516290 spark: 0x2e +11306493: cap 0: Start a parallel conjunction 0x25162f0, static_id: 2 +11306673: cap 0: Create spark for conjunction: 0x25162f0 spark: 0x2f +11306943: cap 0: Start a parallel conjunction 0x2516350, static_id: 2 +11307127: cap 0: Create spark for conjunction: 0x2516350 spark: 0x30 +11307402: cap 0: Start a parallel conjunction 0x25163b0, static_id: 2 +11307586: cap 0: Create spark for conjunction: 0x25163b0 spark: 0x31 +11307852: cap 0: Start a parallel conjunction 0x2516410, static_id: 2 +11308036: cap 0: Create spark for conjunction: 0x2516410 spark: 0x32 +11308320: cap 0: Start a parallel conjunction 0x2516470, static_id: 2 +11308509: cap 0: Create spark for conjunction: 0x2516470 spark: 0x33 +11308788: cap 0: Start a parallel conjunction 0x25164d0, static_id: 2 +11308990: cap 0: Create spark for conjunction: 0x25164d0 spark: 0x34 +11309265: cap 0: Start a parallel conjunction 0x2516530, static_id: 2 +11309445: cap 0: Create spark for conjunction: 0x2516530 spark: 0x35 +11309751: cap 0: Start a parallel conjunction 0x2516590, static_id: 2 +11309931: cap 0: Create spark for conjunction: 0x2516590 spark: 0x36 +11310196: cap 0: Start a parallel conjunction 0x25165f0, static_id: 2 +11310394: cap 0: Create spark for conjunction: 0x25165f0 spark: 0x37 +11310678: cap 0: Start a parallel conjunction 0x2516650, static_id: 2 +11310867: cap 0: Create spark for conjunction: 0x2516650 spark: 0x38 +11311155: cap 0: Start a parallel conjunction 0x25166b0, static_id: 2 +11311339: cap 0: Create spark for conjunction: 0x25166b0 spark: 0x39 +11311609: cap 0: Start a parallel conjunction 0x2516710, static_id: 2 +11311794: cap 0: Create spark for conjunction: 0x2516710 spark: 0x3a +11312073: cap 0: Start a parallel conjunction 0x2516770, static_id: 2 +11312253: cap 0: Create spark for conjunction: 0x2516770 spark: 0x3b +11312532: cap 0: Start a parallel conjunction 0x25167d0, static_id: 2 +11312721: cap 0: Create spark for conjunction: 0x25167d0 spark: 0x3c +11313000: cap 0: Start a parallel conjunction 0x2516830, static_id: 2 +11313211: cap 0: Create spark for conjunction: 0x2516830 spark: 0x3d +11313490: cap 0: Start a parallel conjunction 0x2516890, static_id: 2 +11313670: cap 0: Create spark for conjunction: 0x2516890 spark: 0x3e +11313954: cap 0: Start a parallel conjunction 0x25168f0, static_id: 2 +11314138: cap 0: Create spark for conjunction: 0x25168f0 spark: 0x3f +11314399: cap 0: Start a parallel conjunction 0x2516950, static_id: 2 +11314593: cap 0: Create spark for conjunction: 0x2516950 spark: 0x40 +11314872: cap 0: Start a parallel conjunction 0x25169b0, static_id: 2 +11358931: cap 0: Create spark for conjunction: 0x25169b0 spark: 0x41 +11359269: cap 0: Start a parallel conjunction 0x2516a10, static_id: 2 +11359453: cap 0: Create spark for conjunction: 0x2516a10 spark: 0x42 +11359755: cap 0: Start a parallel conjunction 0x2516a70, static_id: 2 +11359948: cap 0: Create spark for conjunction: 0x2516a70 spark: 0x43 +11360232: cap 0: Start a parallel conjunction 0x2516ad0, static_id: 2 +11360421: cap 0: Create spark for conjunction: 0x2516ad0 spark: 0x44 +11360700: cap 0: Start a parallel conjunction 0x2516b30, static_id: 2 +11360902: cap 0: Create spark for conjunction: 0x2516b30 spark: 0x45 +11361181: cap 0: Start a parallel conjunction 0x2516b90, static_id: 2 +11361370: cap 0: Create spark for conjunction: 0x2516b90 spark: 0x46 +11361645: cap 0: Start a parallel conjunction 0x2516bf0, static_id: 2 +11361843: cap 0: Create spark for conjunction: 0x2516bf0 spark: 0x47 +11362117: cap 0: Start a parallel conjunction 0x2516c50, static_id: 2 +11362302: cap 0: Create spark for conjunction: 0x2516c50 spark: 0x48 +11362599: cap 0: Start a parallel conjunction 0x2516cb0, static_id: 2 +11362810: cap 0: Create spark for conjunction: 0x2516cb0 spark: 0x49 +11363089: cap 0: Start a parallel conjunction 0x2516d10, static_id: 2 +11363274: cap 0: Create spark for conjunction: 0x2516d10 spark: 0x4a +11363553: cap 0: Start a parallel conjunction 0x2516d70, static_id: 2 +11363742: cap 0: Create spark for conjunction: 0x2516d70 spark: 0x4b +11364021: cap 0: Start a parallel conjunction 0x2516dd0, static_id: 2 +11364205: cap 0: Create spark for conjunction: 0x2516dd0 spark: 0x4c +11364480: cap 0: Start a parallel conjunction 0x2516e30, static_id: 2 +11364682: cap 0: Create spark for conjunction: 0x2516e30 spark: 0x4d +11364948: cap 0: Start a parallel conjunction 0x2516e90, static_id: 2 +11365128: cap 0: Create spark for conjunction: 0x2516e90 spark: 0x4e +11365420: cap 0: Start a parallel conjunction 0x2516ef0, static_id: 2 +11365609: cap 0: Create spark for conjunction: 0x2516ef0 spark: 0x4f +11365879: cap 0: Start a parallel conjunction 0x2516f50, static_id: 2 +11366059: cap 0: Create spark for conjunction: 0x2516f50 spark: 0x50 +11366338: cap 0: Start a parallel conjunction 0x2516fb0, static_id: 2 +11366527: cap 0: Create spark for conjunction: 0x2516fb0 spark: 0x51 +11366833: cap 0: Start a parallel conjunction 0x2517010, static_id: 2 +11367022: cap 0: Create spark for conjunction: 0x2517010 spark: 0x52 +11367319: cap 0: Start a parallel conjunction 0x2517070, static_id: 2 +11367513: cap 0: Create spark for conjunction: 0x2517070 spark: 0x53 +11367778: cap 0: Start a parallel conjunction 0x25170d0, static_id: 2 +11367972: cap 0: Create spark for conjunction: 0x25170d0 spark: 0x54 +11368246: cap 0: Start a parallel conjunction 0x2517130, static_id: 2 +11368444: cap 0: Create spark for conjunction: 0x2517130 spark: 0x55 +11368723: cap 0: Start a parallel conjunction 0x2517190, static_id: 2 +11368908: cap 0: Create spark for conjunction: 0x2517190 spark: 0x56 +11369182: cap 0: Start a parallel conjunction 0x25171f0, static_id: 2 +11369385: cap 0: Create spark for conjunction: 0x25171f0 spark: 0x57 +11369664: cap 0: Start a parallel conjunction 0x2517250, static_id: 2 +11369853: cap 0: Create spark for conjunction: 0x2517250 spark: 0x58 +11370136: cap 0: Start a parallel conjunction 0x25172b0, static_id: 2 +11370334: cap 0: Create spark for conjunction: 0x25172b0 spark: 0x59 +11370609: cap 0: Start a parallel conjunction 0x2517310, static_id: 2 +11370811: cap 0: Create spark for conjunction: 0x2517310 spark: 0x5a +11371090: cap 0: Start a parallel conjunction 0x2517370, static_id: 2 +11371297: cap 0: Create spark for conjunction: 0x2517370 spark: 0x5b +11371702: cap 0: Start a parallel conjunction 0x25173d0, static_id: 2 +11371887: cap 0: Create spark for conjunction: 0x25173d0 spark: 0x5c +11372152: cap 0: Start a parallel conjunction 0x2517430, static_id: 2 +11372463: cap 0: Create spark for conjunction: 0x2517430 spark: 0x5d +11372746: cap 0: Start a parallel conjunction 0x2517490, static_id: 2 +11372931: cap 0: Create spark for conjunction: 0x2517490 spark: 0x5e +11373349: cap 0: Start a parallel conjunction 0x25174f0, static_id: 2 +11373552: cap 0: Create spark for conjunction: 0x25174f0 spark: 0x5f +11373831: cap 0: Start a parallel conjunction 0x2517550, static_id: 2 +11374024: cap 0: Create spark for conjunction: 0x2517550 spark: 0x60 +11374299: cap 0: Start a parallel conjunction 0x25175b0, static_id: 2 +11374492: cap 0: Create spark for conjunction: 0x25175b0 spark: 0x61 +11374758: cap 0: Start a parallel conjunction 0x2517610, static_id: 2 +11374942: cap 0: Create spark for conjunction: 0x2517610 spark: 0x62 +11375221: cap 0: Start a parallel conjunction 0x2517670, static_id: 2 +11375415: cap 0: Create spark for conjunction: 0x2517670 spark: 0x63 +11375671: cap 0: Start a parallel conjunction 0x25176d0, static_id: 2 +11375865: cap 0: Create spark for conjunction: 0x25176d0 spark: 0x64 +11376148: cap 0: Start a parallel conjunction 0x2517730, static_id: 2 +11376342: cap 0: Create spark for conjunction: 0x2517730 spark: 0x65 +11376616: cap 0: Start a parallel conjunction 0x2517790, static_id: 2 +11376805: cap 0: Create spark for conjunction: 0x2517790 spark: 0x66 +11377062: cap 0: Start a parallel conjunction 0x25177f0, static_id: 2 +11377264: cap 0: Create spark for conjunction: 0x25177f0 spark: 0x67 +11377539: cap 0: Start a parallel conjunction 0x2517850, static_id: 2 +11377723: cap 0: Create spark for conjunction: 0x2517850 spark: 0x68 +11378007: cap 0: Start a parallel conjunction 0x25178b0, static_id: 2 +11378205: cap 0: Create spark for conjunction: 0x25178b0 spark: 0x69 +11378484: cap 0: Start a parallel conjunction 0x2517910, static_id: 2 +11378677: cap 0: Create spark for conjunction: 0x2517910 spark: 0x6a +11378965: cap 0: Start a parallel conjunction 0x2517970, static_id: 2 +11379168: cap 0: Create spark for conjunction: 0x2517970 spark: 0x6b +11379465: cap 0: Start a parallel conjunction 0x25179d0, static_id: 2 +11379649: cap 0: Create spark for conjunction: 0x25179d0 spark: 0x6c +11379915: cap 0: Start a parallel conjunction 0x2517a30, static_id: 2 +11380117: cap 0: Create spark for conjunction: 0x2517a30 spark: 0x6d +11380378: cap 0: Start a parallel conjunction 0x2517a90, static_id: 2 +11380558: cap 0: Create spark for conjunction: 0x2517a90 spark: 0x6e +11380837: cap 0: Start a parallel conjunction 0x2517af0, static_id: 2 +11381040: cap 0: Create spark for conjunction: 0x2517af0 spark: 0x6f +11381296: cap 0: Start a parallel conjunction 0x2517b50, static_id: 2 +11381481: cap 0: Create spark for conjunction: 0x2517b50 spark: 0x70 +11381751: cap 0: Start a parallel conjunction 0x2517bb0, static_id: 2 +11381953: cap 0: Create spark for conjunction: 0x2517bb0 spark: 0x71 +11382219: cap 0: Start a parallel conjunction 0x2517c10, static_id: 2 +11382412: cap 0: Create spark for conjunction: 0x2517c10 spark: 0x72 +11382700: cap 0: Start a parallel conjunction 0x2517c70, static_id: 2 +11382912: cap 0: Create spark for conjunction: 0x2517c70 spark: 0x73 +11383195: cap 0: Start a parallel conjunction 0x2517cd0, static_id: 2 +11383402: cap 0: Create spark for conjunction: 0x2517cd0 spark: 0x74 +11383672: cap 0: Start a parallel conjunction 0x2517d30, static_id: 2 +11383875: cap 0: Create spark for conjunction: 0x2517d30 spark: 0x75 +11384163: cap 0: Start a parallel conjunction 0x2517d90, static_id: 2 +11384352: cap 0: Create spark for conjunction: 0x2517d90 spark: 0x76 +11384622: cap 0: Start a parallel conjunction 0x2517df0, static_id: 2 +11384824: cap 0: Create spark for conjunction: 0x2517df0 spark: 0x77 +11385099: cap 0: Start a parallel conjunction 0x2517e50, static_id: 2 +11385288: cap 0: Create spark for conjunction: 0x2517e50 spark: 0x78 +11385567: cap 0: Start a parallel conjunction 0x2517eb0, static_id: 2 +11385765: cap 0: Create spark for conjunction: 0x2517eb0 spark: 0x79 +11386021: cap 0: Start a parallel conjunction 0x2517f10, static_id: 2 +11386210: cap 0: Create spark for conjunction: 0x2517f10 spark: 0x7a +11386480: cap 0: Start a parallel conjunction 0x2517f70, static_id: 2 +11386674: cap 0: Create spark for conjunction: 0x2517f70 spark: 0x7b +11386971: cap 0: Start a parallel conjunction 0x2517fd0, static_id: 2 +11387160: cap 0: Create spark for conjunction: 0x2517fd0 spark: 0x7c +11387475: cap 0: Start a parallel conjunction 0x2518030, static_id: 2 +11387695: cap 0: Create spark for conjunction: 0x2518030 spark: 0x7d +11388001: cap 0: Start a parallel conjunction 0x2518090, static_id: 2 +11388190: cap 0: Create spark for conjunction: 0x2518090 spark: 0x7e +11388496: cap 0: Start a parallel conjunction 0x25180f0, static_id: 2 +11388699: cap 0: Create spark for conjunction: 0x25180f0 spark: 0x7f +11388960: cap 0: Start a parallel conjunction 0x2518150, static_id: 2 +11389144: cap 0: Create spark for conjunction: 0x2518150 spark: 0x80 +11389423: cap 0: Start a parallel conjunction 0x25181b0, static_id: 2 +11409403: cap 0: Create spark for conjunction: 0x25181b0 spark: 0x81 +11409732: cap 0: Start a parallel conjunction 0x2518210, static_id: 2 +11409930: cap 0: Create spark for conjunction: 0x2518210 spark: 0x82 +11410236: cap 0: Start a parallel conjunction 0x2518270, static_id: 2 +11410425: cap 0: Create spark for conjunction: 0x2518270 spark: 0x83 +11410699: cap 0: Start a parallel conjunction 0x25182d0, static_id: 2 +11410947: cap 0: Create spark for conjunction: 0x25182d0 spark: 0x84 +11411226: cap 0: Start a parallel conjunction 0x2518330, static_id: 2 +11411406: cap 0: Create spark for conjunction: 0x2518330 spark: 0x85 +11411694: cap 0: Start a parallel conjunction 0x2518390, static_id: 2 +11411874: cap 0: Create spark for conjunction: 0x2518390 spark: 0x86 +11412135: cap 0: Start a parallel conjunction 0x25183f0, static_id: 2 +11412337: cap 0: Create spark for conjunction: 0x25183f0 spark: 0x87 +11412621: cap 0: Start a parallel conjunction 0x2518450, static_id: 2 +11412868: cap 0: Create spark for conjunction: 0x2518450 spark: 0x88 +11413170: cap 0: Start a parallel conjunction 0x25184b0, static_id: 2 +11413363: cap 0: Create spark for conjunction: 0x25184b0 spark: 0x89 +11413638: cap 0: Start a parallel conjunction 0x2518510, static_id: 2 +11413822: cap 0: Create spark for conjunction: 0x2518510 spark: 0x8a +11414218: cap 0: Start a parallel conjunction 0x2518570, static_id: 2 +11414461: cap 0: Create spark for conjunction: 0x2518570 spark: 0x8b +11414758: cap 0: Start a parallel conjunction 0x25185d0, static_id: 2 +11414938: cap 0: Create spark for conjunction: 0x25185d0 spark: 0x8c +11415213: cap 0: Start a parallel conjunction 0x2518630, static_id: 2 +11415415: cap 0: Create spark for conjunction: 0x2518630 spark: 0x8d +11415685: cap 0: Start a parallel conjunction 0x2518690, static_id: 2 +11415865: cap 0: Create spark for conjunction: 0x2518690 spark: 0x8e +11416149: cap 0: Start a parallel conjunction 0x25186f0, static_id: 2 +11416333: cap 0: Create spark for conjunction: 0x25186f0 spark: 0x8f +11416603: cap 0: Start a parallel conjunction 0x2518750, static_id: 2 +11416788: cap 0: Create spark for conjunction: 0x2518750 spark: 0x90 +11417067: cap 0: Start a parallel conjunction 0x25187b0, static_id: 2 +11417256: cap 0: Create spark for conjunction: 0x25187b0 spark: 0x91 +11417530: cap 0: Start a parallel conjunction 0x2518810, static_id: 2 +11417715: cap 0: Create spark for conjunction: 0x2518810 spark: 0x92 +11418012: cap 0: Start a parallel conjunction 0x2518870, static_id: 2 +11418205: cap 0: Create spark for conjunction: 0x2518870 spark: 0x93 +11418471: cap 0: Start a parallel conjunction 0x25188d0, static_id: 2 +11418669: cap 0: Create spark for conjunction: 0x25188d0 spark: 0x94 +11418961: cap 0: Start a parallel conjunction 0x2518930, static_id: 2 +11419150: cap 0: Create spark for conjunction: 0x2518930 spark: 0x95 +11419434: cap 0: Start a parallel conjunction 0x2518990, static_id: 2 +11419618: cap 0: Create spark for conjunction: 0x2518990 spark: 0x96 +11419879: cap 0: Start a parallel conjunction 0x25189f0, static_id: 2 +11420077: cap 0: Create spark for conjunction: 0x25189f0 spark: 0x97 +11420352: cap 0: Start a parallel conjunction 0x2518a50, static_id: 2 +11420536: cap 0: Create spark for conjunction: 0x2518a50 spark: 0x98 +11420838: cap 0: Start a parallel conjunction 0x2518ab0, static_id: 2 +11421036: cap 0: Create spark for conjunction: 0x2518ab0 spark: 0x99 +11421315: cap 0: Start a parallel conjunction 0x2518b10, static_id: 2 +11421513: cap 0: Create spark for conjunction: 0x2518b10 spark: 0x9a +11421792: cap 0: Start a parallel conjunction 0x2518b70, static_id: 2 +11421985: cap 0: Create spark for conjunction: 0x2518b70 spark: 0x9b +11422264: cap 0: Start a parallel conjunction 0x2518bd0, static_id: 2 +11422449: cap 0: Create spark for conjunction: 0x2518bd0 spark: 0x9c +11422737: cap 0: Start a parallel conjunction 0x2518c30, static_id: 2 +11422939: cap 0: Create spark for conjunction: 0x2518c30 spark: 0x9d +11423209: cap 0: Start a parallel conjunction 0x2518c90, static_id: 2 +11423403: cap 0: Create spark for conjunction: 0x2518c90 spark: 0x9e +11423686: cap 0: Start a parallel conjunction 0x2518cf0, static_id: 2 +11423871: cap 0: Create spark for conjunction: 0x2518cf0 spark: 0x9f +11424136: cap 0: Start a parallel conjunction 0x2518d50, static_id: 2 +11424316: cap 0: Create spark for conjunction: 0x2518d50 spark: 0xa0 +11424586: cap 0: Start a parallel conjunction 0x2518db0, static_id: 2 +11424780: cap 0: Create spark for conjunction: 0x2518db0 spark: 0xa1 +11425050: cap 0: Start a parallel conjunction 0x2518e10, static_id: 2 +11425234: cap 0: Create spark for conjunction: 0x2518e10 spark: 0xa2 +11425536: cap 0: Start a parallel conjunction 0x2518e70, static_id: 2 +11425725: cap 0: Create spark for conjunction: 0x2518e70 spark: 0xa3 +11425995: cap 0: Start a parallel conjunction 0x2518ed0, static_id: 2 +11426184: cap 0: Create spark for conjunction: 0x2518ed0 spark: 0xa4 +11426458: cap 0: Start a parallel conjunction 0x2518f30, static_id: 2 +11426643: cap 0: Create spark for conjunction: 0x2518f30 spark: 0xa5 +11426935: cap 0: Start a parallel conjunction 0x2518f90, static_id: 2 +11427151: cap 0: Create spark for conjunction: 0x2518f90 spark: 0xa6 +11427466: cap 0: Start a parallel conjunction 0x2518ff0, static_id: 2 +11427673: cap 0: Create spark for conjunction: 0x2518ff0 spark: 0xa7 +11427952: cap 0: Start a parallel conjunction 0x2519050, static_id: 2 +11428141: cap 0: Create spark for conjunction: 0x2519050 spark: 0xa8 +11428429: cap 0: Start a parallel conjunction 0x25190b0, static_id: 2 +11428609: cap 0: Create spark for conjunction: 0x25190b0 spark: 0xa9 +11428875: cap 0: Start a parallel conjunction 0x2519110, static_id: 2 +11429064: cap 0: Create spark for conjunction: 0x2519110 spark: 0xaa +11429365: cap 0: Start a parallel conjunction 0x2519170, static_id: 2 +11429554: cap 0: Create spark for conjunction: 0x2519170 spark: 0xab +11429842: cap 0: Start a parallel conjunction 0x25191d0, static_id: 2 +11430036: cap 0: Create spark for conjunction: 0x25191d0 spark: 0xac +11430310: cap 0: Start a parallel conjunction 0x2519230, static_id: 2 +11430504: cap 0: Create spark for conjunction: 0x2519230 spark: 0xad +11430774: cap 0: Start a parallel conjunction 0x2519290, static_id: 2 +11430954: cap 0: Create spark for conjunction: 0x2519290 spark: 0xae +11431246: cap 0: Start a parallel conjunction 0x25192f0, static_id: 2 +11431431: cap 0: Create spark for conjunction: 0x25192f0 spark: 0xaf +11431696: cap 0: Start a parallel conjunction 0x2519350, static_id: 2 +11431885: cap 0: Create spark for conjunction: 0x2519350 spark: 0xb0 +11432164: cap 0: Start a parallel conjunction 0x25193b0, static_id: 2 +11432358: cap 0: Create spark for conjunction: 0x25193b0 spark: 0xb1 +11432632: cap 0: Start a parallel conjunction 0x2519410, static_id: 2 +11432821: cap 0: Create spark for conjunction: 0x2519410 spark: 0xb2 +11433213: cap 0: Start a parallel conjunction 0x2519470, static_id: 2 +11433406: cap 0: Create spark for conjunction: 0x2519470 spark: 0xb3 +11433681: cap 0: Start a parallel conjunction 0x25194d0, static_id: 2 +11433892: cap 0: Create spark for conjunction: 0x25194d0 spark: 0xb4 +11434185: cap 0: Start a parallel conjunction 0x2519530, static_id: 2 +11434378: cap 0: Create spark for conjunction: 0x2519530 spark: 0xb5 +11434657: cap 0: Start a parallel conjunction 0x2519590, static_id: 2 +11434842: cap 0: Create spark for conjunction: 0x2519590 spark: 0xb6 +11435107: cap 0: Start a parallel conjunction 0x25195f0, static_id: 2 +11435323: cap 0: Create spark for conjunction: 0x25195f0 spark: 0xb7 +11435611: cap 0: Start a parallel conjunction 0x2519650, static_id: 2 +11435805: cap 0: Create spark for conjunction: 0x2519650 spark: 0xb8 +11436237: cap 0: Start a parallel conjunction 0x25196b0, static_id: 2 +11436421: cap 0: Create spark for conjunction: 0x25196b0 spark: 0xb9 +11436682: cap 0: Start a parallel conjunction 0x2519710, static_id: 2 +11436979: cap 0: Create spark for conjunction: 0x2519710 spark: 0xba +11437285: cap 0: Start a parallel conjunction 0x2519770, static_id: 2 +11437488: cap 0: Create spark for conjunction: 0x2519770 spark: 0xbb +11437834: cap 0: Start a parallel conjunction 0x25197d0, static_id: 2 +11438028: cap 0: Create spark for conjunction: 0x25197d0 spark: 0xbc +11438311: cap 0: Start a parallel conjunction 0x2519830, static_id: 2 +11438500: cap 0: Create spark for conjunction: 0x2519830 spark: 0xbd +11438770: cap 0: Start a parallel conjunction 0x2519890, static_id: 2 +11438959: cap 0: Create spark for conjunction: 0x2519890 spark: 0xbe +11439243: cap 0: Start a parallel conjunction 0x25198f0, static_id: 2 +11439432: cap 0: Create spark for conjunction: 0x25198f0 spark: 0xbf +11439693: cap 0: Start a parallel conjunction 0x2519950, static_id: 2 +11439886: cap 0: Create spark for conjunction: 0x2519950 spark: 0xc0 +11440170: cap 0: Start a parallel conjunction 0x25199b0, static_id: 2 +11440363: cap 0: Create spark for conjunction: 0x25199b0 spark: 0xc1 +11440633: cap 0: Start a parallel conjunction 0x2519a10, static_id: 2 +11440818: cap 0: Create spark for conjunction: 0x2519a10 spark: 0xc2 +11441097: cap 0: Start a parallel conjunction 0x2519a70, static_id: 2 +11441290: cap 0: Create spark for conjunction: 0x2519a70 spark: 0xc3 +11441560: cap 0: Start a parallel conjunction 0x2519ad0, static_id: 2 +11441749: cap 0: Create spark for conjunction: 0x2519ad0 spark: 0xc4 +11442037: cap 0: Start a parallel conjunction 0x2519b30, static_id: 2 +11442235: cap 0: Create spark for conjunction: 0x2519b30 spark: 0xc5 +11442514: cap 0: Start a parallel conjunction 0x2519b90, static_id: 2 +11442699: cap 0: Create spark for conjunction: 0x2519b90 spark: 0xc6 +11442964: cap 0: Start a parallel conjunction 0x2519bf0, static_id: 2 +11443167: cap 0: Create spark for conjunction: 0x2519bf0 spark: 0xc7 +11443446: cap 0: Start a parallel conjunction 0x2519c50, static_id: 2 +11443635: cap 0: Create spark for conjunction: 0x2519c50 spark: 0xc8 +11444053: cap 0: Start a parallel conjunction 0x2519cb0, static_id: 2 +11444251: cap 0: Create spark for conjunction: 0x2519cb0 spark: 0xc9 +11444517: cap 0: Start a parallel conjunction 0x2519d10, static_id: 2 +11444701: cap 0: Create spark for conjunction: 0x2519d10 spark: 0xca +11444971: cap 0: Start a parallel conjunction 0x2519d70, static_id: 2 +11445165: cap 0: Create spark for conjunction: 0x2519d70 spark: 0xcb +11445453: cap 0: Start a parallel conjunction 0x2519dd0, static_id: 2 +11445637: cap 0: Create spark for conjunction: 0x2519dd0 spark: 0xcc +11445912: cap 0: Start a parallel conjunction 0x2519e30, static_id: 2 +11446101: cap 0: Create spark for conjunction: 0x2519e30 spark: 0xcd +11446380: cap 0: Start a parallel conjunction 0x2519e90, static_id: 2 +11446564: cap 0: Create spark for conjunction: 0x2519e90 spark: 0xce +11446848: cap 0: Start a parallel conjunction 0x2519ef0, static_id: 2 +11447041: cap 0: Create spark for conjunction: 0x2519ef0 spark: 0xcf +11447316: cap 0: Start a parallel conjunction 0x2519f50, static_id: 2 +11447505: cap 0: Create spark for conjunction: 0x2519f50 spark: 0xd0 +11447793: cap 0: Start a parallel conjunction 0x2519fb0, static_id: 2 +11447991: cap 0: Create spark for conjunction: 0x2519fb0 spark: 0xd1 +11448544: cap 0: Start a parallel conjunction 0x251a010, static_id: 2 +11448729: cap 0: Create spark for conjunction: 0x251a010 spark: 0xd2 +11449026: cap 0: Start a parallel conjunction 0x251a070, static_id: 2 +11449206: cap 0: Create spark for conjunction: 0x251a070 spark: 0xd3 +11449480: cap 0: Start a parallel conjunction 0x251a0d0, static_id: 2 +11449678: cap 0: Create spark for conjunction: 0x251a0d0 spark: 0xd4 +11449957: cap 0: Start a parallel conjunction 0x251a130, static_id: 2 +11450155: cap 0: Create spark for conjunction: 0x251a130 spark: 0xd5 +11450443: cap 0: Start a parallel conjunction 0x251a190, static_id: 2 +11450623: cap 0: Create spark for conjunction: 0x251a190 spark: 0xd6 +11450884: cap 0: Start a parallel conjunction 0x251a1f0, static_id: 2 +11451087: cap 0: Create spark for conjunction: 0x251a1f0 spark: 0xd7 +11451370: cap 0: Start a parallel conjunction 0x251a250, static_id: 2 +11451555: cap 0: Create spark for conjunction: 0x251a250 spark: 0xd8 +11451852: cap 0: Start a parallel conjunction 0x251a2b0, static_id: 2 +11452041: cap 0: Create spark for conjunction: 0x251a2b0 spark: 0xd9 +11452311: cap 0: Start a parallel conjunction 0x251a310, static_id: 2 +11452500: cap 0: Create spark for conjunction: 0x251a310 spark: 0xda +11452779: cap 0: Start a parallel conjunction 0x251a370, static_id: 2 +11452968: cap 0: Create spark for conjunction: 0x251a370 spark: 0xdb +11453247: cap 0: Start a parallel conjunction 0x251a3d0, static_id: 2 +11453427: cap 0: Create spark for conjunction: 0x251a3d0 spark: 0xdc +11453701: cap 0: Start a parallel conjunction 0x251a430, static_id: 2 +11453904: cap 0: Create spark for conjunction: 0x251a430 spark: 0xdd +11454174: cap 0: Start a parallel conjunction 0x251a490, static_id: 2 +11454354: cap 0: Create spark for conjunction: 0x251a490 spark: 0xde +11454637: cap 0: Start a parallel conjunction 0x251a4f0, static_id: 2 +11454826: cap 0: Create spark for conjunction: 0x251a4f0 spark: 0xdf +11455092: cap 0: Start a parallel conjunction 0x251a550, static_id: 2 +11455272: cap 0: Create spark for conjunction: 0x251a550 spark: 0xe0 +11455546: cap 0: Start a parallel conjunction 0x251a5b0, static_id: 2 +11455731: cap 0: Create spark for conjunction: 0x251a5b0 spark: 0xe1 +11456014: cap 0: Start a parallel conjunction 0x251a610, static_id: 2 +11456199: cap 0: Create spark for conjunction: 0x251a610 spark: 0xe2 +11456487: cap 0: Start a parallel conjunction 0x251a670, static_id: 2 +11456676: cap 0: Create spark for conjunction: 0x251a670 spark: 0xe3 +11456946: cap 0: Start a parallel conjunction 0x251a6d0, static_id: 2 +11457148: cap 0: Create spark for conjunction: 0x251a6d0 spark: 0xe4 +11457445: cap 0: Start a parallel conjunction 0x251a730, static_id: 2 +11457639: cap 0: Create spark for conjunction: 0x251a730 spark: 0xe5 +11457927: cap 0: Start a parallel conjunction 0x251a790, static_id: 2 +11458107: cap 0: Create spark for conjunction: 0x251a790 spark: 0xe6 +11458372: cap 0: Start a parallel conjunction 0x251a7f0, static_id: 2 +11458566: cap 0: Create spark for conjunction: 0x251a7f0 spark: 0xe7 +11458836: cap 0: Start a parallel conjunction 0x251a850, static_id: 2 +11459020: cap 0: Create spark for conjunction: 0x251a850 spark: 0xe8 +11459299: cap 0: Start a parallel conjunction 0x251a8b0, static_id: 2 +11459493: cap 0: Create spark for conjunction: 0x251a8b0 spark: 0xe9 +11459758: cap 0: Start a parallel conjunction 0x251a910, static_id: 2 +11466868: cap 0: Create spark for conjunction: 0x251a910 spark: 0xea +11467057: cap 0: Start a parallel conjunction 0x251a970, static_id: 2 +11467179: cap 0: Create spark for conjunction: 0x251a970 spark: 0xeb +11467372: cap 0: Start a parallel conjunction 0x251a9d0, static_id: 2 +11467494: cap 0: Create spark for conjunction: 0x251a9d0 spark: 0xec +11467683: cap 0: Start a parallel conjunction 0x251aa30, static_id: 2 +11467809: cap 0: Create spark for conjunction: 0x251aa30 spark: 0xed +11467993: cap 0: Start a parallel conjunction 0x251aa90, static_id: 2 +11468115: cap 0: Create spark for conjunction: 0x251aa90 spark: 0xee +11468304: cap 0: Start a parallel conjunction 0x251aaf0, static_id: 2 +11468434: cap 0: Create spark for conjunction: 0x251aaf0 spark: 0xef +11468619: cap 0: Start a parallel conjunction 0x251ab50, static_id: 2 +11468740: cap 0: Create spark for conjunction: 0x251ab50 spark: 0xf0 +11468920: cap 0: Start a parallel conjunction 0x251abb0, static_id: 2 +11469046: cap 0: Create spark for conjunction: 0x251abb0 spark: 0xf1 +11469226: cap 0: Start a parallel conjunction 0x251ac10, static_id: 2 +11469348: cap 0: Create spark for conjunction: 0x251ac10 spark: 0xf2 +11469532: cap 0: Start a parallel conjunction 0x251ac70, static_id: 2 +11469658: cap 0: Create spark for conjunction: 0x251ac70 spark: 0xf3 +11469834: cap 0: Start a parallel conjunction 0x251acd0, static_id: 2 +11469960: cap 0: Create spark for conjunction: 0x251acd0 spark: 0xf4 +11470144: cap 0: Start a parallel conjunction 0x251ad30, static_id: 2 +11470270: cap 0: Create spark for conjunction: 0x251ad30 spark: 0xf5 +11470464: cap 0: Start a parallel conjunction 0x251ad90, static_id: 2 +11470585: cap 0: Create spark for conjunction: 0x251ad90 spark: 0xf6 +11470761: cap 0: Start a parallel conjunction 0x251adf0, static_id: 2 +11470887: cap 0: Create spark for conjunction: 0x251adf0 spark: 0xf7 +11471071: cap 0: Start a parallel conjunction 0x251ae50, static_id: 2 +11471193: cap 0: Create spark for conjunction: 0x251ae50 spark: 0xf8 +11471391: cap 0: Start a parallel conjunction 0x251aeb0, static_id: 2 +11471512: cap 0: Create spark for conjunction: 0x251aeb0 spark: 0xf9 +11471692: cap 0: Start a parallel conjunction 0x251af10, static_id: 2 +11471818: cap 0: Create spark for conjunction: 0x251af10 spark: 0xfa +11472223: cap 0: Start a parallel conjunction 0x251af70, static_id: 2 +11472349: cap 0: Create spark for conjunction: 0x251af70 spark: 0xfb +11472718: cap 0: Start a parallel conjunction 0x251afd0, static_id: 2 +11472844: cap 0: Create spark for conjunction: 0x251afd0 spark: 0xfc +11473209: cap 0: Start a parallel conjunction 0x251b030, static_id: 2 +11473339: cap 0: Create spark for conjunction: 0x251b030 spark: 0xfd +11473524: cap 0: Start a parallel conjunction 0x251b090, static_id: 2 +11473645: cap 0: Create spark for conjunction: 0x251b090 spark: 0xfe +11473834: cap 0: Start a parallel conjunction 0x251b0f0, static_id: 2 +11473956: cap 0: Create spark for conjunction: 0x251b0f0 spark: 0xff +11474136: cap 0: Start a parallel conjunction 0x251b150, static_id: 2 +11474257: cap 0: Create spark for conjunction: 0x251b150 spark: 0x100 +11474446: cap 0: Start a parallel conjunction 0x251b1b0, static_id: 2 +11497689: cap 0: Create spark for conjunction: 0x251b1b0 spark: 0x101 +11497918: cap 0: Start a parallel conjunction 0x251b210, static_id: 2 +11498053: cap 0: Create spark for conjunction: 0x251b210 spark: 0x102 +11498256: cap 0: Start a parallel conjunction 0x251b270, static_id: 2 +11498391: cap 0: Create spark for conjunction: 0x251b270 spark: 0x103 +11498566: cap 0: Start a parallel conjunction 0x251b2d0, static_id: 2 +11498742: cap 0: Create spark for conjunction: 0x251b2d0 spark: 0x104 +11498926: cap 0: Start a parallel conjunction 0x251b330, static_id: 2 +11499057: cap 0: Create spark for conjunction: 0x251b330 spark: 0x105 +11499246: cap 0: Start a parallel conjunction 0x251b390, static_id: 2 +11499372: cap 0: Create spark for conjunction: 0x251b390 spark: 0x106 +11499561: cap 0: Start a parallel conjunction 0x251b3f0, static_id: 2 +11499696: cap 0: Create spark for conjunction: 0x251b3f0 spark: 0x107 +11499876: cap 0: Start a parallel conjunction 0x251b450, static_id: 2 +11500042: cap 0: Create spark for conjunction: 0x251b450 spark: 0x108 +11500245: cap 0: Start a parallel conjunction 0x251b4b0, static_id: 2 +11500375: cap 0: Create spark for conjunction: 0x251b4b0 spark: 0x109 +11500555: cap 0: Start a parallel conjunction 0x251b510, static_id: 2 +11500681: cap 0: Create spark for conjunction: 0x251b510 spark: 0x10a +11500866: cap 0: Start a parallel conjunction 0x251b570, static_id: 2 +11500987: cap 0: Create spark for conjunction: 0x251b570 spark: 0x10b +11501176: cap 0: Start a parallel conjunction 0x251b5d0, static_id: 2 +11501307: cap 0: Create spark for conjunction: 0x251b5d0 spark: 0x10c +11501496: cap 0: Start a parallel conjunction 0x251b630, static_id: 2 +11501631: cap 0: Create spark for conjunction: 0x251b630 spark: 0x10d +11501815: cap 0: Start a parallel conjunction 0x251b690, static_id: 2 +11501937: cap 0: Create spark for conjunction: 0x251b690 spark: 0x10e +11502135: cap 0: Start a parallel conjunction 0x251b6f0, static_id: 2 +11502274: cap 0: Create spark for conjunction: 0x251b6f0 spark: 0x10f +11502445: cap 0: Start a parallel conjunction 0x251b750, static_id: 2 +11502567: cap 0: Create spark for conjunction: 0x251b750 spark: 0x110 +11502769: cap 0: Start a parallel conjunction 0x251b7b0, static_id: 2 +11502895: cap 0: Create spark for conjunction: 0x251b7b0 spark: 0x111 +11503075: cap 0: Start a parallel conjunction 0x251b810, static_id: 2 +11503192: cap 0: Create spark for conjunction: 0x251b810 spark: 0x112 +11503377: cap 0: Start a parallel conjunction 0x251b870, static_id: 2 +11503507: cap 0: Create spark for conjunction: 0x251b870 spark: 0x113 +11503687: cap 0: Start a parallel conjunction 0x251b8d0, static_id: 2 +11503818: cap 0: Create spark for conjunction: 0x251b8d0 spark: 0x114 +11504007: cap 0: Start a parallel conjunction 0x251b930, static_id: 2 +11504137: cap 0: Create spark for conjunction: 0x251b930 spark: 0x115 +11504470: cap 0: Start a parallel conjunction 0x251b990, static_id: 2 +11504592: cap 0: Create spark for conjunction: 0x251b990 spark: 0x116 +11504790: cap 0: Start a parallel conjunction 0x251b9f0, static_id: 2 +11505217: cap 0: Create spark for conjunction: 0x251b9f0 spark: 0x117 +11505402: cap 0: Start a parallel conjunction 0x251ba50, static_id: 2 +11505523: cap 0: Create spark for conjunction: 0x251ba50 spark: 0x118 +11505721: cap 0: Start a parallel conjunction 0x251bab0, static_id: 2 +11505852: cap 0: Create spark for conjunction: 0x251bab0 spark: 0x119 +11506041: cap 0: Start a parallel conjunction 0x251bb10, static_id: 2 +11506167: cap 0: Create spark for conjunction: 0x251bb10 spark: 0x11a +11506369: cap 0: Start a parallel conjunction 0x251bb70, static_id: 2 +11506500: cap 0: Create spark for conjunction: 0x251bb70 spark: 0x11b +11506689: cap 0: Start a parallel conjunction 0x251bbd0, static_id: 2 +11506810: cap 0: Create spark for conjunction: 0x251bbd0 spark: 0x11c +11506990: cap 0: Start a parallel conjunction 0x251bc30, static_id: 2 +11507130: cap 0: Create spark for conjunction: 0x251bc30 spark: 0x11d +11507310: cap 0: Start a parallel conjunction 0x251bc90, static_id: 2 +11507431: cap 0: Create spark for conjunction: 0x251bc90 spark: 0x11e +11507620: cap 0: Start a parallel conjunction 0x251bcf0, static_id: 2 +11507751: cap 0: Create spark for conjunction: 0x251bcf0 spark: 0x11f +11507926: cap 0: Start a parallel conjunction 0x251bd50, static_id: 2 +11508052: cap 0: Create spark for conjunction: 0x251bd50 spark: 0x120 +11508237: cap 0: Start a parallel conjunction 0x251bdb0, static_id: 2 +11508363: cap 0: Create spark for conjunction: 0x251bdb0 spark: 0x121 +11508556: cap 0: Start a parallel conjunction 0x251be10, static_id: 2 +11508682: cap 0: Create spark for conjunction: 0x251be10 spark: 0x122 +11508889: cap 0: Start a parallel conjunction 0x251be70, static_id: 2 +11509020: cap 0: Create spark for conjunction: 0x251be70 spark: 0x123 +11509200: cap 0: Start a parallel conjunction 0x251bed0, static_id: 2 +11509326: cap 0: Create spark for conjunction: 0x251bed0 spark: 0x124 +11509510: cap 0: Start a parallel conjunction 0x251bf30, static_id: 2 +11509636: cap 0: Create spark for conjunction: 0x251bf30 spark: 0x125 +11509929: cap 0: Start a parallel conjunction 0x251bf90, static_id: 2 +11510050: cap 0: Create spark for conjunction: 0x251bf90 spark: 0x126 +11510361: cap 0: Start a parallel conjunction 0x251bff0, static_id: 2 +11510496: cap 0: Create spark for conjunction: 0x251bff0 spark: 0x127 +11510685: cap 0: Start a parallel conjunction 0x251c050, static_id: 2 +11510811: cap 0: Create spark for conjunction: 0x251c050 spark: 0x128 +11511000: cap 0: Start a parallel conjunction 0x251c0b0, static_id: 2 +11511126: cap 0: Create spark for conjunction: 0x251c0b0 spark: 0x129 +11511301: cap 0: Start a parallel conjunction 0x251c110, static_id: 2 +11511427: cap 0: Create spark for conjunction: 0x251c110 spark: 0x12a +11511612: cap 0: Start a parallel conjunction 0x251c170, static_id: 2 +11511733: cap 0: Create spark for conjunction: 0x251c170 spark: 0x12b +11511918: cap 0: Start a parallel conjunction 0x251c1d0, static_id: 2 +11512039: cap 0: Create spark for conjunction: 0x251c1d0 spark: 0x12c +11512219: cap 0: Start a parallel conjunction 0x251c230, static_id: 2 +11512345: cap 0: Create spark for conjunction: 0x251c230 spark: 0x12d +11512530: cap 0: Start a parallel conjunction 0x251c290, static_id: 2 +11512647: cap 0: Create spark for conjunction: 0x251c290 spark: 0x12e +11512939: cap 0: Start a parallel conjunction 0x251c2f0, static_id: 2 +11513061: cap 0: Create spark for conjunction: 0x251c2f0 spark: 0x12f +11513232: cap 0: Start a parallel conjunction 0x251c350, static_id: 2 +11513353: cap 0: Create spark for conjunction: 0x251c350 spark: 0x130 +11513538: cap 0: Start a parallel conjunction 0x251c3b0, static_id: 2 +11513664: cap 0: Create spark for conjunction: 0x251c3b0 spark: 0x131 +11513839: cap 0: Start a parallel conjunction 0x251c410, static_id: 2 +11513961: cap 0: Create spark for conjunction: 0x251c410 spark: 0x132 +11514267: cap 0: Start a parallel conjunction 0x251c470, static_id: 2 +11514397: cap 0: Create spark for conjunction: 0x251c470 spark: 0x133 +11514568: cap 0: Start a parallel conjunction 0x251c4d0, static_id: 2 +11514699: cap 0: Create spark for conjunction: 0x251c4d0 spark: 0x134 +11514892: cap 0: Start a parallel conjunction 0x251c530, static_id: 2 +11515027: cap 0: Create spark for conjunction: 0x251c530 spark: 0x135 +11515225: cap 0: Start a parallel conjunction 0x251c590, static_id: 2 +11515351: cap 0: Create spark for conjunction: 0x251c590 spark: 0x136 +11515531: cap 0: Start a parallel conjunction 0x251c5f0, static_id: 2 +11515662: cap 0: Create spark for conjunction: 0x251c5f0 spark: 0x137 +11515846: cap 0: Start a parallel conjunction 0x251c650, static_id: 2 +11515972: cap 0: Create spark for conjunction: 0x251c650 spark: 0x138 +11516175: cap 0: Start a parallel conjunction 0x251c6b0, static_id: 2 +11516296: cap 0: Create spark for conjunction: 0x251c6b0 spark: 0x139 +11516476: cap 0: Start a parallel conjunction 0x251c710, static_id: 2 +11516598: cap 0: Create spark for conjunction: 0x251c710 spark: 0x13a +11516782: cap 0: Start a parallel conjunction 0x251c770, static_id: 2 +11516908: cap 0: Create spark for conjunction: 0x251c770 spark: 0x13b +11517093: cap 0: Start a parallel conjunction 0x251c7d0, static_id: 2 +11517214: cap 0: Create spark for conjunction: 0x251c7d0 spark: 0x13c +11517394: cap 0: Start a parallel conjunction 0x251c830, static_id: 2 +11517529: cap 0: Create spark for conjunction: 0x251c830 spark: 0x13d +11517705: cap 0: Start a parallel conjunction 0x251c890, static_id: 2 +11517826: cap 0: Create spark for conjunction: 0x251c890 spark: 0x13e +11518011: cap 0: Start a parallel conjunction 0x251c8f0, static_id: 2 +11518141: cap 0: Create spark for conjunction: 0x251c8f0 spark: 0x13f +11518317: cap 0: Start a parallel conjunction 0x251c950, static_id: 2 +11518443: cap 0: Create spark for conjunction: 0x251c950 spark: 0x140 +11518627: cap 0: Start a parallel conjunction 0x251c9b0, static_id: 2 +11518758: cap 0: Create spark for conjunction: 0x251c9b0 spark: 0x141 +11518942: cap 0: Start a parallel conjunction 0x251ca10, static_id: 2 +11519068: cap 0: Create spark for conjunction: 0x251ca10 spark: 0x142 +11519257: cap 0: Start a parallel conjunction 0x251ca70, static_id: 2 +11519383: cap 0: Create spark for conjunction: 0x251ca70 spark: 0x143 +11519563: cap 0: Start a parallel conjunction 0x251cad0, static_id: 2 +11519694: cap 0: Create spark for conjunction: 0x251cad0 spark: 0x144 +11519878: cap 0: Start a parallel conjunction 0x251cb30, static_id: 2 +11520009: cap 0: Create spark for conjunction: 0x251cb30 spark: 0x145 +11520198: cap 0: Start a parallel conjunction 0x251cb90, static_id: 2 +11520319: cap 0: Create spark for conjunction: 0x251cb90 spark: 0x146 +11520490: cap 0: Start a parallel conjunction 0x251cbf0, static_id: 2 +11520621: cap 0: Create spark for conjunction: 0x251cbf0 spark: 0x147 +11520801: cap 0: Start a parallel conjunction 0x251cc50, static_id: 2 +11520922: cap 0: Create spark for conjunction: 0x251cc50 spark: 0x148 +11521111: cap 0: Start a parallel conjunction 0x251ccb0, static_id: 2 +11521251: cap 0: Create spark for conjunction: 0x251ccb0 spark: 0x149 +11521422: cap 0: Start a parallel conjunction 0x251cd10, static_id: 2 +11521548: cap 0: Create spark for conjunction: 0x251cd10 spark: 0x14a +11521741: cap 0: Start a parallel conjunction 0x251cd70, static_id: 2 +11521876: cap 0: Create spark for conjunction: 0x251cd70 spark: 0x14b +11522065: cap 0: Start a parallel conjunction 0x251cdd0, static_id: 2 +11522187: cap 0: Create spark for conjunction: 0x251cdd0 spark: 0x14c +11522371: cap 0: Start a parallel conjunction 0x251ce30, static_id: 2 +11522506: cap 0: Create spark for conjunction: 0x251ce30 spark: 0x14d +11522686: cap 0: Start a parallel conjunction 0x251ce90, static_id: 2 +11522808: cap 0: Create spark for conjunction: 0x251ce90 spark: 0x14e +11522992: cap 0: Start a parallel conjunction 0x251cef0, static_id: 2 +11523118: cap 0: Create spark for conjunction: 0x251cef0 spark: 0x14f +11523298: cap 0: Start a parallel conjunction 0x251cf50, static_id: 2 +11523424: cap 0: Create spark for conjunction: 0x251cf50 spark: 0x150 +11523609: cap 0: Start a parallel conjunction 0x251cfb0, static_id: 2 +11523739: cap 0: Create spark for conjunction: 0x251cfb0 spark: 0x151 +11524059: cap 0: Start a parallel conjunction 0x251d010, static_id: 2 +11524180: cap 0: Create spark for conjunction: 0x251d010 spark: 0x152 +11524378: cap 0: Start a parallel conjunction 0x251d070, static_id: 2 +11524518: cap 0: Create spark for conjunction: 0x251d070 spark: 0x153 +11524698: cap 0: Start a parallel conjunction 0x251d0d0, static_id: 2 +11524828: cap 0: Create spark for conjunction: 0x251d0d0 spark: 0x154 +11525013: cap 0: Start a parallel conjunction 0x251d130, static_id: 2 +11525134: cap 0: Create spark for conjunction: 0x251d130 spark: 0x155 +11525319: cap 0: Start a parallel conjunction 0x251d190, static_id: 2 +11525449: cap 0: Create spark for conjunction: 0x251d190 spark: 0x156 +11525625: cap 0: Start a parallel conjunction 0x251d1f0, static_id: 2 +11525760: cap 0: Create spark for conjunction: 0x251d1f0 spark: 0x157 +11525940: cap 0: Start a parallel conjunction 0x251d250, static_id: 2 +11526061: cap 0: Create spark for conjunction: 0x251d250 spark: 0x158 +11526250: cap 0: Start a parallel conjunction 0x251d2b0, static_id: 2 +11526381: cap 0: Create spark for conjunction: 0x251d2b0 spark: 0x159 +11526556: cap 0: Start a parallel conjunction 0x251d310, static_id: 2 +11526678: cap 0: Create spark for conjunction: 0x251d310 spark: 0x15a +11527038: cap 0: Start a parallel conjunction 0x251d370, static_id: 2 +11527168: cap 0: Create spark for conjunction: 0x251d370 spark: 0x15b +11527357: cap 0: Start a parallel conjunction 0x251d3d0, static_id: 2 +11527479: cap 0: Create spark for conjunction: 0x251d3d0 spark: 0x15c +11527659: cap 0: Start a parallel conjunction 0x251d430, static_id: 2 +11527794: cap 0: Create spark for conjunction: 0x251d430 spark: 0x15d +11527974: cap 0: Start a parallel conjunction 0x251d490, static_id: 2 +11528095: cap 0: Create spark for conjunction: 0x251d490 spark: 0x15e +11528293: cap 0: Start a parallel conjunction 0x251d4f0, static_id: 2 +11528424: cap 0: Create spark for conjunction: 0x251d4f0 spark: 0x15f +11528608: cap 0: Start a parallel conjunction 0x251d550, static_id: 2 +11528730: cap 0: Create spark for conjunction: 0x251d550 spark: 0x160 +11528914: cap 0: Start a parallel conjunction 0x251d5b0, static_id: 2 +11529049: cap 0: Create spark for conjunction: 0x251d5b0 spark: 0x161 +11529234: cap 0: Start a parallel conjunction 0x251d610, static_id: 2 +11529355: cap 0: Create spark for conjunction: 0x251d610 spark: 0x162 +11529567: cap 0: Start a parallel conjunction 0x251d670, static_id: 2 +11529693: cap 0: Create spark for conjunction: 0x251d670 spark: 0x163 +11529877: cap 0: Start a parallel conjunction 0x251d6d0, static_id: 2 +11530003: cap 0: Create spark for conjunction: 0x251d6d0 spark: 0x164 +11530197: cap 0: Start a parallel conjunction 0x251d730, static_id: 2 +11530323: cap 0: Create spark for conjunction: 0x251d730 spark: 0x165 +11530512: cap 0: Start a parallel conjunction 0x251d790, static_id: 2 +11530633: cap 0: Create spark for conjunction: 0x251d790 spark: 0x166 +11530809: cap 0: Start a parallel conjunction 0x251d7f0, static_id: 2 +11530944: cap 0: Create spark for conjunction: 0x251d7f0 spark: 0x167 +11531124: cap 0: Start a parallel conjunction 0x251d850, static_id: 2 +11531245: cap 0: Create spark for conjunction: 0x251d850 spark: 0x168 +11531430: cap 0: Start a parallel conjunction 0x251d8b0, static_id: 2 +11531556: cap 0: Create spark for conjunction: 0x251d8b0 spark: 0x169 +11531731: cap 0: Start a parallel conjunction 0x251d910, static_id: 2 +11531853: cap 0: Create spark for conjunction: 0x251d910 spark: 0x16a +11532033: cap 0: Start a parallel conjunction 0x251d970, static_id: 2 +11532163: cap 0: Create spark for conjunction: 0x251d970 spark: 0x16b +11532348: cap 0: Start a parallel conjunction 0x251d9d0, static_id: 2 +11532469: cap 0: Create spark for conjunction: 0x251d9d0 spark: 0x16c +11532649: cap 0: Start a parallel conjunction 0x251da30, static_id: 2 +11532784: cap 0: Create spark for conjunction: 0x251da30 spark: 0x16d +11532969: cap 0: Start a parallel conjunction 0x251da90, static_id: 2 +11533090: cap 0: Create spark for conjunction: 0x251da90 spark: 0x16e +11533279: cap 0: Start a parallel conjunction 0x251daf0, static_id: 2 +11533405: cap 0: Create spark for conjunction: 0x251daf0 spark: 0x16f +11533590: cap 0: Start a parallel conjunction 0x251db50, static_id: 2 +11533711: cap 0: Create spark for conjunction: 0x251db50 spark: 0x170 +11533887: cap 0: Start a parallel conjunction 0x251dbb0, static_id: 2 +11534017: cap 0: Create spark for conjunction: 0x251dbb0 spark: 0x171 +11534202: cap 0: Start a parallel conjunction 0x251dc10, static_id: 2 +11534323: cap 0: Create spark for conjunction: 0x251dc10 spark: 0x172 +11534656: cap 0: Start a parallel conjunction 0x251dc70, static_id: 2 +11534787: cap 0: Create spark for conjunction: 0x251dc70 spark: 0x173 +11534962: cap 0: Start a parallel conjunction 0x251dcd0, static_id: 2 +11535309: cap 0: Create spark for conjunction: 0x251dcd0 spark: 0x174 +11535507: cap 0: Start a parallel conjunction 0x251dd30, static_id: 2 +11535633: cap 0: Create spark for conjunction: 0x251dd30 spark: 0x175 +11535817: cap 0: Start a parallel conjunction 0x251dd90, static_id: 2 +11535939: cap 0: Create spark for conjunction: 0x251dd90 spark: 0x176 +11536114: cap 0: Start a parallel conjunction 0x251ddf0, static_id: 2 +11536249: cap 0: Create spark for conjunction: 0x251ddf0 spark: 0x177 +11536443: cap 0: Start a parallel conjunction 0x251de50, static_id: 2 +11536569: cap 0: Create spark for conjunction: 0x251de50 spark: 0x178 +11536771: cap 0: Start a parallel conjunction 0x251deb0, static_id: 2 +11536902: cap 0: Create spark for conjunction: 0x251deb0 spark: 0x179 +11537091: cap 0: Start a parallel conjunction 0x251df10, static_id: 2 +11537212: cap 0: Create spark for conjunction: 0x251df10 spark: 0x17a +11537397: cap 0: Start a parallel conjunction 0x251df70, static_id: 2 +11537523: cap 0: Create spark for conjunction: 0x251df70 spark: 0x17b +11537820: cap 0: Start a parallel conjunction 0x251dfd0, static_id: 2 +11537941: cap 0: Create spark for conjunction: 0x251dfd0 spark: 0x17c +11538261: cap 0: Start a parallel conjunction 0x251e030, static_id: 2 +11538396: cap 0: Create spark for conjunction: 0x251e030 spark: 0x17d +11538576: cap 0: Start a parallel conjunction 0x251e090, static_id: 2 +11538697: cap 0: Create spark for conjunction: 0x251e090 spark: 0x17e +11538882: cap 0: Start a parallel conjunction 0x251e0f0, static_id: 2 +11539012: cap 0: Create spark for conjunction: 0x251e0f0 spark: 0x17f +11539188: cap 0: Start a parallel conjunction 0x251e150, static_id: 2 +11539314: cap 0: Create spark for conjunction: 0x251e150 spark: 0x180 +11539507: cap 0: Start a parallel conjunction 0x251e1b0, static_id: 2 +11539638: cap 0: Create spark for conjunction: 0x251e1b0 spark: 0x181 +11539822: cap 0: Start a parallel conjunction 0x251e210, static_id: 2 +11539944: cap 0: Create spark for conjunction: 0x251e210 spark: 0x182 +11540137: cap 0: Start a parallel conjunction 0x251e270, static_id: 2 +11540272: cap 0: Create spark for conjunction: 0x251e270 spark: 0x183 +11540448: cap 0: Start a parallel conjunction 0x251e2d0, static_id: 2 +11540614: cap 0: Create spark for conjunction: 0x251e2d0 spark: 0x184 +11540803: cap 0: Start a parallel conjunction 0x251e330, static_id: 2 +11540929: cap 0: Create spark for conjunction: 0x251e330 spark: 0x185 +11541118: cap 0: Start a parallel conjunction 0x251e390, static_id: 2 +11541240: cap 0: Create spark for conjunction: 0x251e390 spark: 0x186 +11541577: cap 0: Start a parallel conjunction 0x251e3f0, static_id: 2 +11541712: cap 0: Create spark for conjunction: 0x251e3f0 spark: 0x187 +11541897: cap 0: Start a parallel conjunction 0x251e450, static_id: 2 +11542059: cap 0: Create spark for conjunction: 0x251e450 spark: 0x188 +11542261: cap 0: Start a parallel conjunction 0x251e4b0, static_id: 2 +11542383: cap 0: Create spark for conjunction: 0x251e4b0 spark: 0x189 +11542558: cap 0: Start a parallel conjunction 0x251e510, static_id: 2 +11542680: cap 0: Create spark for conjunction: 0x251e510 spark: 0x18a +11542864: cap 0: Start a parallel conjunction 0x251e570, static_id: 2 +11542990: cap 0: Create spark for conjunction: 0x251e570 spark: 0x18b +11543175: cap 0: Start a parallel conjunction 0x251e5d0, static_id: 2 +11543296: cap 0: Create spark for conjunction: 0x251e5d0 spark: 0x18c +11543476: cap 0: Start a parallel conjunction 0x251e630, static_id: 2 +11543620: cap 0: Create spark for conjunction: 0x251e630 spark: 0x18d +11543800: cap 0: Start a parallel conjunction 0x251e690, static_id: 2 +11543922: cap 0: Create spark for conjunction: 0x251e690 spark: 0x18e +11544111: cap 0: Start a parallel conjunction 0x251e6f0, static_id: 2 +11544241: cap 0: Create spark for conjunction: 0x251e6f0 spark: 0x18f +11544417: cap 0: Start a parallel conjunction 0x251e750, static_id: 2 +11544547: cap 0: Create spark for conjunction: 0x251e750 spark: 0x190 +11544732: cap 0: Start a parallel conjunction 0x251e7b0, static_id: 2 +11544858: cap 0: Create spark for conjunction: 0x251e7b0 spark: 0x191 +11545042: cap 0: Start a parallel conjunction 0x251e810, static_id: 2 +11545164: cap 0: Create spark for conjunction: 0x251e810 spark: 0x192 +11545353: cap 0: Start a parallel conjunction 0x251e870, static_id: 2 +11545479: cap 0: Create spark for conjunction: 0x251e870 spark: 0x193 +11545659: cap 0: Start a parallel conjunction 0x251e8d0, static_id: 2 +11545785: cap 0: Create spark for conjunction: 0x251e8d0 spark: 0x194 +11545974: cap 0: Start a parallel conjunction 0x251e930, static_id: 2 +11546100: cap 0: Create spark for conjunction: 0x251e930 spark: 0x195 +11546293: cap 0: Start a parallel conjunction 0x251e990, static_id: 2 +11546415: cap 0: Create spark for conjunction: 0x251e990 spark: 0x196 +11546590: cap 0: Start a parallel conjunction 0x251e9f0, static_id: 2 +11546725: cap 0: Create spark for conjunction: 0x251e9f0 spark: 0x197 +11546910: cap 0: Start a parallel conjunction 0x251ea50, static_id: 2 +11547036: cap 0: Create spark for conjunction: 0x251ea50 spark: 0x198 +11547243: cap 0: Start a parallel conjunction 0x251eab0, static_id: 2 +11547378: cap 0: Create spark for conjunction: 0x251eab0 spark: 0x199 +11547562: cap 0: Start a parallel conjunction 0x251eb10, static_id: 2 +11547684: cap 0: Create spark for conjunction: 0x251eb10 spark: 0x19a +11547868: cap 0: Start a parallel conjunction 0x251eb70, static_id: 2 +11547990: cap 0: Create spark for conjunction: 0x251eb70 spark: 0x19b +11548174: cap 0: Start a parallel conjunction 0x251ebd0, static_id: 2 +11548296: cap 0: Create spark for conjunction: 0x251ebd0 spark: 0x19c +11548476: cap 0: Start a parallel conjunction 0x251ec30, static_id: 2 +11548602: cap 0: Create spark for conjunction: 0x251ec30 spark: 0x19d +11548782: cap 0: Start a parallel conjunction 0x251ec90, static_id: 2 +11548903: cap 0: Create spark for conjunction: 0x251ec90 spark: 0x19e +11549092: cap 0: Start a parallel conjunction 0x251ecf0, static_id: 2 +11549223: cap 0: Create spark for conjunction: 0x251ecf0 spark: 0x19f +11549403: cap 0: Start a parallel conjunction 0x251ed50, static_id: 2 +11549524: cap 0: Create spark for conjunction: 0x251ed50 spark: 0x1a0 +11549709: cap 0: Start a parallel conjunction 0x251edb0, static_id: 2 +11549839: cap 0: Create spark for conjunction: 0x251edb0 spark: 0x1a1 +11550019: cap 0: Start a parallel conjunction 0x251ee10, static_id: 2 +11550141: cap 0: Create spark for conjunction: 0x251ee10 spark: 0x1a2 +11550330: cap 0: Start a parallel conjunction 0x251ee70, static_id: 2 +11550465: cap 0: Create spark for conjunction: 0x251ee70 spark: 0x1a3 +11550658: cap 0: Start a parallel conjunction 0x251eed0, static_id: 2 +11550784: cap 0: Create spark for conjunction: 0x251eed0 spark: 0x1a4 +11550982: cap 0: Start a parallel conjunction 0x251ef30, static_id: 2 +11551108: cap 0: Create spark for conjunction: 0x251ef30 spark: 0x1a5 +11551293: cap 0: Start a parallel conjunction 0x251ef90, static_id: 2 +11551419: cap 0: Create spark for conjunction: 0x251ef90 spark: 0x1a6 +11551752: cap 0: Start a parallel conjunction 0x251eff0, static_id: 2 +11551887: cap 0: Create spark for conjunction: 0x251eff0 spark: 0x1a7 +11552076: cap 0: Start a parallel conjunction 0x251f050, static_id: 2 +11552197: cap 0: Create spark for conjunction: 0x251f050 spark: 0x1a8 +11552386: cap 0: Start a parallel conjunction 0x251f0b0, static_id: 2 +11552517: cap 0: Create spark for conjunction: 0x251f0b0 spark: 0x1a9 +11552755: cap 0: Start a parallel conjunction 0x251f110, static_id: 2 +11552886: cap 0: Create spark for conjunction: 0x251f110 spark: 0x1aa +11553066: cap 0: Start a parallel conjunction 0x251f170, static_id: 2 +11553196: cap 0: Create spark for conjunction: 0x251f170 spark: 0x1ab +11553390: cap 0: Start a parallel conjunction 0x251f1d0, static_id: 2 +11553511: cap 0: Create spark for conjunction: 0x251f1d0 spark: 0x1ac +11553696: cap 0: Start a parallel conjunction 0x251f230, static_id: 2 +11553835: cap 0: Create spark for conjunction: 0x251f230 spark: 0x1ad +11554015: cap 0: Start a parallel conjunction 0x251f290, static_id: 2 +11554146: cap 0: Create spark for conjunction: 0x251f290 spark: 0x1ae +11554330: cap 0: Start a parallel conjunction 0x251f2f0, static_id: 2 +11554465: cap 0: Create spark for conjunction: 0x251f2f0 spark: 0x1af +11554645: cap 0: Start a parallel conjunction 0x251f350, static_id: 2 +11554767: cap 0: Create spark for conjunction: 0x251f350 spark: 0x1b0 +11554956: cap 0: Start a parallel conjunction 0x251f3b0, static_id: 2 +11555082: cap 0: Create spark for conjunction: 0x251f3b0 spark: 0x1b1 +11555262: cap 0: Start a parallel conjunction 0x251f410, static_id: 2 +11555383: cap 0: Create spark for conjunction: 0x251f410 spark: 0x1b2 +11555662: cap 0: Start a parallel conjunction 0x251f470, static_id: 2 +11555788: cap 0: Create spark for conjunction: 0x251f470 spark: 0x1b3 +11555964: cap 0: Start a parallel conjunction 0x251f4d0, static_id: 2 +11556090: cap 0: Create spark for conjunction: 0x251f4d0 spark: 0x1b4 +11556270: cap 0: Start a parallel conjunction 0x251f530, static_id: 2 +11556391: cap 0: Create spark for conjunction: 0x251f530 spark: 0x1b5 +11556576: cap 0: Start a parallel conjunction 0x251f590, static_id: 2 +11556697: cap 0: Create spark for conjunction: 0x251f590 spark: 0x1b6 +11556877: cap 0: Start a parallel conjunction 0x251f5f0, static_id: 2 +11557008: cap 0: Create spark for conjunction: 0x251f5f0 spark: 0x1b7 +11557188: cap 0: Start a parallel conjunction 0x251f650, static_id: 2 +11557309: cap 0: Create spark for conjunction: 0x251f650 spark: 0x1b8 +11557503: cap 0: Start a parallel conjunction 0x251f6b0, static_id: 2 +11557638: cap 0: Create spark for conjunction: 0x251f6b0 spark: 0x1b9 +11557818: cap 0: Start a parallel conjunction 0x251f710, static_id: 2 +11557944: cap 0: Create spark for conjunction: 0x251f710 spark: 0x1ba +11558137: cap 0: Start a parallel conjunction 0x251f770, static_id: 2 +11558268: cap 0: Create spark for conjunction: 0x251f770 spark: 0x1bb +11558452: cap 0: Start a parallel conjunction 0x251f7d0, static_id: 2 +11558578: cap 0: Create spark for conjunction: 0x251f7d0 spark: 0x1bc +11558754: cap 0: Start a parallel conjunction 0x251f830, static_id: 2 +11558893: cap 0: Create spark for conjunction: 0x251f830 spark: 0x1bd +11559069: cap 0: Start a parallel conjunction 0x251f890, static_id: 2 +11559190: cap 0: Create spark for conjunction: 0x251f890 spark: 0x1be +11559375: cap 0: Start a parallel conjunction 0x251f8f0, static_id: 2 +11559505: cap 0: Create spark for conjunction: 0x251f8f0 spark: 0x1bf +11559681: cap 0: Start a parallel conjunction 0x251f950, static_id: 2 +11559802: cap 0: Create spark for conjunction: 0x251f950 spark: 0x1c0 +11559982: cap 0: Start a parallel conjunction 0x251f9b0, static_id: 2 +11560099: cap 0: Create spark for conjunction: 0x251f9b0 spark: 0x1c1 +11560279: cap 0: Start a parallel conjunction 0x251fa10, static_id: 2 +11560396: cap 0: Create spark for conjunction: 0x251fa10 spark: 0x1c2 +11560581: cap 0: Start a parallel conjunction 0x251fa70, static_id: 2 +11560711: cap 0: Create spark for conjunction: 0x251fa70 spark: 0x1c3 +11560896: cap 0: Start a parallel conjunction 0x251fad0, static_id: 2 +11561026: cap 0: Create spark for conjunction: 0x251fad0 spark: 0x1c4 +11561215: cap 0: Start a parallel conjunction 0x251fb30, static_id: 2 +11561350: cap 0: Create spark for conjunction: 0x251fb30 spark: 0x1c5 +11561539: cap 0: Start a parallel conjunction 0x251fb90, static_id: 2 +11561665: cap 0: Create spark for conjunction: 0x251fb90 spark: 0x1c6 +11561836: cap 0: Start a parallel conjunction 0x251fbf0, static_id: 2 +11561971: cap 0: Create spark for conjunction: 0x251fbf0 spark: 0x1c7 +11562151: cap 0: Start a parallel conjunction 0x251fc50, static_id: 2 +11562277: cap 0: Create spark for conjunction: 0x251fc50 spark: 0x1c8 +11562466: cap 0: Start a parallel conjunction 0x251fcb0, static_id: 2 +11562606: cap 0: Create spark for conjunction: 0x251fcb0 spark: 0x1c9 +11562781: cap 0: Start a parallel conjunction 0x251fd10, static_id: 2 +11562907: cap 0: Create spark for conjunction: 0x251fd10 spark: 0x1ca +11563087: cap 0: Start a parallel conjunction 0x251fd70, static_id: 2 +11563209: cap 0: Create spark for conjunction: 0x251fd70 spark: 0x1cb +11563402: cap 0: Start a parallel conjunction 0x251fdd0, static_id: 2 +11563524: cap 0: Create spark for conjunction: 0x251fdd0 spark: 0x1cc +11563713: cap 0: Start a parallel conjunction 0x251fe30, static_id: 2 +11563848: cap 0: Create spark for conjunction: 0x251fe30 spark: 0x1cd +11564032: cap 0: Start a parallel conjunction 0x251fe90, static_id: 2 +11564154: cap 0: Create spark for conjunction: 0x251fe90 spark: 0x1ce +11564338: cap 0: Start a parallel conjunction 0x251fef0, static_id: 2 +11564469: cap 0: Create spark for conjunction: 0x251fef0 spark: 0x1cf +11564640: cap 0: Start a parallel conjunction 0x251ff50, static_id: 2 +11564874: cap 0: Create spark for conjunction: 0x251ff50 spark: 0x1d0 +11565175: cap 0: Start a parallel conjunction 0x251ffb0, static_id: 2 +11565301: cap 0: Create spark for conjunction: 0x251ffb0 spark: 0x1d1 +11565711: cap 0: Start a parallel conjunction 0x2520010, static_id: 2 +11565832: cap 0: Create spark for conjunction: 0x2520010 spark: 0x1d2 +11566026: cap 0: Start a parallel conjunction 0x2520070, static_id: 2 +11566152: cap 0: Create spark for conjunction: 0x2520070 spark: 0x1d3 +11566327: cap 0: Start a parallel conjunction 0x25200d0, static_id: 2 +11566453: cap 0: Create spark for conjunction: 0x25200d0 spark: 0x1d4 +11566638: cap 0: Start a parallel conjunction 0x2520130, static_id: 2 +11566768: cap 0: Create spark for conjunction: 0x2520130 spark: 0x1d5 +11566966: cap 0: Start a parallel conjunction 0x2520190, static_id: 2 +11567088: cap 0: Create spark for conjunction: 0x2520190 spark: 0x1d6 +11567461: cap 0: Start a parallel conjunction 0x25201f0, static_id: 2 +11567596: cap 0: Create spark for conjunction: 0x25201f0 spark: 0x1d7 +11567781: cap 0: Start a parallel conjunction 0x2520250, static_id: 2 +11567907: cap 0: Create spark for conjunction: 0x2520250 spark: 0x1d8 +11568105: cap 0: Start a parallel conjunction 0x25202b0, static_id: 2 +11568226: cap 0: Create spark for conjunction: 0x25202b0 spark: 0x1d9 +11568397: cap 0: Start a parallel conjunction 0x2520310, static_id: 2 +11568523: cap 0: Create spark for conjunction: 0x2520310 spark: 0x1da +11568708: cap 0: Start a parallel conjunction 0x2520370, static_id: 2 +11568834: cap 0: Create spark for conjunction: 0x2520370 spark: 0x1db +11569018: cap 0: Start a parallel conjunction 0x25203d0, static_id: 2 +11569140: cap 0: Create spark for conjunction: 0x25203d0 spark: 0x1dc +11569320: cap 0: Start a parallel conjunction 0x2520430, static_id: 2 +11569455: cap 0: Create spark for conjunction: 0x2520430 spark: 0x1dd +11569630: cap 0: Start a parallel conjunction 0x2520490, static_id: 2 +11569752: cap 0: Create spark for conjunction: 0x2520490 spark: 0x1de +11569936: cap 0: Start a parallel conjunction 0x25204f0, static_id: 2 +11570067: cap 0: Create spark for conjunction: 0x25204f0 spark: 0x1df +11570242: cap 0: Start a parallel conjunction 0x2520550, static_id: 2 +11570364: cap 0: Create spark for conjunction: 0x2520550 spark: 0x1e0 +11570544: cap 0: Start a parallel conjunction 0x25205b0, static_id: 2 +11570670: cap 0: Create spark for conjunction: 0x25205b0 spark: 0x1e1 +11570850: cap 0: Start a parallel conjunction 0x2520610, static_id: 2 +11570971: cap 0: Create spark for conjunction: 0x2520610 spark: 0x1e2 +11571160: cap 0: Start a parallel conjunction 0x2520670, static_id: 2 +11571295: cap 0: Create spark for conjunction: 0x2520670 spark: 0x1e3 +11571466: cap 0: Start a parallel conjunction 0x25206d0, static_id: 2 +11571601: cap 0: Create spark for conjunction: 0x25206d0 spark: 0x1e4 +11571795: cap 0: Start a parallel conjunction 0x2520730, static_id: 2 +11571921: cap 0: Create spark for conjunction: 0x2520730 spark: 0x1e5 +11572114: cap 0: Start a parallel conjunction 0x2520790, static_id: 2 +11572240: cap 0: Create spark for conjunction: 0x2520790 spark: 0x1e6 +11572416: cap 0: Start a parallel conjunction 0x25207f0, static_id: 2 +11572546: cap 0: Create spark for conjunction: 0x25207f0 spark: 0x1e7 +11572735: cap 0: Start a parallel conjunction 0x2520850, static_id: 2 +11572861: cap 0: Create spark for conjunction: 0x2520850 spark: 0x1e8 +11573055: cap 0: Start a parallel conjunction 0x25208b0, static_id: 2 +11573190: cap 0: Create spark for conjunction: 0x25208b0 spark: 0x1e9 +11573365: cap 0: Start a parallel conjunction 0x2520910, static_id: 2 +11573487: cap 0: Create spark for conjunction: 0x2520910 spark: 0x1ea +11573676: cap 0: Start a parallel conjunction 0x2520970, static_id: 2 +11573802: cap 0: Create spark for conjunction: 0x2520970 spark: 0x1eb +11573986: cap 0: Start a parallel conjunction 0x25209d0, static_id: 2 +11574112: cap 0: Create spark for conjunction: 0x25209d0 spark: 0x1ec +11574288: cap 0: Start a parallel conjunction 0x2520a30, static_id: 2 +11574427: cap 0: Create spark for conjunction: 0x2520a30 spark: 0x1ed +11574603: cap 0: Start a parallel conjunction 0x2520a90, static_id: 2 +11574724: cap 0: Create spark for conjunction: 0x2520a90 spark: 0x1ee +11574909: cap 0: Start a parallel conjunction 0x2520af0, static_id: 2 +11575039: cap 0: Create spark for conjunction: 0x2520af0 spark: 0x1ef +11575219: cap 0: Start a parallel conjunction 0x2520b50, static_id: 2 +11575341: cap 0: Create spark for conjunction: 0x2520b50 spark: 0x1f0 +11575521: cap 0: Start a parallel conjunction 0x2520bb0, static_id: 2 +11575647: cap 0: Create spark for conjunction: 0x2520bb0 spark: 0x1f1 +11575827: cap 0: Start a parallel conjunction 0x2520c10, static_id: 2 +11575948: cap 0: Create spark for conjunction: 0x2520c10 spark: 0x1f2 +11576137: cap 0: Start a parallel conjunction 0x2520c70, static_id: 2 +11576277: cap 0: Create spark for conjunction: 0x2520c70 spark: 0x1f3 +11576452: cap 0: Start a parallel conjunction 0x2520cd0, static_id: 2 +11576578: cap 0: Create spark for conjunction: 0x2520cd0 spark: 0x1f4 +11576772: cap 0: Start a parallel conjunction 0x2520d30, static_id: 2 +11576898: cap 0: Create spark for conjunction: 0x2520d30 spark: 0x1f5 +11577087: cap 0: Start a parallel conjunction 0x2520d90, static_id: 2 +11577208: cap 0: Create spark for conjunction: 0x2520d90 spark: 0x1f6 +11577393: cap 0: Start a parallel conjunction 0x2520df0, static_id: 2 +11577523: cap 0: Create spark for conjunction: 0x2520df0 spark: 0x1f7 +11577712: cap 0: Start a parallel conjunction 0x2520e50, static_id: 2 +11577834: cap 0: Create spark for conjunction: 0x2520e50 spark: 0x1f8 +11578032: cap 0: Start a parallel conjunction 0x2520eb0, static_id: 2 +11578153: cap 0: Create spark for conjunction: 0x2520eb0 spark: 0x1f9 +11578324: cap 0: Start a parallel conjunction 0x2520f10, static_id: 2 +11578450: cap 0: Create spark for conjunction: 0x2520f10 spark: 0x1fa +11578635: cap 0: Start a parallel conjunction 0x2520f70, static_id: 2 +11578765: cap 0: Create spark for conjunction: 0x2520f70 spark: 0x1fb +11579089: cap 0: Start a parallel conjunction 0x2520fd0, static_id: 2 +11579211: cap 0: Create spark for conjunction: 0x2520fd0 spark: 0x1fc +11579530: cap 0: Start a parallel conjunction 0x2521030, static_id: 2 +11579670: cap 0: Create spark for conjunction: 0x2521030 spark: 0x1fd +11579850: cap 0: Start a parallel conjunction 0x2521090, static_id: 2 +11579971: cap 0: Create spark for conjunction: 0x2521090 spark: 0x1fe +11580160: cap 0: Start a parallel conjunction 0x25210f0, static_id: 2 +11580291: cap 0: Create spark for conjunction: 0x25210f0 spark: 0x1ff +11580466: cap 0: Start a parallel conjunction 0x2521150, static_id: 2 +11580588: cap 0: Create spark for conjunction: 0x2521150 spark: 0x200 +11580772: cap 0: Start a parallel conjunction 0x25211b0, static_id: 2 +11625201: cap 1: Trying to steal a spark +11626915: cap 1: stealing a spark from cap 0 +11631217: cap 0: Create spark for conjunction: 0x25211b0 spark: 0x201 +11631456: cap 0: Start a parallel conjunction 0x2521210, static_id: 2 +11631586: cap 0: Create spark for conjunction: 0x2521210 spark: 0x202 +11631789: cap 0: Start a parallel conjunction 0x2521270, static_id: 2 +11631924: cap 0: Create spark for conjunction: 0x2521270 spark: 0x203 +11632104: cap 0: Start a parallel conjunction 0x25212d0, static_id: 2 +11632243: cap 0: Create spark for conjunction: 0x25212d0 spark: 0x204 +11632437: cap 0: Start a parallel conjunction 0x2521330, static_id: 2 +11632567: cap 0: Create spark for conjunction: 0x2521330 spark: 0x205 +11632756: cap 0: Start a parallel conjunction 0x2521390, static_id: 2 +11632882: cap 0: Create spark for conjunction: 0x2521390 spark: 0x206 +11633062: cap 0: Start a parallel conjunction 0x25213f0, static_id: 2 +11633206: cap 0: Create spark for conjunction: 0x25213f0 spark: 0x207 +11633395: cap 0: Start a parallel conjunction 0x2521450, static_id: 2 +11633526: cap 0: Create spark for conjunction: 0x2521450 spark: 0x208 +11633737: cap 0: Start a parallel conjunction 0x25214b0, static_id: 2 +11633872: cap 0: Create spark for conjunction: 0x25214b0 spark: 0x209 +11634057: cap 0: Start a parallel conjunction 0x2521510, static_id: 2 +11634183: cap 0: Create spark for conjunction: 0x2521510 spark: 0x20a +11634381: cap 0: Start a parallel conjunction 0x2521570, static_id: 2 +11634511: cap 0: Create spark for conjunction: 0x2521570 spark: 0x20b +11634705: cap 0: Start a parallel conjunction 0x25215d0, static_id: 2 +11634831: cap 0: Create spark for conjunction: 0x25215d0 spark: 0x20c +11635015: cap 0: Start a parallel conjunction 0x2521630, static_id: 2 +11635159: cap 0: Create spark for conjunction: 0x2521630 spark: 0x20d +11635344: cap 0: Start a parallel conjunction 0x2521690, static_id: 2 +11635465: cap 0: Create spark for conjunction: 0x2521690 spark: 0x20e +11635659: cap 0: Start a parallel conjunction 0x25216f0, static_id: 2 +11635789: cap 0: Create spark for conjunction: 0x25216f0 spark: 0x20f +11636037: cap 0: Start a parallel conjunction 0x2521750, static_id: 2 +11636158: cap 0: Create spark for conjunction: 0x2521750 spark: 0x210 +11636343: cap 0: Start a parallel conjunction 0x25217b0, static_id: 2 +11636473: cap 0: Create spark for conjunction: 0x25217b0 spark: 0x211 +11636649: cap 0: Start a parallel conjunction 0x2521810, static_id: 2 +11636770: cap 0: Create spark for conjunction: 0x2521810 spark: 0x212 +11636964: cap 0: Start a parallel conjunction 0x2521870, static_id: 2 +11637099: cap 0: Create spark for conjunction: 0x2521870 spark: 0x213 +11637283: cap 0: Start a parallel conjunction 0x25218d0, static_id: 2 +11637409: cap 0: Create spark for conjunction: 0x25218d0 spark: 0x214 +11637589: cap 0: Start a parallel conjunction 0x2521930, static_id: 2 +11637729: cap 0: Create spark for conjunction: 0x2521930 spark: 0x215 +11637931: cap 0: Start a parallel conjunction 0x2521990, static_id: 2 +11638062: cap 0: Create spark for conjunction: 0x2521990 spark: 0x216 +11638246: cap 0: Start a parallel conjunction 0x25219f0, static_id: 2 +11638377: cap 0: Create spark for conjunction: 0x25219f0 spark: 0x217 +11638845: cap 0: Start a parallel conjunction 0x2521a50, static_id: 2 +11638971: cap 0: Create spark for conjunction: 0x2521a50 spark: 0x218 +11639173: cap 0: Start a parallel conjunction 0x2521ab0, static_id: 2 +11639304: cap 0: Create spark for conjunction: 0x2521ab0 spark: 0x219 +11639488: cap 0: Start a parallel conjunction 0x2521b10, static_id: 2 +11639614: cap 0: Create spark for conjunction: 0x2521b10 spark: 0x21a +11639799: cap 0: Start a parallel conjunction 0x2521b70, static_id: 2 +11639929: cap 0: Create spark for conjunction: 0x2521b70 spark: 0x21b +11640118: cap 0: Start a parallel conjunction 0x2521bd0, static_id: 2 +11640249: cap 0: Create spark for conjunction: 0x2521bd0 spark: 0x21c +11640438: cap 0: Start a parallel conjunction 0x2521c30, static_id: 2 +11640573: cap 0: Create spark for conjunction: 0x2521c30 spark: 0x21d +11640753: cap 0: Start a parallel conjunction 0x2521c90, static_id: 2 +11640874: cap 0: Create spark for conjunction: 0x2521c90 spark: 0x21e +11641063: cap 0: Start a parallel conjunction 0x2521cf0, static_id: 2 +11641194: cap 0: Create spark for conjunction: 0x2521cf0 spark: 0x21f +11641374: cap 0: Start a parallel conjunction 0x2521d50, static_id: 2 +11641495: cap 0: Create spark for conjunction: 0x2521d50 spark: 0x220 +11641675: cap 0: Start a parallel conjunction 0x2521db0, static_id: 2 +11641810: cap 0: Create spark for conjunction: 0x2521db0 spark: 0x221 +11641990: cap 0: Start a parallel conjunction 0x2521e10, static_id: 2 +11642121: cap 0: Create spark for conjunction: 0x2521e10 spark: 0x222 +11642305: cap 0: Start a parallel conjunction 0x2521e70, static_id: 2 +11642436: cap 0: Create spark for conjunction: 0x2521e70 spark: 0x223 +11642616: cap 0: Start a parallel conjunction 0x2521ed0, static_id: 2 +11642742: cap 0: Create spark for conjunction: 0x2521ed0 spark: 0x224 +11642926: cap 0: Start a parallel conjunction 0x2521f30, static_id: 2 +11643057: cap 0: Create spark for conjunction: 0x2521f30 spark: 0x225 +11643241: cap 0: Start a parallel conjunction 0x2521f90, static_id: 2 +11643367: cap 0: Create spark for conjunction: 0x2521f90 spark: 0x226 +11643691: cap 0: Start a parallel conjunction 0x2521ff0, static_id: 2 +11643826: cap 0: Create spark for conjunction: 0x2521ff0 spark: 0x227 +11644011: cap 0: Start a parallel conjunction 0x2522050, static_id: 2 +11644137: cap 0: Create spark for conjunction: 0x2522050 spark: 0x228 +11644335: cap 0: Start a parallel conjunction 0x25220b0, static_id: 2 +11644461: cap 0: Create spark for conjunction: 0x25220b0 spark: 0x229 +11644645: cap 0: Start a parallel conjunction 0x2522110, static_id: 2 +11644771: cap 0: Create spark for conjunction: 0x2522110 spark: 0x22a +11644960: cap 0: Start a parallel conjunction 0x2522170, static_id: 2 +11645100: cap 0: Create spark for conjunction: 0x2522170 spark: 0x22b +11645293: cap 0: Start a parallel conjunction 0x25221d0, static_id: 2 +11645419: cap 0: Create spark for conjunction: 0x25221d0 spark: 0x22c +11645599: cap 0: Start a parallel conjunction 0x2522230, static_id: 2 +11646090: cap 0: Create spark for conjunction: 0x2522230 spark: 0x22d +11646274: cap 0: Start a parallel conjunction 0x2522290, static_id: 2 +11646391: cap 0: Create spark for conjunction: 0x2522290 spark: 0x22e +11646841: cap 0: Start a parallel conjunction 0x25222f0, static_id: 2 +11646972: cap 0: Create spark for conjunction: 0x25222f0 spark: 0x22f +11647147: cap 0: Start a parallel conjunction 0x2522350, static_id: 2 +11647269: cap 0: Create spark for conjunction: 0x2522350 spark: 0x230 +11647453: cap 0: Start a parallel conjunction 0x25223b0, static_id: 2 +11647579: cap 0: Create spark for conjunction: 0x25223b0 spark: 0x231 +11647759: cap 0: Start a parallel conjunction 0x2522410, static_id: 2 +11647881: cap 0: Create spark for conjunction: 0x2522410 spark: 0x232 +11648070: cap 0: Start a parallel conjunction 0x2522470, static_id: 2 +11648196: cap 0: Create spark for conjunction: 0x2522470 spark: 0x233 +11648380: cap 0: Start a parallel conjunction 0x25224d0, static_id: 2 +11648506: cap 0: Create spark for conjunction: 0x25224d0 spark: 0x234 +11648691: cap 0: Start a parallel conjunction 0x2522530, static_id: 2 +11648826: cap 0: Create spark for conjunction: 0x2522530 spark: 0x235 +11649024: cap 0: Start a parallel conjunction 0x2522590, static_id: 2 +11649150: cap 0: Create spark for conjunction: 0x2522590 spark: 0x236 +11649339: cap 0: Start a parallel conjunction 0x25225f0, static_id: 2 +11649483: cap 0: Create spark for conjunction: 0x25225f0 spark: 0x237 +11649672: cap 0: Start a parallel conjunction 0x2522650, static_id: 2 +11649793: cap 0: Create spark for conjunction: 0x2522650 spark: 0x238 +11649991: cap 0: Start a parallel conjunction 0x25226b0, static_id: 2 +11650117: cap 0: Create spark for conjunction: 0x25226b0 spark: 0x239 +11650302: cap 0: Start a parallel conjunction 0x2522710, static_id: 2 +11650428: cap 0: Create spark for conjunction: 0x2522710 spark: 0x23a +11650612: cap 0: Start a parallel conjunction 0x2522770, static_id: 2 +11650738: cap 0: Create spark for conjunction: 0x2522770 spark: 0x23b +11650936: cap 0: Start a parallel conjunction 0x25227d0, static_id: 2 +11651058: cap 0: Create spark for conjunction: 0x25227d0 spark: 0x23c +11651247: cap 0: Start a parallel conjunction 0x2522830, static_id: 2 +11651386: cap 0: Create spark for conjunction: 0x2522830 spark: 0x23d +11651562: cap 0: Start a parallel conjunction 0x2522890, static_id: 2 +11651688: cap 0: Create spark for conjunction: 0x2522890 spark: 0x23e +11651877: cap 0: Start a parallel conjunction 0x25228f0, static_id: 2 +11652007: cap 0: Create spark for conjunction: 0x25228f0 spark: 0x23f +11652183: cap 0: Start a parallel conjunction 0x2522950, static_id: 2 +11652304: cap 0: Create spark for conjunction: 0x2522950 spark: 0x240 +11652660: cap 0: Start a parallel conjunction 0x25229b0, static_id: 2 +11652786: cap 0: Create spark for conjunction: 0x25229b0 spark: 0x241 +11652966: cap 0: Start a parallel conjunction 0x2522a10, static_id: 2 +11653087: cap 0: Create spark for conjunction: 0x2522a10 spark: 0x242 +11653276: cap 0: Start a parallel conjunction 0x2522a70, static_id: 2 +11653402: cap 0: Create spark for conjunction: 0x2522a70 spark: 0x243 +11653587: cap 0: Start a parallel conjunction 0x2522ad0, static_id: 2 +11653713: cap 0: Create spark for conjunction: 0x2522ad0 spark: 0x244 +11653897: cap 0: Start a parallel conjunction 0x2522b30, static_id: 2 +11654028: cap 0: Create spark for conjunction: 0x2522b30 spark: 0x245 +11654221: cap 0: Start a parallel conjunction 0x2522b90, static_id: 2 +11654347: cap 0: Create spark for conjunction: 0x2522b90 spark: 0x246 +11654532: cap 0: Start a parallel conjunction 0x2522bf0, static_id: 2 +11654676: cap 0: Create spark for conjunction: 0x2522bf0 spark: 0x247 +11654865: cap 0: Start a parallel conjunction 0x2522c50, static_id: 2 +11654986: cap 0: Create spark for conjunction: 0x2522c50 spark: 0x248 +11655189: cap 0: Start a parallel conjunction 0x2522cb0, static_id: 2 +11655328: cap 0: Create spark for conjunction: 0x2522cb0 spark: 0x249 +11655504: cap 0: Start a parallel conjunction 0x2522d10, static_id: 2 +11655630: cap 0: Create spark for conjunction: 0x2522d10 spark: 0x24a +11655828: cap 0: Start a parallel conjunction 0x2522d70, static_id: 2 +11655958: cap 0: Create spark for conjunction: 0x2522d70 spark: 0x24b +11656152: cap 0: Start a parallel conjunction 0x2522dd0, static_id: 2 +11656278: cap 0: Create spark for conjunction: 0x2522dd0 spark: 0x24c +11656462: cap 0: Start a parallel conjunction 0x2522e30, static_id: 2 +11656602: cap 0: Create spark for conjunction: 0x2522e30 spark: 0x24d +11656786: cap 0: Start a parallel conjunction 0x2522e90, static_id: 2 +11656908: cap 0: Create spark for conjunction: 0x2522e90 spark: 0x24e +11657097: cap 0: Start a parallel conjunction 0x2522ef0, static_id: 2 +11657227: cap 0: Create spark for conjunction: 0x2522ef0 spark: 0x24f +11657407: cap 0: Start a parallel conjunction 0x2522f50, static_id: 2 +11657524: cap 0: Create spark for conjunction: 0x2522f50 spark: 0x250 +11657857: cap 0: Start a parallel conjunction 0x2522fb0, static_id: 2 +11657983: cap 0: Create spark for conjunction: 0x2522fb0 spark: 0x251 +11658172: cap 0: Start a parallel conjunction 0x2523010, static_id: 2 +11658294: cap 0: Create spark for conjunction: 0x2523010 spark: 0x252 +11658487: cap 0: Start a parallel conjunction 0x2523070, static_id: 2 +11658618: cap 0: Create spark for conjunction: 0x2523070 spark: 0x253 +11658802: cap 0: Start a parallel conjunction 0x25230d0, static_id: 2 +11658933: cap 0: Create spark for conjunction: 0x25230d0 spark: 0x254 +11659126: cap 0: Start a parallel conjunction 0x2523130, static_id: 2 +11659252: cap 0: Create spark for conjunction: 0x2523130 spark: 0x255 +11659446: cap 0: Start a parallel conjunction 0x2523190, static_id: 2 +11659567: cap 0: Create spark for conjunction: 0x2523190 spark: 0x256 +11659752: cap 0: Start a parallel conjunction 0x25231f0, static_id: 2 +11659896: cap 0: Create spark for conjunction: 0x25231f0 spark: 0x257 +11660076: cap 0: Start a parallel conjunction 0x2523250, static_id: 2 +11660202: cap 0: Create spark for conjunction: 0x2523250 spark: 0x258 +11660395: cap 0: Start a parallel conjunction 0x25232b0, static_id: 2 +11660530: cap 0: Create spark for conjunction: 0x25232b0 spark: 0x259 +11660710: cap 0: Start a parallel conjunction 0x2523310, static_id: 2 +11660832: cap 0: Create spark for conjunction: 0x2523310 spark: 0x25a +11661183: cap 0: Start a parallel conjunction 0x2523370, static_id: 2 +11661313: cap 0: Create spark for conjunction: 0x2523370 spark: 0x25b +11661507: cap 0: Start a parallel conjunction 0x25233d0, static_id: 2 +11661633: cap 0: Create spark for conjunction: 0x25233d0 spark: 0x25c +11661813: cap 0: Start a parallel conjunction 0x2523430, static_id: 2 +11661952: cap 0: Create spark for conjunction: 0x2523430 spark: 0x25d +11662132: cap 0: Start a parallel conjunction 0x2523490, static_id: 2 +11662254: cap 0: Create spark for conjunction: 0x2523490 spark: 0x25e +11662447: cap 0: Start a parallel conjunction 0x25234f0, static_id: 2 +11662573: cap 0: Create spark for conjunction: 0x25234f0 spark: 0x25f +11662753: cap 0: Start a parallel conjunction 0x2523550, static_id: 2 +11662875: cap 0: Create spark for conjunction: 0x2523550 spark: 0x260 +11663059: cap 0: Start a parallel conjunction 0x25235b0, static_id: 2 +11663190: cap 0: Create spark for conjunction: 0x25235b0 spark: 0x261 +11663374: cap 0: Start a parallel conjunction 0x2523610, static_id: 2 +11663500: cap 0: Create spark for conjunction: 0x2523610 spark: 0x262 +11663689: cap 0: Start a parallel conjunction 0x2523670, static_id: 2 +11663824: cap 0: Create spark for conjunction: 0x2523670 spark: 0x263 +11664018: cap 0: Start a parallel conjunction 0x25236d0, static_id: 2 +11664157: cap 0: Create spark for conjunction: 0x25236d0 spark: 0x264 +11664346: cap 0: Start a parallel conjunction 0x2523730, static_id: 2 +11664481: cap 0: Create spark for conjunction: 0x2523730 spark: 0x265 +11664675: cap 0: Start a parallel conjunction 0x2523790, static_id: 2 +11664801: cap 0: Create spark for conjunction: 0x2523790 spark: 0x266 +11664985: cap 0: Start a parallel conjunction 0x25237f0, static_id: 2 +11665116: cap 0: Create spark for conjunction: 0x25237f0 spark: 0x267 +11665300: cap 0: Start a parallel conjunction 0x2523850, static_id: 2 +11665422: cap 0: Create spark for conjunction: 0x2523850 spark: 0x268 +11665611: cap 0: Start a parallel conjunction 0x25238b0, static_id: 2 +11665741: cap 0: Create spark for conjunction: 0x25238b0 spark: 0x269 +11665921: cap 0: Start a parallel conjunction 0x2523910, static_id: 2 +11666047: cap 0: Create spark for conjunction: 0x2523910 spark: 0x26a +11666232: cap 0: Start a parallel conjunction 0x2523970, static_id: 2 +11666367: cap 0: Create spark for conjunction: 0x2523970 spark: 0x26b +11666556: cap 0: Start a parallel conjunction 0x25239d0, static_id: 2 +11666677: cap 0: Create spark for conjunction: 0x25239d0 spark: 0x26c +11666862: cap 0: Start a parallel conjunction 0x2523a30, static_id: 2 +11666997: cap 0: Create spark for conjunction: 0x2523a30 spark: 0x26d +11667172: cap 0: Start a parallel conjunction 0x2523a90, static_id: 2 +11667294: cap 0: Create spark for conjunction: 0x2523a90 spark: 0x26e +11667483: cap 0: Start a parallel conjunction 0x2523af0, static_id: 2 +11667609: cap 0: Create spark for conjunction: 0x2523af0 spark: 0x26f +11667793: cap 0: Start a parallel conjunction 0x2523b50, static_id: 2 +11667915: cap 0: Create spark for conjunction: 0x2523b50 spark: 0x270 +11668099: cap 0: Start a parallel conjunction 0x2523bb0, static_id: 2 +11668252: cap 0: Create spark for conjunction: 0x2523bb0 spark: 0x271 +11668432: cap 0: Start a parallel conjunction 0x2523c10, static_id: 2 +11668554: cap 0: Create spark for conjunction: 0x2523c10 spark: 0x272 +11668747: cap 0: Start a parallel conjunction 0x2523c70, static_id: 2 +11668878: cap 0: Create spark for conjunction: 0x2523c70 spark: 0x273 +11669058: cap 0: Start a parallel conjunction 0x2523cd0, static_id: 2 +11669193: cap 0: Create spark for conjunction: 0x2523cd0 spark: 0x274 +11669391: cap 0: Start a parallel conjunction 0x2523d30, static_id: 2 +11669521: cap 0: Create spark for conjunction: 0x2523d30 spark: 0x275 +11669710: cap 0: Start a parallel conjunction 0x2523d90, static_id: 2 +11669836: cap 0: Create spark for conjunction: 0x2523d90 spark: 0x276 +11670021: cap 0: Start a parallel conjunction 0x2523df0, static_id: 2 +11670160: cap 0: Create spark for conjunction: 0x2523df0 spark: 0x277 +11670340: cap 0: Start a parallel conjunction 0x2523e50, static_id: 2 +11670466: cap 0: Create spark for conjunction: 0x2523e50 spark: 0x278 +11670660: cap 0: Start a parallel conjunction 0x2523eb0, static_id: 2 +11670790: cap 0: Create spark for conjunction: 0x2523eb0 spark: 0x279 +11670970: cap 0: Start a parallel conjunction 0x2523f10, static_id: 2 +11671096: cap 0: Create spark for conjunction: 0x2523f10 spark: 0x27a +11671281: cap 0: Start a parallel conjunction 0x2523f70, static_id: 2 +11671411: cap 0: Create spark for conjunction: 0x2523f70 spark: 0x27b +11671744: cap 0: Start a parallel conjunction 0x2523fd0, static_id: 2 +11671870: cap 0: Create spark for conjunction: 0x2523fd0 spark: 0x27c +11672298: cap 0: Start a parallel conjunction 0x2524030, static_id: 2 +11672446: cap 0: Create spark for conjunction: 0x2524030 spark: 0x27d +11672631: cap 0: Start a parallel conjunction 0x2524090, static_id: 2 +11672752: cap 0: Create spark for conjunction: 0x2524090 spark: 0x27e +11672941: cap 0: Start a parallel conjunction 0x25240f0, static_id: 2 +11673076: cap 0: Create spark for conjunction: 0x25240f0 spark: 0x27f +11673256: cap 0: Start a parallel conjunction 0x2524150, static_id: 2 +11673382: cap 0: Create spark for conjunction: 0x2524150 spark: 0x280 +11673567: cap 0: Start a parallel conjunction 0x25241b0, static_id: 2 +11673697: cap 0: Create spark for conjunction: 0x25241b0 spark: 0x281 +11673873: cap 0: Start a parallel conjunction 0x2524210, static_id: 2 +11673994: cap 0: Create spark for conjunction: 0x2524210 spark: 0x282 +11674183: cap 0: Start a parallel conjunction 0x2524270, static_id: 2 +11674318: cap 0: Create spark for conjunction: 0x2524270 spark: 0x283 +11674503: cap 0: Start a parallel conjunction 0x25242d0, static_id: 2 +11674674: cap 0: Create spark for conjunction: 0x25242d0 spark: 0x284 +11674867: cap 0: Start a parallel conjunction 0x2524330, static_id: 2 +11675002: cap 0: Create spark for conjunction: 0x2524330 spark: 0x285 +11675196: cap 0: Start a parallel conjunction 0x2524390, static_id: 2 +11675317: cap 0: Create spark for conjunction: 0x2524390 spark: 0x286 +11675493: cap 0: Start a parallel conjunction 0x25243f0, static_id: 2 +11675632: cap 0: Create spark for conjunction: 0x25243f0 spark: 0x287 +11675817: cap 0: Start a parallel conjunction 0x2524450, static_id: 2 +11675983: cap 0: Create spark for conjunction: 0x2524450 spark: 0x288 +11676190: cap 0: Start a parallel conjunction 0x25244b0, static_id: 2 +11676321: cap 0: Create spark for conjunction: 0x25244b0 spark: 0x289 +11676505: cap 0: Start a parallel conjunction 0x2524510, static_id: 2 +11676789: cap 0: Create spark for conjunction: 0x2524510 spark: 0x28a +11676969: cap 0: Start a parallel conjunction 0x2524570, static_id: 2 +11677131: cap 0: Create spark for conjunction: 0x2524570 spark: 0x28b +11677720: cap 0: Start a parallel conjunction 0x25245d0, static_id: 2 +11677842: cap 0: Create spark for conjunction: 0x25245d0 spark: 0x28c +11678026: cap 0: Start a parallel conjunction 0x2524630, static_id: 2 +11678166: cap 0: Create spark for conjunction: 0x2524630 spark: 0x28d +11678346: cap 0: Start a parallel conjunction 0x2524690, static_id: 2 +11678467: cap 0: Create spark for conjunction: 0x2524690 spark: 0x28e +11678652: cap 0: Start a parallel conjunction 0x25246f0, static_id: 2 +11678782: cap 0: Create spark for conjunction: 0x25246f0 spark: 0x28f +11678967: cap 0: Start a parallel conjunction 0x2524750, static_id: 2 +11679088: cap 0: Create spark for conjunction: 0x2524750 spark: 0x290 +11679268: cap 0: Start a parallel conjunction 0x25247b0, static_id: 2 +11679399: cap 0: Create spark for conjunction: 0x25247b0 spark: 0x291 +11679583: cap 0: Start a parallel conjunction 0x2524810, static_id: 2 +11679714: cap 0: Create spark for conjunction: 0x2524810 spark: 0x292 +11679912: cap 0: Start a parallel conjunction 0x2524870, static_id: 2 +11680042: cap 0: Create spark for conjunction: 0x2524870 spark: 0x293 +11680231: cap 0: Start a parallel conjunction 0x25248d0, static_id: 2 +11680366: cap 0: Create spark for conjunction: 0x25248d0 spark: 0x294 +11680564: cap 0: Start a parallel conjunction 0x2524930, static_id: 2 +11680695: cap 0: Create spark for conjunction: 0x2524930 spark: 0x295 +11680888: cap 0: Start a parallel conjunction 0x2524990, static_id: 2 +11681014: cap 0: Create spark for conjunction: 0x2524990 spark: 0x296 +11681199: cap 0: Start a parallel conjunction 0x25249f0, static_id: 2 +11681338: cap 0: Create spark for conjunction: 0x25249f0 spark: 0x297 +11681518: cap 0: Start a parallel conjunction 0x2524a50, static_id: 2 +11681644: cap 0: Create spark for conjunction: 0x2524a50 spark: 0x298 +11681833: cap 0: Start a parallel conjunction 0x2524ab0, static_id: 2 +11681959: cap 0: Create spark for conjunction: 0x2524ab0 spark: 0x299 +11682139: cap 0: Start a parallel conjunction 0x2524b10, static_id: 2 +11682261: cap 0: Create spark for conjunction: 0x2524b10 spark: 0x29a +11682445: cap 0: Start a parallel conjunction 0x2524b70, static_id: 2 +11682576: cap 0: Create spark for conjunction: 0x2524b70 spark: 0x29b +11682760: cap 0: Start a parallel conjunction 0x2524bd0, static_id: 2 +11682886: cap 0: Create spark for conjunction: 0x2524bd0 spark: 0x29c +11683062: cap 0: Start a parallel conjunction 0x2524c30, static_id: 2 +11683206: cap 0: Create spark for conjunction: 0x2524c30 spark: 0x29d +11683386: cap 0: Start a parallel conjunction 0x2524c90, static_id: 2 +11683512: cap 0: Create spark for conjunction: 0x2524c90 spark: 0x29e +11683705: cap 0: Start a parallel conjunction 0x2524cf0, static_id: 2 +11683836: cap 0: Create spark for conjunction: 0x2524cf0 spark: 0x29f +11684011: cap 0: Start a parallel conjunction 0x2524d50, static_id: 2 +11684133: cap 0: Create spark for conjunction: 0x2524d50 spark: 0x2a0 +11684317: cap 0: Start a parallel conjunction 0x2524db0, static_id: 2 +11684448: cap 0: Create spark for conjunction: 0x2524db0 spark: 0x2a1 +11684628: cap 0: Start a parallel conjunction 0x2524e10, static_id: 2 +11684749: cap 0: Create spark for conjunction: 0x2524e10 spark: 0x2a2 +11684938: cap 0: Start a parallel conjunction 0x2524e70, static_id: 2 +11685073: cap 0: Create spark for conjunction: 0x2524e70 spark: 0x2a3 +11685253: cap 0: Start a parallel conjunction 0x2524ed0, static_id: 2 +11685388: cap 0: Create spark for conjunction: 0x2524ed0 spark: 0x2a4 +11685577: cap 0: Start a parallel conjunction 0x2524f30, static_id: 2 +11685712: cap 0: Create spark for conjunction: 0x2524f30 spark: 0x2a5 +11685901: cap 0: Start a parallel conjunction 0x2524f90, static_id: 2 +11686027: cap 0: Create spark for conjunction: 0x2524f90 spark: 0x2a6 +11686554: cap 0: Start a parallel conjunction 0x2524ff0, static_id: 2 +11686693: cap 0: Create spark for conjunction: 0x2524ff0 spark: 0x2a7 +11686882: cap 0: Start a parallel conjunction 0x2525050, static_id: 2 +11687008: cap 0: Create spark for conjunction: 0x2525050 spark: 0x2a8 +11687202: cap 0: Start a parallel conjunction 0x25250b0, static_id: 2 +11687332: cap 0: Create spark for conjunction: 0x25250b0 spark: 0x2a9 +11687512: cap 0: Start a parallel conjunction 0x2525110, static_id: 2 +11687643: cap 0: Create spark for conjunction: 0x2525110 spark: 0x2aa +11687827: cap 0: Start a parallel conjunction 0x2525170, static_id: 2 +11687953: cap 0: Create spark for conjunction: 0x2525170 spark: 0x2ab +11688142: cap 0: Start a parallel conjunction 0x25251d0, static_id: 2 +11688264: cap 0: Create spark for conjunction: 0x25251d0 spark: 0x2ac +11688448: cap 0: Start a parallel conjunction 0x2525230, static_id: 2 +11688583: cap 0: Create spark for conjunction: 0x2525230 spark: 0x2ad +11688763: cap 0: Start a parallel conjunction 0x2525290, static_id: 2 +11688885: cap 0: Create spark for conjunction: 0x2525290 spark: 0x2ae +11689074: cap 0: Start a parallel conjunction 0x25252f0, static_id: 2 +11689209: cap 0: Create spark for conjunction: 0x25252f0 spark: 0x2af +11689389: cap 0: Start a parallel conjunction 0x2525350, static_id: 2 +11689510: cap 0: Create spark for conjunction: 0x2525350 spark: 0x2b0 +11689695: cap 0: Start a parallel conjunction 0x25253b0, static_id: 2 +11689825: cap 0: Create spark for conjunction: 0x25253b0 spark: 0x2b1 +11690005: cap 0: Start a parallel conjunction 0x2525410, static_id: 2 +11690131: cap 0: Create spark for conjunction: 0x2525410 spark: 0x2b2 +11690325: cap 0: Start a parallel conjunction 0x2525470, static_id: 2 +11690455: cap 0: Create spark for conjunction: 0x2525470 spark: 0x2b3 +11690631: cap 0: Start a parallel conjunction 0x25254d0, static_id: 2 +11690766: cap 0: Create spark for conjunction: 0x25254d0 spark: 0x2b4 +11690955: cap 0: Start a parallel conjunction 0x2525530, static_id: 2 +11691090: cap 0: Create spark for conjunction: 0x2525530 spark: 0x2b5 +11691279: cap 0: Start a parallel conjunction 0x2525590, static_id: 2 +11691405: cap 0: Create spark for conjunction: 0x2525590 spark: 0x2b6 +11691585: cap 0: Start a parallel conjunction 0x25255f0, static_id: 2 +11691724: cap 0: Create spark for conjunction: 0x25255f0 spark: 0x2b7 +11691904: cap 0: Start a parallel conjunction 0x2525650, static_id: 2 +11692026: cap 0: Create spark for conjunction: 0x2525650 spark: 0x2b8 +11692233: cap 0: Start a parallel conjunction 0x25256b0, static_id: 2 +11692363: cap 0: Create spark for conjunction: 0x25256b0 spark: 0x2b9 +11692539: cap 0: Start a parallel conjunction 0x2525710, static_id: 2 +11692665: cap 0: Create spark for conjunction: 0x2525710 spark: 0x2ba +11692849: cap 0: Start a parallel conjunction 0x2525770, static_id: 2 +11692975: cap 0: Create spark for conjunction: 0x2525770 spark: 0x2bb +11693164: cap 0: Start a parallel conjunction 0x25257d0, static_id: 2 +11693290: cap 0: Create spark for conjunction: 0x25257d0 spark: 0x2bc +11693475: cap 0: Start a parallel conjunction 0x2525830, static_id: 2 +11693610: cap 0: Create spark for conjunction: 0x2525830 spark: 0x2bd +11693794: cap 0: Start a parallel conjunction 0x2525890, static_id: 2 +11693916: cap 0: Create spark for conjunction: 0x2525890 spark: 0x2be +11694127: cap 0: Start a parallel conjunction 0x25258f0, static_id: 2 +11694258: cap 0: Create spark for conjunction: 0x25258f0 spark: 0x2bf +11694438: cap 0: Start a parallel conjunction 0x2525950, static_id: 2 +11694564: cap 0: Create spark for conjunction: 0x2525950 spark: 0x2c0 +11694753: cap 0: Start a parallel conjunction 0x25259b0, static_id: 2 +11694892: cap 0: Create spark for conjunction: 0x25259b0 spark: 0x2c1 +11695081: cap 0: Start a parallel conjunction 0x2525a10, static_id: 2 +11695203: cap 0: Create spark for conjunction: 0x2525a10 spark: 0x2c2 +11695401: cap 0: Start a parallel conjunction 0x2525a70, static_id: 2 +11695531: cap 0: Create spark for conjunction: 0x2525a70 spark: 0x2c3 +11695711: cap 0: Start a parallel conjunction 0x2525ad0, static_id: 2 +11695842: cap 0: Create spark for conjunction: 0x2525ad0 spark: 0x2c4 +11696031: cap 0: Start a parallel conjunction 0x2525b30, static_id: 2 +11696161: cap 0: Create spark for conjunction: 0x2525b30 spark: 0x2c5 +11696350: cap 0: Start a parallel conjunction 0x2525b90, static_id: 2 +11696476: cap 0: Create spark for conjunction: 0x2525b90 spark: 0x2c6 +11696656: cap 0: Start a parallel conjunction 0x2525bf0, static_id: 2 +11696791: cap 0: Create spark for conjunction: 0x2525bf0 spark: 0x2c7 +11696980: cap 0: Start a parallel conjunction 0x2525c50, static_id: 2 +11697106: cap 0: Create spark for conjunction: 0x2525c50 spark: 0x2c8 +11697300: cap 0: Start a parallel conjunction 0x2525cb0, static_id: 2 +11697435: cap 0: Create spark for conjunction: 0x2525cb0 spark: 0x2c9 +11697615: cap 0: Start a parallel conjunction 0x2525d10, static_id: 2 +11697741: cap 0: Create spark for conjunction: 0x2525d10 spark: 0x2ca +11697925: cap 0: Start a parallel conjunction 0x2525d70, static_id: 2 +11698060: cap 0: Create spark for conjunction: 0x2525d70 spark: 0x2cb +11698249: cap 0: Start a parallel conjunction 0x2525dd0, static_id: 2 +11698380: cap 0: Create spark for conjunction: 0x2525dd0 spark: 0x2cc +11698560: cap 0: Start a parallel conjunction 0x2525e30, static_id: 2 +11698699: cap 0: Create spark for conjunction: 0x2525e30 spark: 0x2cd +11698888: cap 0: Start a parallel conjunction 0x2525e90, static_id: 2 +11699014: cap 0: Create spark for conjunction: 0x2525e90 spark: 0x2ce +11699221: cap 0: Start a parallel conjunction 0x2525ef0, static_id: 2 +11699356: cap 0: Create spark for conjunction: 0x2525ef0 spark: 0x2cf +11699536: cap 0: Start a parallel conjunction 0x2525f50, static_id: 2 +11699662: cap 0: Create spark for conjunction: 0x2525f50 spark: 0x2d0 +11700009: cap 0: Start a parallel conjunction 0x2525fb0, static_id: 2 +11700139: cap 0: Create spark for conjunction: 0x2525fb0 spark: 0x2d1 +11700432: cap 0: Start a parallel conjunction 0x2526010, static_id: 2 +11700558: cap 0: Create spark for conjunction: 0x2526010 spark: 0x2d2 +11700751: cap 0: Start a parallel conjunction 0x2526070, static_id: 2 +11700882: cap 0: Create spark for conjunction: 0x2526070 spark: 0x2d3 +11701057: cap 0: Start a parallel conjunction 0x25260d0, static_id: 2 +11701183: cap 0: Create spark for conjunction: 0x25260d0 spark: 0x2d4 +11701372: cap 0: Start a parallel conjunction 0x2526130, static_id: 2 +11701503: cap 0: Create spark for conjunction: 0x2526130 spark: 0x2d5 +11701692: cap 0: Start a parallel conjunction 0x2526190, static_id: 2 +11701818: cap 0: Create spark for conjunction: 0x2526190 spark: 0x2d6 +11702133: cap 0: Start a parallel conjunction 0x25261f0, static_id: 2 +11702272: cap 0: Create spark for conjunction: 0x25261f0 spark: 0x2d7 +11702457: cap 0: Start a parallel conjunction 0x2526250, static_id: 2 +11702578: cap 0: Create spark for conjunction: 0x2526250 spark: 0x2d8 +11702763: cap 0: Start a parallel conjunction 0x25262b0, static_id: 2 +11702893: cap 0: Create spark for conjunction: 0x25262b0 spark: 0x2d9 +11703073: cap 0: Start a parallel conjunction 0x2526310, static_id: 2 +11703199: cap 0: Create spark for conjunction: 0x2526310 spark: 0x2da +11703384: cap 0: Start a parallel conjunction 0x2526370, static_id: 2 +11703510: cap 0: Create spark for conjunction: 0x2526370 spark: 0x2db +11703825: cap 0: Start a parallel conjunction 0x25263d0, static_id: 2 +11703946: cap 0: Create spark for conjunction: 0x25263d0 spark: 0x2dc +11704140: cap 0: Start a parallel conjunction 0x2526430, static_id: 2 +11704275: cap 0: Create spark for conjunction: 0x2526430 spark: 0x2dd +11704455: cap 0: Start a parallel conjunction 0x2526490, static_id: 2 +11704576: cap 0: Create spark for conjunction: 0x2526490 spark: 0x2de +11704761: cap 0: Start a parallel conjunction 0x25264f0, static_id: 2 +11704891: cap 0: Create spark for conjunction: 0x25264f0 spark: 0x2df +11705067: cap 0: Start a parallel conjunction 0x2526550, static_id: 2 +11705188: cap 0: Create spark for conjunction: 0x2526550 spark: 0x2e0 +11705373: cap 0: Start a parallel conjunction 0x25265b0, static_id: 2 +11705499: cap 0: Create spark for conjunction: 0x25265b0 spark: 0x2e1 +11705683: cap 0: Start a parallel conjunction 0x2526610, static_id: 2 +11705814: cap 0: Create spark for conjunction: 0x2526610 spark: 0x2e2 +11706003: cap 0: Start a parallel conjunction 0x2526670, static_id: 2 +11706133: cap 0: Create spark for conjunction: 0x2526670 spark: 0x2e3 +11706318: cap 0: Start a parallel conjunction 0x25266d0, static_id: 2 +11706448: cap 0: Create spark for conjunction: 0x25266d0 spark: 0x2e4 +11706642: cap 0: Start a parallel conjunction 0x2526730, static_id: 2 +11706777: cap 0: Create spark for conjunction: 0x2526730 spark: 0x2e5 +11706966: cap 0: Start a parallel conjunction 0x2526790, static_id: 2 +11707092: cap 0: Create spark for conjunction: 0x2526790 spark: 0x2e6 +11707272: cap 0: Start a parallel conjunction 0x25267f0, static_id: 2 +11707551: cap 0: Create spark for conjunction: 0x25267f0 spark: 0x2e7 +11707744: cap 0: Start a parallel conjunction 0x2526850, static_id: 2 +11707866: cap 0: Create spark for conjunction: 0x2526850 spark: 0x2e8 +11708185: cap 0: Start a parallel conjunction 0x25268b0, static_id: 2 +11708316: cap 0: Create spark for conjunction: 0x25268b0 spark: 0x2e9 +11708505: cap 0: Start a parallel conjunction 0x2526910, static_id: 2 +11708626: cap 0: Create spark for conjunction: 0x2526910 spark: 0x2ea +11708811: cap 0: Start a parallel conjunction 0x2526970, static_id: 2 +11708937: cap 0: Create spark for conjunction: 0x2526970 spark: 0x2eb +11709126: cap 0: Start a parallel conjunction 0x25269d0, static_id: 2 +11709247: cap 0: Create spark for conjunction: 0x25269d0 spark: 0x2ec +11709427: cap 0: Start a parallel conjunction 0x2526a30, static_id: 2 +11709562: cap 0: Create spark for conjunction: 0x2526a30 spark: 0x2ed +11709742: cap 0: Start a parallel conjunction 0x2526a90, static_id: 2 +11709864: cap 0: Create spark for conjunction: 0x2526a90 spark: 0x2ee +11710062: cap 0: Start a parallel conjunction 0x2526af0, static_id: 2 +11710197: cap 0: Create spark for conjunction: 0x2526af0 spark: 0x2ef +11710372: cap 0: Start a parallel conjunction 0x2526b50, static_id: 2 +11710503: cap 0: Create spark for conjunction: 0x2526b50 spark: 0x2f0 +11710696: cap 0: Start a parallel conjunction 0x2526bb0, static_id: 2 +11710827: cap 0: Create spark for conjunction: 0x2526bb0 spark: 0x2f1 +11711011: cap 0: Start a parallel conjunction 0x2526c10, static_id: 2 +11711128: cap 0: Create spark for conjunction: 0x2526c10 spark: 0x2f2 +11711322: cap 0: Start a parallel conjunction 0x2526c70, static_id: 2 +11711457: cap 0: Create spark for conjunction: 0x2526c70 spark: 0x2f3 +11711637: cap 0: Start a parallel conjunction 0x2526cd0, static_id: 2 +11711763: cap 0: Create spark for conjunction: 0x2526cd0 spark: 0x2f4 +11711952: cap 0: Start a parallel conjunction 0x2526d30, static_id: 2 +11712082: cap 0: Create spark for conjunction: 0x2526d30 spark: 0x2f5 +11712271: cap 0: Start a parallel conjunction 0x2526d90, static_id: 2 +11712397: cap 0: Create spark for conjunction: 0x2526d90 spark: 0x2f6 +11712577: cap 0: Start a parallel conjunction 0x2526df0, static_id: 2 +11712712: cap 0: Create spark for conjunction: 0x2526df0 spark: 0x2f7 +11712888: cap 0: Start a parallel conjunction 0x2526e50, static_id: 2 +11713009: cap 0: Create spark for conjunction: 0x2526e50 spark: 0x2f8 +11713198: cap 0: Start a parallel conjunction 0x2526eb0, static_id: 2 +11713329: cap 0: Create spark for conjunction: 0x2526eb0 spark: 0x2f9 +11713504: cap 0: Start a parallel conjunction 0x2526f10, static_id: 2 +11713626: cap 0: Create spark for conjunction: 0x2526f10 spark: 0x2fa +11713810: cap 0: Start a parallel conjunction 0x2526f70, static_id: 2 +11713936: cap 0: Create spark for conjunction: 0x2526f70 spark: 0x2fb +11714130: cap 0: Start a parallel conjunction 0x2526fd0, static_id: 2 +11714256: cap 0: Create spark for conjunction: 0x2526fd0 spark: 0x2fc +11714463: cap 0: Start a parallel conjunction 0x2527030, static_id: 2 +11714598: cap 0: Create spark for conjunction: 0x2527030 spark: 0x2fd +11714787: cap 0: Start a parallel conjunction 0x2527090, static_id: 2 +11714908: cap 0: Create spark for conjunction: 0x2527090 spark: 0x2fe +11715097: cap 0: Start a parallel conjunction 0x25270f0, static_id: 2 +11715223: cap 0: Create spark for conjunction: 0x25270f0 spark: 0x2ff +11715403: cap 0: Start a parallel conjunction 0x2527150, static_id: 2 +11715525: cap 0: Create spark for conjunction: 0x2527150 spark: 0x300 +11715705: cap 0: Start a parallel conjunction 0x25271b0, static_id: 2 +11715835: cap 0: Create spark for conjunction: 0x25271b0 spark: 0x301 +11716015: cap 0: Start a parallel conjunction 0x2527210, static_id: 2 +11716137: cap 0: Create spark for conjunction: 0x2527210 spark: 0x302 +11716321: cap 0: Start a parallel conjunction 0x2527270, static_id: 2 +11716452: cap 0: Create spark for conjunction: 0x2527270 spark: 0x303 +11716632: cap 0: Start a parallel conjunction 0x25272d0, static_id: 2 +11716803: cap 0: Create spark for conjunction: 0x25272d0 spark: 0x304 +11716987: cap 0: Start a parallel conjunction 0x2527330, static_id: 2 +11717113: cap 0: Create spark for conjunction: 0x2527330 spark: 0x305 +11717302: cap 0: Start a parallel conjunction 0x2527390, static_id: 2 +11717424: cap 0: Create spark for conjunction: 0x2527390 spark: 0x306 +11717604: cap 0: Start a parallel conjunction 0x25273f0, static_id: 2 +11717743: cap 0: Create spark for conjunction: 0x25273f0 spark: 0x307 +11717919: cap 0: Start a parallel conjunction 0x2527450, static_id: 2 +11718085: cap 0: Create spark for conjunction: 0x2527450 spark: 0x308 +11718288: cap 0: Start a parallel conjunction 0x25274b0, static_id: 2 +11718418: cap 0: Create spark for conjunction: 0x25274b0 spark: 0x309 +11718594: cap 0: Start a parallel conjunction 0x2527510, static_id: 2 +11718720: cap 0: Create spark for conjunction: 0x2527510 spark: 0x30a +11718904: cap 0: Start a parallel conjunction 0x2527570, static_id: 2 +11719035: cap 0: Create spark for conjunction: 0x2527570 spark: 0x30b +11719219: cap 0: Start a parallel conjunction 0x25275d0, static_id: 2 +11719341: cap 0: Create spark for conjunction: 0x25275d0 spark: 0x30c +11719525: cap 0: Start a parallel conjunction 0x2527630, static_id: 2 +11719669: cap 0: Create spark for conjunction: 0x2527630 spark: 0x30d +11719849: cap 0: Start a parallel conjunction 0x2527690, static_id: 2 +11719971: cap 0: Create spark for conjunction: 0x2527690 spark: 0x30e +11720155: cap 0: Start a parallel conjunction 0x25276f0, static_id: 2 +11720290: cap 0: Create spark for conjunction: 0x25276f0 spark: 0x30f +11720475: cap 0: Start a parallel conjunction 0x2527750, static_id: 2 +11720601: cap 0: Create spark for conjunction: 0x2527750 spark: 0x310 +11720776: cap 0: Start a parallel conjunction 0x25277b0, static_id: 2 +11720907: cap 0: Create spark for conjunction: 0x25277b0 spark: 0x311 +11721087: cap 0: Start a parallel conjunction 0x2527810, static_id: 2 +11721204: cap 0: Create spark for conjunction: 0x2527810 spark: 0x312 +11721393: cap 0: Start a parallel conjunction 0x2527870, static_id: 2 +11721528: cap 0: Create spark for conjunction: 0x2527870 spark: 0x313 +11721708: cap 0: Start a parallel conjunction 0x25278d0, static_id: 2 +11721834: cap 0: Create spark for conjunction: 0x25278d0 spark: 0x314 +11722149: cap 0: Start a parallel conjunction 0x2527930, static_id: 2 +11722275: cap 0: Create spark for conjunction: 0x2527930 spark: 0x315 +11722464: cap 0: Start a parallel conjunction 0x2527990, static_id: 2 +11722590: cap 0: Create spark for conjunction: 0x2527990 spark: 0x316 +11722770: cap 0: Start a parallel conjunction 0x25279f0, static_id: 2 +11722905: cap 0: Create spark for conjunction: 0x25279f0 spark: 0x317 +11723089: cap 0: Start a parallel conjunction 0x2527a50, static_id: 2 +11723215: cap 0: Create spark for conjunction: 0x2527a50 spark: 0x318 +11723400: cap 0: Start a parallel conjunction 0x2527ab0, static_id: 2 +11723535: cap 0: Create spark for conjunction: 0x2527ab0 spark: 0x319 +11723715: cap 0: Start a parallel conjunction 0x2527b10, static_id: 2 +11723836: cap 0: Create spark for conjunction: 0x2527b10 spark: 0x31a +11724021: cap 0: Start a parallel conjunction 0x2527b70, static_id: 2 +11724151: cap 0: Create spark for conjunction: 0x2527b70 spark: 0x31b +11724340: cap 0: Start a parallel conjunction 0x2527bd0, static_id: 2 +11724462: cap 0: Create spark for conjunction: 0x2527bd0 spark: 0x31c +11724642: cap 0: Start a parallel conjunction 0x2527c30, static_id: 2 +11724781: cap 0: Create spark for conjunction: 0x2527c30 spark: 0x31d +11724961: cap 0: Start a parallel conjunction 0x2527c90, static_id: 2 +11725092: cap 0: Create spark for conjunction: 0x2527c90 spark: 0x31e +11725285: cap 0: Start a parallel conjunction 0x2527cf0, static_id: 2 +11725425: cap 0: Create spark for conjunction: 0x2527cf0 spark: 0x31f +11728597: cap 0: End par conjunct: 0x2527cf0 +11730312: cap 0: running a local spark +12148717: cap 3: creating spark thread 3 +12149284: cap 3: running thread 3 +12335386: cap 2: creating spark thread 2 +12336304: cap 2: running thread 2 +12609625: cap 1: creating spark thread 4 +12610075: cap 1: running thread 4 +12877888: cap 3: End par conjunct: 0x25151b0 +12878455: cap 3: Trying to steal a spark +12879013: cap 3: stealing a spark from cap 0 +13341195: cap 2: End par conjunct: 0x2515150 +13342090: cap 2: Trying to steal a spark +13343094: cap 2: stealing a spark from cap 0 +13501534: cap 3: End par conjunct: 0x2515270 +13501827: cap 3: Trying to steal a spark +13502322: cap 3: stealing a spark from cap 0 +13596930: cap 1: End par conjunct: 0x2515210 +13597681: cap 1: Trying to steal a spark +13598401: cap 1: stealing a spark from cap 0 +14083335: cap 1: stopping thread 4 (heap overflow) +14083542: cap 1: starting GC +14136727: cap 0: stopping thread 1 (thread yielding) +14140219: cap 3: stopping thread 3 (thread yielding) +14149165: cap 2: stopping thread 2 (thread yielding) +23736676: cap 0: running thread 1 +23740087: cap 3: running thread 3 +23748079: cap 2: running thread 2 +23783076: cap 1: finished GC +23783292: cap 1: running thread 4 +24076197: cap 2: End par conjunct: 0x25152d0 +24078132: cap 2: Trying to steal a spark +24079986: cap 2: stealing a spark from cap 0 +24232905: cap 3: End par conjunct: 0x2515330 +24233566: cap 3: Trying to steal a spark +24234601: cap 3: stealing a spark from cap 0 +24254811: cap 1: End par conjunct: 0x2515390 +24255621: cap 1: Trying to steal a spark +24256161: cap 1: stealing a spark from cap 0 +24726721: cap 2: End par conjunct: 0x25153f0 +24726996: cap 2: Trying to steal a spark +24727351: cap 2: stealing a spark from cap 0 +24884374: cap 1: End par conjunct: 0x25154b0 +24884775: cap 1: Trying to steal a spark +24884995: cap 1: stealing a spark from cap 0 +25181676: cap 3: End par conjunct: 0x2515450 +25182256: cap 3: Trying to steal a spark +25182837: cap 3: stealing a spark from cap 0 +25332556: cap 2: End par conjunct: 0x2515510 +25332939: cap 2: Trying to steal a spark +25333330: cap 2: stealing a spark from cap 0 +25496014: cap 1: End par conjunct: 0x2515570 +25496253: cap 1: Trying to steal a spark +25496473: cap 1: stealing a spark from cap 0 +25927915: cap 2: End par conjunct: 0x2515630 +25928122: cap 2: Trying to steal a spark +25928334: cap 2: stealing a spark from cap 0 +26084745: cap 3: End par conjunct: 0x25155d0 +26085249: cap 3: Trying to steal a spark +26085843: cap 3: stealing a spark from cap 0 +26090298: cap 1: End par conjunct: 0x2515690 +26090689: cap 1: Trying to steal a spark +26091085: cap 1: stealing a spark from cap 0 +26536383: cap 2: End par conjunct: 0x25156f0 +26536603: cap 2: Trying to steal a spark +26536914: cap 2: stealing a spark from cap 0 +26692762: cap 1: End par conjunct: 0x25157b0 +26692992: cap 1: Trying to steal a spark +26693203: cap 1: stealing a spark from cap 0 +26979043: cap 3: End par conjunct: 0x2515750 +26979642: cap 3: Trying to steal a spark +26980258: cap 3: stealing a spark from cap 0 +27137002: cap 2: End par conjunct: 0x2515810 +27137416: cap 2: Trying to steal a spark +27137952: cap 2: stealing a spark from cap 0 +27307827: cap 1: End par conjunct: 0x2515870 +27308056: cap 1: Trying to steal a spark +27308272: cap 1: stealing a spark from cap 0 +27746244: cap 2: End par conjunct: 0x2515930 +27746469: cap 2: Trying to steal a spark +27746680: cap 2: stealing a spark from cap 0 +27876528: cap 3: End par conjunct: 0x25158d0 +27877045: cap 3: Trying to steal a spark +27877761: cap 3: stealing a spark from cap 0 +27921861: cap 1: End par conjunct: 0x2515990 +27922432: cap 1: Trying to steal a spark +27922869: cap 1: stealing a spark from cap 0 +28351957: cap 2: End par conjunct: 0x25159f0 +28352187: cap 2: Trying to steal a spark +28352407: cap 2: stealing a spark from cap 0 +28533199: cap 1: End par conjunct: 0x2515ab0 +28533424: cap 1: Trying to steal a spark +28533631: cap 1: stealing a spark from cap 0 +28780488: cap 3: End par conjunct: 0x2515a50 +28780996: cap 3: Trying to steal a spark +28781604: cap 3: stealing a spark from cap 0 +28984594: cap 2: End par conjunct: 0x2515b10 +28985049: cap 2: Trying to steal a spark +28985485: cap 2: stealing a spark from cap 0 +29173518: cap 1: End par conjunct: 0x2515b70 +29173806: cap 1: Trying to steal a spark +29174062: cap 1: stealing a spark from cap 0 +29588274: cap 2: End par conjunct: 0x2515c30 +29588494: cap 2: Trying to steal a spark +29588706: cap 2: stealing a spark from cap 0 +29705886: cap 3: End par conjunct: 0x2515bd0 +29706475: cap 3: Trying to steal a spark +29707047: cap 3: stealing a spark from cap 0 +29788911: cap 1: End par conjunct: 0x2515c90 +29789302: cap 1: Trying to steal a spark +29789694: cap 1: stealing a spark from cap 0 +30185464: cap 2: End par conjunct: 0x2515cf0 +30185671: cap 2: Trying to steal a spark +30185982: cap 2: stealing a spark from cap 0 +30392149: cap 1: End par conjunct: 0x2515db0 +30392374: cap 1: Trying to steal a spark +30392590: cap 1: stealing a spark from cap 0 +30611209: cap 3: End par conjunct: 0x2515d50 +30611916: cap 3: Trying to steal a spark +30612640: cap 3: stealing a spark from cap 0 +30809916: cap 2: End par conjunct: 0x2515e10 +30810312: cap 2: Trying to steal a spark +30810712: cap 2: stealing a spark from cap 0 +31008384: cap 1: End par conjunct: 0x2515e70 +31008600: cap 1: Trying to steal a spark +31008901: cap 1: stealing a spark from cap 0 +31420368: cap 2: End par conjunct: 0x2515f30 +31420593: cap 2: Trying to steal a spark +31420809: cap 2: stealing a spark from cap 0 +31533394: cap 3: End par conjunct: 0x2515ed0 +31533984: cap 3: Trying to steal a spark +31534591: cap 3: stealing a spark from cap 0 +31615168: cap 1: End par conjunct: 0x2515f90 +31615596: cap 1: Trying to steal a spark +31615992: cap 1: stealing a spark from cap 0 +32033641: cap 2: End par conjunct: 0x2515ff0 +32033866: cap 2: Trying to steal a spark +32034177: cap 2: stealing a spark from cap 0 +32268591: cap 1: End par conjunct: 0x25160b0 +32268874: cap 1: Trying to steal a spark +32269131: cap 1: stealing a spark from cap 0 +32468868: cap 3: End par conjunct: 0x2516050 +32469426: cap 3: Trying to steal a spark +32470078: cap 3: stealing a spark from cap 0 +32677348: cap 2: End par conjunct: 0x2516110 +32677776: cap 2: Trying to steal a spark +32678208: cap 2: stealing a spark from cap 0 +32876379: cap 1: End par conjunct: 0x2516170 +32876590: cap 1: Trying to steal a spark +32876811: cap 1: stealing a spark from cap 0 +33304153: cap 2: End par conjunct: 0x2516230 +33304374: cap 2: Trying to steal a spark +33304684: cap 2: stealing a spark from cap 0 +33398968: cap 3: End par conjunct: 0x25161d0 +33399441: cap 3: Trying to steal a spark +33399936: cap 3: stealing a spark from cap 0 +33498414: cap 1: End par conjunct: 0x2516290 +33498900: cap 1: Trying to steal a spark +33499372: cap 1: stealing a spark from cap 0 +33926773: cap 2: End par conjunct: 0x25162f0 +33927003: cap 2: Trying to steal a spark +33927219: cap 2: stealing a spark from cap 0 +34125759: cap 1: End par conjunct: 0x25163b0 +34125984: cap 1: Trying to steal a spark +34126200: cap 1: stealing a spark from cap 0 +34343518: cap 3: End par conjunct: 0x2516350 +34344018: cap 3: Trying to steal a spark +34344841: cap 3: stealing a spark from cap 0 +34555158: cap 2: End par conjunct: 0x2516410 +34555585: cap 2: Trying to steal a spark +34555999: cap 2: stealing a spark from cap 0 +34755426: cap 1: End par conjunct: 0x2516470 +34755651: cap 1: Trying to steal a spark +34755885: cap 1: stealing a spark from cap 0 +35181679: cap 2: End par conjunct: 0x2516530 +35181904: cap 2: Trying to steal a spark +35182219: cap 2: stealing a spark from cap 0 +35299462: cap 3: End par conjunct: 0x25164d0 +35300011: cap 3: Trying to steal a spark +35300614: cap 3: stealing a spark from cap 0 +35403894: cap 1: End par conjunct: 0x2516590 +35404425: cap 1: Trying to steal a spark +35404992: cap 1: stealing a spark from cap 0 +35817421: cap 2: End par conjunct: 0x25165f0 +35817651: cap 2: Trying to steal a spark +35817867: cap 2: stealing a spark from cap 0 +36025614: cap 1: End par conjunct: 0x25166b0 +36025843: cap 1: Trying to steal a spark +36026055: cap 1: stealing a spark from cap 0 +36222511: cap 3: End par conjunct: 0x2516650 +36223024: cap 3: Trying to steal a spark +36223618: cap 3: stealing a spark from cap 0 +36455044: cap 2: End par conjunct: 0x2516710 +36455602: cap 2: Trying to steal a spark +36456102: cap 2: stealing a spark from cap 0 +36668988: cap 1: End par conjunct: 0x2516770 +36669204: cap 1: Trying to steal a spark +36669415: cap 1: stealing a spark from cap 0 +37113880: cap 2: End par conjunct: 0x2516830 +37114330: cap 2: Trying to steal a spark +37114650: cap 2: stealing a spark from cap 0 +37175854: cap 3: End par conjunct: 0x25167d0 +37176363: cap 3: Trying to steal a spark +37176957: cap 3: stealing a spark from cap 0 +37328764: cap 1: End par conjunct: 0x2516890 +37329291: cap 1: Trying to steal a spark +37329781: cap 1: stealing a spark from cap 0 +37769184: cap 2: End par conjunct: 0x25168f0 +37769454: cap 2: Trying to steal a spark +37769818: cap 2: stealing a spark from cap 0 +37969281: cap 1: End par conjunct: 0x25169b0 +37969506: cap 1: Trying to steal a spark +37969722: cap 1: stealing a spark from cap 0 +38118726: cap 3: End par conjunct: 0x2516950 +38119275: cap 3: Trying to steal a spark +38119873: cap 3: stealing a spark from cap 0 +38409223: cap 2: End par conjunct: 0x2516a10 +38409628: cap 2: Trying to steal a spark +38410029: cap 2: stealing a spark from cap 0 +38624274: cap 1: End par conjunct: 0x2516a70 +38624539: cap 1: Trying to steal a spark +38624760: cap 1: stealing a spark from cap 0 +39093678: cap 2: End par conjunct: 0x2516b30 +39093957: cap 2: Trying to steal a spark +39094204: cap 2: stealing a spark from cap 0 +39133138: cap 3: End par conjunct: 0x2516ad0 +39133723: cap 3: Trying to steal a spark +39134574: cap 3: stealing a spark from cap 0 +39276504: cap 1: End par conjunct: 0x2516b90 +39276913: cap 1: Trying to steal a spark +39277332: cap 1: stealing a spark from cap 0 +39746497: cap 2: End par conjunct: 0x2516bf0 +39746718: cap 2: Trying to steal a spark +39746938: cap 2: stealing a spark from cap 0 +39951765: cap 1: End par conjunct: 0x2516cb0 +39952062: cap 1: Trying to steal a spark +39952341: cap 1: stealing a spark from cap 0 +40113454: cap 3: End par conjunct: 0x2516c50 +40113999: cap 3: Trying to steal a spark +40114507: cap 3: stealing a spark from cap 0 +40408366: cap 2: End par conjunct: 0x2516d10 +40408816: cap 2: Trying to steal a spark +40409239: cap 2: stealing a spark from cap 0 +40619043: cap 1: End par conjunct: 0x2516d70 +40619268: cap 1: Trying to steal a spark +40619488: cap 1: stealing a spark from cap 0 +41067765: cap 2: End par conjunct: 0x2516e30 +41068017: cap 2: Trying to steal a spark +41068260: cap 2: stealing a spark from cap 0 +41114754: cap 3: End par conjunct: 0x2516dd0 +41115456: cap 3: Trying to steal a spark +41116095: cap 3: stealing a spark from cap 0 +41283873: cap 1: End par conjunct: 0x2516e90 +41284156: cap 1: Trying to steal a spark +41284548: cap 1: stealing a spark from cap 0 +41730048: cap 2: End par conjunct: 0x2516ef0 +41730273: cap 2: Trying to steal a spark +41730583: cap 2: stealing a spark from cap 0 +41952546: cap 1: End par conjunct: 0x2516fb0 +41952771: cap 1: Trying to steal a spark +41952982: cap 1: stealing a spark from cap 0 +42100420: cap 3: End par conjunct: 0x2516f50 +42100924: cap 3: Trying to steal a spark +42101577: cap 3: stealing a spark from cap 0 +42400962: cap 2: End par conjunct: 0x2517010 +42401286: cap 2: Trying to steal a spark +42401709: cap 2: stealing a spark from cap 0 +42633526: cap 1: End par conjunct: 0x2517070 +42633801: cap 1: Trying to steal a spark +42634035: cap 1: stealing a spark from cap 0 +43071579: cap 2: End par conjunct: 0x2517130 +43071804: cap 2: Trying to steal a spark +43072141: cap 2: stealing a spark from cap 0 +43098408: cap 3: End par conjunct: 0x25170d0 +43099047: cap 3: Trying to steal a spark +43099650: cap 3: stealing a spark from cap 0 +43299085: cap 1: End par conjunct: 0x2517190 +43299540: cap 1: Trying to steal a spark +43299994: cap 1: stealing a spark from cap 0 +43749342: cap 2: End par conjunct: 0x25171f0 +43749675: cap 2: Trying to steal a spark +43749981: cap 2: stealing a spark from cap 0 +43987482: cap 1: End par conjunct: 0x25172b0 +43987711: cap 1: Trying to steal a spark +43987927: cap 1: stealing a spark from cap 0 +44106511: cap 3: End par conjunct: 0x2517250 +44107020: cap 3: Trying to steal a spark +44107524: cap 3: stealing a spark from cap 0 +44435862: cap 2: End par conjunct: 0x2517310 +44436258: cap 2: Trying to steal a spark +44436654: cap 2: stealing a spark from cap 0 +44685877: cap 1: End par conjunct: 0x2517370 +44686093: cap 1: Trying to steal a spark +44686305: cap 1: stealing a spark from cap 0 +45133911: cap 2: End par conjunct: 0x2517430 +45134136: cap 2: Trying to steal a spark +45134446: cap 2: stealing a spark from cap 0 +45154615: cap 3: End par conjunct: 0x25173d0 +45155164: cap 3: Trying to steal a spark +45155763: cap 3: stealing a spark from cap 0 +45397935: cap 1: End par conjunct: 0x2517490 +45398326: cap 1: Trying to steal a spark +45398718: cap 1: stealing a spark from cap 0 +45836001: cap 2: End par conjunct: 0x25174f0 +45836226: cap 2: Trying to steal a spark +45836541: cap 2: stealing a spark from cap 0 +46110154: cap 1: End par conjunct: 0x25175b0 +46110379: cap 1: Trying to steal a spark +46110595: cap 1: stealing a spark from cap 0 +46221808: cap 3: End par conjunct: 0x2517550 +46222308: cap 3: Trying to steal a spark +46222902: cap 3: stealing a spark from cap 0 +46588792: cap 2: End par conjunct: 0x2517610 +46589211: cap 2: Trying to steal a spark +46589625: cap 2: stealing a spark from cap 0 +46844860: cap 1: End par conjunct: 0x2517670 +46845072: cap 1: Trying to steal a spark +46845288: cap 1: stealing a spark from cap 0 +47312941: cap 2: End par conjunct: 0x2517730 +47313166: cap 2: Trying to steal a spark +47313477: cap 2: stealing a spark from cap 0 +47330820: cap 3: End par conjunct: 0x25176d0 +47331400: cap 3: Trying to steal a spark +47332035: cap 3: stealing a spark from cap 0 +47604280: cap 1: End par conjunct: 0x2517790 +47604735: cap 1: Trying to steal a spark +47605203: cap 1: stealing a spark from cap 0 +48060094: cap 2: End par conjunct: 0x25177f0 +48060297: cap 2: Trying to steal a spark +48060603: cap 2: stealing a spark from cap 0 +48358003: cap 1: End par conjunct: 0x25178b0 +48358228: cap 1: Trying to steal a spark +48358458: cap 1: stealing a spark from cap 0 +48437491: cap 3: End par conjunct: 0x2517850 +48437964: cap 3: Trying to steal a spark +48438558: cap 3: stealing a spark from cap 0 +48805825: cap 2: End par conjunct: 0x2517910 +48806239: cap 2: Trying to steal a spark +48806824: cap 2: stealing a spark from cap 0 +49100440: cap 1: End par conjunct: 0x2517970 +49100665: cap 1: Trying to steal a spark +49100886: cap 1: stealing a spark from cap 0 +49579861: cap 3: End par conjunct: 0x25179d0 +49580419: cap 3: Trying to steal a spark +49581022: cap 3: stealing a spark from cap 0 +49636854: cap 2: End par conjunct: 0x2517a30 +49637754: cap 2: Trying to steal a spark +49638730: cap 2: stealing a spark from cap 0 +49870381: cap 1: End par conjunct: 0x2517a90 +49870705: cap 1: Trying to steal a spark +49870917: cap 1: stealing a spark from cap 0 +50426550: cap 2: End par conjunct: 0x2517b50 +50426932: cap 2: Trying to steal a spark +50427261: cap 2: stealing a spark from cap 0 +50665230: cap 1: End par conjunct: 0x2517bb0 +50665441: cap 1: Trying to steal a spark +50665653: cap 1: stealing a spark from cap 0 +50830560: cap 3: End par conjunct: 0x2517af0 +50831068: cap 3: Trying to steal a spark +50831662: cap 3: stealing a spark from cap 0 +51224148: cap 2: End par conjunct: 0x2517c10 +51224454: cap 2: Trying to steal a spark +51225012: cap 2: stealing a spark from cap 0 +51483465: cap 1: End par conjunct: 0x2517c70 +51483685: cap 1: Trying to steal a spark +51483906: cap 1: stealing a spark from cap 0 +52064626: cap 3: End par conjunct: 0x2517cd0 +52065135: cap 3: Trying to steal a spark +52065729: cap 3: stealing a spark from cap 0 +52247997: cap 2: End par conjunct: 0x2517d30 +52248433: cap 2: Trying to steal a spark +52248924: cap 2: stealing a spark from cap 0 +52314489: cap 1: End par conjunct: 0x2517d90 +52314921: cap 1: Trying to steal a spark +52315168: cap 1: stealing a spark from cap 0 +53089573: cap 2: End par conjunct: 0x2517e50 +53089983: cap 2: Trying to steal a spark +53090334: cap 2: stealing a spark from cap 0 +53148744: cap 1: End par conjunct: 0x2517eb0 +53148991: cap 1: Trying to steal a spark +53149203: cap 1: stealing a spark from cap 0 +53306419: cap 3: End par conjunct: 0x2517df0 +53306928: cap 3: Trying to steal a spark +53307544: cap 3: stealing a spark from cap 0 +53907304: cap 2: End par conjunct: 0x2517f10 +53907579: cap 2: Trying to steal a spark +53907961: cap 2: stealing a spark from cap 0 +54013536: cap 1: End par conjunct: 0x2517f70 +54013806: cap 1: Trying to steal a spark +54014022: cap 1: stealing a spark from cap 0 +54337927: cap 3: End par conjunct: 0x2517fd0 +54338431: cap 3: Trying to steal a spark +54338931: cap 3: stealing a spark from cap 0 +54762241: cap 2: End par conjunct: 0x2518030 +54762664: cap 2: Trying to steal a spark +54763177: cap 2: stealing a spark from cap 0 +54909072: cap 1: End par conjunct: 0x2518090 +54909450: cap 1: Trying to steal a spark +54909684: cap 1: stealing a spark from cap 0 +55878903: cap 2: End par conjunct: 0x2518150 +55879249: cap 2: Trying to steal a spark +55879465: cap 2: stealing a spark from cap 0 +55923277: cap 3: End par conjunct: 0x25180f0 +55923610: cap 3: Trying to steal a spark +55924101: cap 3: stealing a spark from cap 0 +56954371: cap 1: End par conjunct: 0x25181b0 +56954632: cap 1: Trying to steal a spark +56955096: cap 1: stealing a spark from cap 0 +58131936: cap 2: End par conjunct: 0x2518210 +58132260: cap 2: Trying to steal a spark +58132476: cap 2: stealing a spark from cap 0 +58232556: cap 3: End par conjunct: 0x2518270 +58232889: cap 3: Trying to steal a spark +58233262: cap 3: stealing a spark from cap 0 +59230395: cap 1: End par conjunct: 0x25182d0 +59231034: cap 1: Trying to steal a spark +59231439: cap 1: stealing a spark from cap 0 +59402803: cap 3: End par conjunct: 0x2518390 +59403244: cap 3: Trying to steal a spark +59403739: cap 3: stealing a spark from cap 0 +59775511: cap 2: End par conjunct: 0x2518330 +59775781: cap 2: Trying to steal a spark +59776168: cap 2: stealing a spark from cap 0 +60382269: cap 3: End par conjunct: 0x2518450 +60382647: cap 3: Trying to steal a spark +60383133: cap 3: stealing a spark from cap 0 +60445363: cap 1: End par conjunct: 0x25183f0 +60445737: cap 1: Trying to steal a spark +60446155: cap 1: stealing a spark from cap 0 +61507039: cap 2: End par conjunct: 0x25184b0 +61507665: cap 2: Trying to steal a spark +61508101: cap 2: stealing a spark from cap 0 +62346784: cap 1: End par conjunct: 0x2518570 +62347000: cap 1: Trying to steal a spark +62347216: cap 1: stealing a spark from cap 0 +62512888: cap 3: End par conjunct: 0x2518510 +62513284: cap 3: Trying to steal a spark +62513658: cap 3: stealing a spark from cap 0 +63392238: cap 2: End par conjunct: 0x25185d0 +63392625: cap 2: Trying to steal a spark +63393111: cap 2: stealing a spark from cap 0 +63590472: cap 3: End par conjunct: 0x2518690 +63590904: cap 3: Trying to steal a spark +63591385: cap 3: stealing a spark from cap 0 +64123029: cap 1: End par conjunct: 0x2518630 +64123375: cap 1: Trying to steal a spark +64123893: cap 1: stealing a spark from cap 0 +64477633: cap 2: End par conjunct: 0x25186f0 +64477975: cap 2: Trying to steal a spark +64478223: cap 2: stealing a spark from cap 0 +64722933: cap 3: End par conjunct: 0x2518750 +64723369: cap 3: Trying to steal a spark +64723851: cap 3: stealing a spark from cap 0 +65542941: cap 1: End par conjunct: 0x25187b0 +65543301: cap 1: Trying to steal a spark +65543782: cap 1: stealing a spark from cap 0 +65650234: cap 2: End par conjunct: 0x2518810 +65650576: cap 2: Trying to steal a spark +65650788: cap 2: stealing a spark from cap 0 +66578935: cap 3: End par conjunct: 0x2518870 +66579484: cap 3: Trying to steal a spark +66580056: cap 3: stealing a spark from cap 0 +66854529: cap 2: End par conjunct: 0x2518930 +66854853: cap 2: Trying to steal a spark +66855343: cap 2: stealing a spark from cap 0 +66946320: cap 1: End par conjunct: 0x25188d0 +66946707: cap 1: Trying to steal a spark +66946963: cap 1: stealing a spark from cap 0 +67733041: cap 3: End par conjunct: 0x2518990 +67733455: cap 3: Trying to steal a spark +67733950: cap 3: stealing a spark from cap 0 +68058499: cap 2: End par conjunct: 0x25189f0 +68058882: cap 2: Trying to steal a spark +68059377: cap 2: stealing a spark from cap 0 +68678649: cap 1: End par conjunct: 0x2518a50 +68678982: cap 1: Trying to steal a spark +68679229: cap 1: stealing a spark from cap 0 +69240861: cap 3: End par conjunct: 0x2518ab0 +69241176: cap 3: Trying to steal a spark +69241567: cap 3: stealing a spark from cap 0 +69304954: cap 2: End par conjunct: 0x2518b10 +69305319: cap 2: Trying to steal a spark +69305692: cap 2: stealing a spark from cap 0 +70140240: cap 1: End par conjunct: 0x2518b70 +70140469: cap 1: Trying to steal a spark +70140685: cap 1: stealing a spark from cap 0 +70773511: cap 3: End par conjunct: 0x2518bd0 +70773885: cap 3: Trying to steal a spark +70774366: cap 3: stealing a spark from cap 0 +70808850: cap 2: End par conjunct: 0x2518c30 +70809367: cap 2: Trying to steal a spark +70809768: cap 2: stealing a spark from cap 0 +71873527: cap 1: End par conjunct: 0x2518c90 +71873860: cap 1: Trying to steal a spark +71874072: cap 1: stealing a spark from cap 0 +72283689: cap 2: End par conjunct: 0x2518d50 +72284017: cap 2: Trying to steal a spark +72284233: cap 2: stealing a spark from cap 0 +73054251: cap 3: End par conjunct: 0x2518cf0 +73054732: cap 3: Trying to steal a spark +73055466: cap 3: stealing a spark from cap 0 +73159285: cap 1: End par conjunct: 0x2518db0 +73159722: cap 1: Trying to steal a spark +73160388: cap 1: stealing a spark from cap 0 +74440966: cap 3: End par conjunct: 0x2518e70 +74441227: cap 3: Trying to steal a spark +74441610: cap 3: stealing a spark from cap 0 +74785315: cap 2: End par conjunct: 0x2518e10 +74786017: cap 2: Trying to steal a spark +74787043: cap 2: stealing a spark from cap 0 +75288483: cap 1: End par conjunct: 0x2518ed0 +75288820: cap 1: Trying to steal a spark +75289032: cap 1: stealing a spark from cap 0 +77436747: cap 3: End par conjunct: 0x2518f30 +77437134: cap 3: Trying to steal a spark +77437759: cap 3: stealing a spark from cap 0 +78004147: cap 2: End par conjunct: 0x2518f90 +78004602: cap 2: Trying to steal a spark +78005169: cap 2: stealing a spark from cap 0 +78438784: cap 1: End par conjunct: 0x2518ff0 +78439081: cap 1: Trying to steal a spark +78439360: cap 1: stealing a spark from cap 0 +80926996: cap 3: End par conjunct: 0x2519050 +80927392: cap 3: Trying to steal a spark +80927775: cap 3: stealing a spark from cap 0 +82047559: cap 2: End par conjunct: 0x25190b0 +82047987: cap 2: Trying to steal a spark +82048459: cap 2: stealing a spark from cap 0 +83968875: cap 1: End par conjunct: 0x2519110 +83969217: cap 1: Trying to steal a spark +83969428: cap 1: stealing a spark from cap 0 +86729665: cap 3: End par conjunct: 0x2519170 +86730021: cap 3: Trying to steal a spark +86730417: cap 3: stealing a spark from cap 0 +88351767: cap 2: End par conjunct: 0x25191d0 +88352401: cap 2: Trying to steal a spark +88353040: cap 2: stealing a spark from cap 0 +91559997: cap 1: End par conjunct: 0x2519230 +91560532: cap 1: Trying to steal a spark +91560888: cap 1: stealing a spark from cap 0 +94191606: cap 3: End par conjunct: 0x2519290 +94192038: cap 3: Trying to steal a spark +94192447: cap 3: stealing a spark from cap 0 +96909921: cap 2: End par conjunct: 0x25192f0 +96910249: cap 2: Trying to steal a spark +96910677: cap 2: stealing a spark from cap 0 101435247: cap 1: End par conjunct: 0x2519350 101435656: cap 1: Trying to steal a spark 101435913: cap 1: stealing a spark from cap 0 @@ -5594,4 +5594,3 @@ Events: 19242932310: cap 0: shutting down 19243048770: deleted capset 0 - diff --git a/test/parallelTest.eventlog.reference b/test/parallelTest.eventlog.reference index 8c469ce..2afedef 100644 --- a/test/parallelTest.eventlog.reference +++ b/test/parallelTest.eventlog.reference @@ -1,71 +1,71 @@ Event Types: - 0: Create thread (size 4) - 1: Run thread (size 4) - 2: Stop thread (size 10) - 3: Thread runnable (size 4) - 4: Migrate thread (size 6) - 8: Wakeup thread (size 6) - 9: Starting GC (size 0) - 10: Finished GC (size 0) - 11: Request sequential GC (size 0) - 12: Request parallel GC (size 0) - 15: Create spark thread (size 4) - 16: Log message (size variable) - 17: Create capabilities (size 2) - 18: Block marker (size 14) - 19: User message (size variable) - 20: GC idle (size 0) - 21: GC working (size 0) - 22: GC done (size 0) - 23: Version (size variable) - 24: Program invocation (size variable) - 25: Create capability set (size 6) - 26: Delete capability set (size 4) - 27: Add capability to capability set (size 6) - 28: Remove capability from capability set (size 6) - 29: RTS name and version (size variable) - 30: Program arguments (size variable) - 31: Program environment variables (size variable) - 32: Process ID (size 8) - 33: Parent process ID (size 8) - 34: Spark counters (size 56) - 35: Spark create (size 0) - 36: Spark dud (size 0) - 37: Spark overflow (size 0) - 38: Spark run (size 0) - 39: Spark steal (size 2) - 40: Spark fizzle (size 0) - 41: Spark GC (size 0) - 43: Wall clock time (size 16) - 44: Thread label (size variable) - 45: Create capability (size 2) - 46: Delete capability (size 2) - 47: Disable capability (size 2) - 48: Enable capability (size 2) - 49: Total heap mem ever allocated (size 12) - 50: Current heap size (size 12) - 51: Current heap live data (size 12) - 52: Heap static parameters (size 38) - 53: GC statistics (size 50) - 54: Synchronise stop-the-world GC (size 0) - 55: Task create (size 18) - 56: Task migrate (size 12) - 57: Task delete (size 8) - 58: User marker (size variable) - 59: Empty event for bug #9003 (size 0) - 60: Starting message receival (size 0) - 61: Finished message receival (size 0) - 62: Creating Process (size 4) - 63: Killing Process (size 4) - 64: Assigning thread to process (size 8) - 65: Creating machine (size 10) - 66: Killing machine (size 2) - 67: Sending message (size 19) - 68: Receiving message (size 23) - 69: Sending/Receiving local message (size 17) +0: Create thread (size 4) +1: Run thread (size 4) +2: Stop thread (size 10) +3: Thread runnable (size 4) +4: Migrate thread (size 6) +8: Wakeup thread (size 6) +9: Starting GC (size 0) +10: Finished GC (size 0) +11: Request sequential GC (size 0) +12: Request parallel GC (size 0) +15: Create spark thread (size 4) +16: Log message (size variable) +17: Create capabilities (size 2) +18: Block marker (size 14) +19: User message (size variable) +20: GC idle (size 0) +21: GC working (size 0) +22: GC done (size 0) +23: Version (size variable) +24: Program invocation (size variable) +25: Create capability set (size 6) +26: Delete capability set (size 4) +27: Add capability to capability set (size 6) +28: Remove capability from capability set (size 6) +29: RTS name and version (size variable) +30: Program arguments (size variable) +31: Program environment variables (size variable) +32: Process ID (size 8) +33: Parent process ID (size 8) +34: Spark counters (size 56) +35: Spark create (size 0) +36: Spark dud (size 0) +37: Spark overflow (size 0) +38: Spark run (size 0) +39: Spark steal (size 2) +40: Spark fizzle (size 0) +41: Spark GC (size 0) +43: Wall clock time (size 16) +44: Thread label (size variable) +45: Create capability (size 2) +46: Delete capability (size 2) +47: Disable capability (size 2) +48: Enable capability (size 2) +49: Total heap mem ever allocated (size 12) +50: Current heap size (size 12) +51: Current heap live data (size 12) +52: Heap static parameters (size 38) +53: GC statistics (size 50) +54: Synchronise stop-the-world GC (size 0) +55: Task create (size 18) +56: Task migrate (size 12) +57: Task delete (size 8) +58: User marker (size variable) +59: Empty event for bug #9003 (size 0) +60: Starting message receival (size 0) +61: Finished message receival (size 0) +62: Creating Process (size 4) +63: Killing Process (size 4) +64: Assigning thread to process (size 8) +65: Creating machine (size 10) +66: Killing machine (size 2) +67: Sending message (size 19) +68: Receiving message (size 23) +69: Sending/Receiving local message (size 17) Events: - 965: creating machine 2 at 143714457434916300 +965: creating machine 2 at 143714457434916300 1016690453: startup: 1 capabilities 1016695409: compiler version is 7.10.20150612 1016698802: program invocation: /opt/Eden/test/./jost=ChainDep 2 3 +RTS -l -RTS @@ -484,4 +484,3 @@ Events: 1036709334: deleted capset 1 1036715687: killing machine 2 - diff --git a/test/pre77stop.eventlog.reference b/test/pre77stop.eventlog.reference index 5f96278..1c0b2cf 100644 --- a/test/pre77stop.eventlog.reference +++ b/test/pre77stop.eventlog.reference @@ -1,94 +1,94 @@ Event Types: - 0: Create thread (size 4) - 1: Run thread (size 4) - 2: Stop thread (size 10) - 3: Thread runnable (size 4) - 4: Migrate thread (size 6) - 8: Wakeup thread (size 6) - 9: Starting GC (size 0) - 10: Finished GC (size 0) - 11: Request sequential GC (size 0) - 12: Request parallel GC (size 0) - 15: Create spark thread (size 4) - 16: Log message (size variable) - 17: Create capabilities (size 2) - 18: Block marker (size 14) - 19: User message (size variable) - 20: GC idle (size 0) - 21: GC working (size 0) - 22: GC done (size 0) - 23: Version (size variable) - 24: Program invocation (size variable) - 25: Create capability set (size 6) - 26: Delete capability set (size 4) - 27: Add capability to capability set (size 6) - 28: Remove capability from capability set (size 6) - 29: RTS name and version (size variable) - 30: Program arguments (size variable) - 31: Program environment variables (size variable) - 32: Process ID (size 8) - 33: Parent process ID (size 8) - 34: Spark counters (size 56) - 35: Spark create (size 0) - 36: Spark dud (size 0) - 37: Spark overflow (size 0) - 38: Spark run (size 0) - 39: Spark steal (size 2) - 40: Spark fizzle (size 0) - 41: Spark GC (size 0) - 43: Wall clock time (size 16) - 44: Thread label (size variable) - 45: Create capability (size 2) - 46: Delete capability (size 2) - 47: Disable capability (size 2) - 48: Enable capability (size 2) - 49: Total heap mem ever allocated (size 12) - 50: Current heap size (size 12) - 51: Current heap live data (size 12) - 52: Heap static parameters (size 38) - 53: GC statistics (size 50) - 54: Synchronise stop-the-world GC (size 0) - 60: Starting message receival (size 0) - 61: Finished message receival (size 0) - 62: Creating Process (size 4) - 63: Killing Process (size 4) - 64: Assigning thread to process (size 8) - 65: Creating machine (size 10) - 66: Killing machine (size 2) - 67: Sending message (size 19) - 68: Receiving message (size 23) - 69: Sending/Receiving local message (size 17) +0: Create thread (size 4) +1: Run thread (size 4) +2: Stop thread (size 10) +3: Thread runnable (size 4) +4: Migrate thread (size 6) +8: Wakeup thread (size 6) +9: Starting GC (size 0) +10: Finished GC (size 0) +11: Request sequential GC (size 0) +12: Request parallel GC (size 0) +15: Create spark thread (size 4) +16: Log message (size variable) +17: Create capabilities (size 2) +18: Block marker (size 14) +19: User message (size variable) +20: GC idle (size 0) +21: GC working (size 0) +22: GC done (size 0) +23: Version (size variable) +24: Program invocation (size variable) +25: Create capability set (size 6) +26: Delete capability set (size 4) +27: Add capability to capability set (size 6) +28: Remove capability from capability set (size 6) +29: RTS name and version (size variable) +30: Program arguments (size variable) +31: Program environment variables (size variable) +32: Process ID (size 8) +33: Parent process ID (size 8) +34: Spark counters (size 56) +35: Spark create (size 0) +36: Spark dud (size 0) +37: Spark overflow (size 0) +38: Spark run (size 0) +39: Spark steal (size 2) +40: Spark fizzle (size 0) +41: Spark GC (size 0) +43: Wall clock time (size 16) +44: Thread label (size variable) +45: Create capability (size 2) +46: Delete capability (size 2) +47: Disable capability (size 2) +48: Enable capability (size 2) +49: Total heap mem ever allocated (size 12) +50: Current heap size (size 12) +51: Current heap live data (size 12) +52: Heap static parameters (size 38) +53: GC statistics (size 50) +54: Synchronise stop-the-world GC (size 0) +60: Starting message receival (size 0) +61: Finished message receival (size 0) +62: Creating Process (size 4) +63: Killing Process (size 4) +64: Assigning thread to process (size 8) +65: Creating machine (size 10) +66: Killing machine (size 2) +67: Sending message (size 19) +68: Receiving message (size 23) +69: Sending/Receiving local message (size 17) Events: - 289733: startup: 1 capabilities - 296334: created capset 0 of type CapsetOsProcess - 296685: created capset 1 of type CapsetClockDomain - 298459: created cap 0 - 298614: assigned cap 0 to capset 0 - 298750: assigned cap 0 to capset 1 - 305355: capset 1: wall clock time 1405192564s 324769000ns (unix epoch) - 305796: capset 0: pid 19928 - 308186: capset 0: parent pid 18797 - 315568: capset 0: RTS version "GHC-7.6.3 rts_l" - 323642: capset 0: args: ["./wrongeventlog2","+RTS","-lsu-g-p","-K80m","-k10m","-H200m","-C1s"] - 331921: capset 0: env: ["SSH_AGENT_PID=1817","PVM_RSH=/usr/bin/ssh","GPG_AGENT_INFO=/tmp/keyring-yTUMmt/gpg:0:1","TERM=xterm","SHELL=/bin/bash","XDG_SESSION_COOKIE=acf1c79e0e2de67643be755c00000003-1405160974.283591-1531347675","WINDOWID=58743399","OLDPWD=/opt/Eden/edentv/fixFor783/BLD-ghc-events-parallel","GNOME_KEYRING_CONTROL=/tmp/keyring-yTUMmt","USER=jost","LS_COLORS=rs=0:di=01;34:ln=01;36:mh=00:pi=40;33:so=01;35:do=01;35:bd=40;33;01:cd=40;33;01:or=40;31;01:su=37;41:sg=30;43:ca=30;41:tw=30;42:ow=34;42:st=37;44:ex=01;32:*.tar=01;31:*.tgz=01;31:*.arj=01;31:*.taz=01;31:*.lzh=01;31:*.lzma=01;31:*.tlz=01;31:*.txz=01;31:*.zip=01;31:*.z=01;31:*.Z=01;31:*.dz=01;31:*.gz=01;31:*.lz=01;31:*.xz=01;31:*.bz2=01;31:*.bz=01;31:*.tbz=01;31:*.tbz2=01;31:*.tz=01;31:*.deb=01;31:*.rpm=01;31:*.jar=01;31:*.war=01;31:*.ear=01;31:*.sar=01;31:*.rar=01;31:*.ace=01;31:*.zoo=01;31:*.cpio=01;31:*.7z=01;31:*.rz=01;31:*.jpg=01;35:*.jpeg=01;35:*.gif=01;35:*.bmp=01;35:*.pbm=01;35:*.pgm=01;35:*.ppm=01;35:*.tga=01;35:*.xbm=01;35:*.xpm=01;35:*.tif=01;35:*.tiff=01;35:*.png=01;35:*.svg=01;35:*.svgz=01;35:*.mng=01;35:*.pcx=01;35:*.mov=01;35:*.mpg=01;35:*.mpeg=01;35:*.m2v=01;35:*.mkv=01;35:*.webm=01;35:*.ogm=01;35:*.mp4=01;35:*.m4v=01;35:*.mp4v=01;35:*.vob=01;35:*.qt=01;35:*.nuv=01;35:*.wmv=01;35:*.asf=01;35:*.rm=01;35:*.rmvb=01;35:*.flc=01;35:*.avi=01;35:*.fli=01;35:*.flv=01;35:*.gl=01;35:*.dl=01;35:*.xcf=01;35:*.xwd=01;35:*.yuv=01;35:*.cgm=01;35:*.emf=01;35:*.axv=01;35:*.anx=01;35:*.ogv=01;35:*.ogx=01;35:*.aac=00;36:*.au=00;36:*.flac=00;36:*.mid=00;36:*.midi=00;36:*.mka=00;36:*.mp3=00;36:*.mpc=00;36:*.ogg=00;36:*.ra=00;36:*.wav=00;36:*.axa=00;36:*.oga=00;36:*.spx=00;36:*.xspf=00;36:","XDG_SESSION_PATH=/org/freedesktop/DisplayManager/Session0","XDG_SEAT_PATH=/org/freedesktop/DisplayManager/Seat0","PVM_ROOT=/usr/lib/pvm3","SSH_AUTH_SOCK=/tmp/keyring-yTUMmt/ssh","SESSION_MANAGER=local/onAir:@/tmp/.ICE-unix/1781,unix/onAir:/tmp/.ICE-unix/1781","DEFAULTS_PATH=/usr/share/gconf/gnome-fallback.default.path","PVM_ARCH=LINUX64","XDG_CONFIG_DIRS=/etc/xdg/xdg-gnome-fallback:/etc/xdg","PATH=/home/jost/bin:/home/jost/bin:/usr/lib/lightdm/lightdm:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/home/jost/.cabal/bin","DESKTOP_SESSION=gnome-fallback","PWD=/opt/Eden/edentv/fixFor783","GNOME_KEYRING_PID=1770","LANG=en_US.UTF-8","MANDATORY_PATH=/usr/share/gconf/gnome-fallback.mandatory.path","UBUNTU_MENUPROXY=libappmenu.so","GDMSESSION=gnome-fallback","SHLVL=1","HOME=/home/jost","LANGUAGE=en_US:en","GNOME_DESKTOP_SESSION_ID=this-is-deprecated","LOGNAME=jost","PVM_EXPORT=DISPLAY","XDG_DATA_DIRS=/usr/share/gnome-fallback:/usr/share/gnome:/usr/local/share/:/usr/share/","DBUS_SESSION_BUS_ADDRESS=unix:abstract=/tmp/dbus-Mviy2n6D5M,guid=3677210ad991dc7e0dc3a1ae00000012","LESSOPEN=| /usr/bin/lesspipe %s","DISPLAY=:0.0","XDG_CURRENT_DESKTOP=GNOME","LESSCLOSE=/usr/bin/lesspipe %s %s","COLORTERM=gnome-terminal","XAUTHORITY=/home/jost/.Xauthority","_=./wrongeventlog2"] - 716554: cap 0: creating thread 1 - 724337: cap 0: running thread 1 - 777249: cap 0: stopping thread 1 (heap overflow) - 4206233: cap 0: running thread 1 - 4371098: cap 0: stopping thread 1 (making a foreign call) - 4373253: cap 0: running thread 1 - 4468468: cap 0: forking child thread - 4628142: cap 0: creating thread 2 - 4629931: cap 0: stopping thread 1 (thread yielding) - 4631259: cap 0: running thread 2 - 4635338: cap 0: stopping thread 2 (heap overflow) - 5624512: cap 0: running thread 2 - 5633862: cap 0: child - 10558539: cap 0: stopping thread 2 (thread yielding) - 10560195: cap 0: running thread 1 - 10571646: cap 0: stopping thread 1 (blocked on black hole owned by thread 2) - 10571821: cap 0: running thread 2 +289733: startup: 1 capabilities +296334: created capset 0 of type CapsetOsProcess +296685: created capset 1 of type CapsetClockDomain +298459: created cap 0 +298614: assigned cap 0 to capset 0 +298750: assigned cap 0 to capset 1 +305355: capset 1: wall clock time 1405192564s 324769000ns (unix epoch) +305796: capset 0: pid 19928 +308186: capset 0: parent pid 18797 +315568: capset 0: RTS version "GHC-7.6.3 rts_l" +323642: capset 0: args: ["./wrongeventlog2","+RTS","-lsu-g-p","-K80m","-k10m","-H200m","-C1s"] +331921: capset 0: env: ["SSH_AGENT_PID=1817","PVM_RSH=/usr/bin/ssh","GPG_AGENT_INFO=/tmp/keyring-yTUMmt/gpg:0:1","TERM=xterm","SHELL=/bin/bash","XDG_SESSION_COOKIE=acf1c79e0e2de67643be755c00000003-1405160974.283591-1531347675","WINDOWID=58743399","OLDPWD=/opt/Eden/edentv/fixFor783/BLD-ghc-events-parallel","GNOME_KEYRING_CONTROL=/tmp/keyring-yTUMmt","USER=jost","LS_COLORS=rs=0:di=01;34:ln=01;36:mh=00:pi=40;33:so=01;35:do=01;35:bd=40;33;01:cd=40;33;01:or=40;31;01:su=37;41:sg=30;43:ca=30;41:tw=30;42:ow=34;42:st=37;44:ex=01;32:*.tar=01;31:*.tgz=01;31:*.arj=01;31:*.taz=01;31:*.lzh=01;31:*.lzma=01;31:*.tlz=01;31:*.txz=01;31:*.zip=01;31:*.z=01;31:*.Z=01;31:*.dz=01;31:*.gz=01;31:*.lz=01;31:*.xz=01;31:*.bz2=01;31:*.bz=01;31:*.tbz=01;31:*.tbz2=01;31:*.tz=01;31:*.deb=01;31:*.rpm=01;31:*.jar=01;31:*.war=01;31:*.ear=01;31:*.sar=01;31:*.rar=01;31:*.ace=01;31:*.zoo=01;31:*.cpio=01;31:*.7z=01;31:*.rz=01;31:*.jpg=01;35:*.jpeg=01;35:*.gif=01;35:*.bmp=01;35:*.pbm=01;35:*.pgm=01;35:*.ppm=01;35:*.tga=01;35:*.xbm=01;35:*.xpm=01;35:*.tif=01;35:*.tiff=01;35:*.png=01;35:*.svg=01;35:*.svgz=01;35:*.mng=01;35:*.pcx=01;35:*.mov=01;35:*.mpg=01;35:*.mpeg=01;35:*.m2v=01;35:*.mkv=01;35:*.webm=01;35:*.ogm=01;35:*.mp4=01;35:*.m4v=01;35:*.mp4v=01;35:*.vob=01;35:*.qt=01;35:*.nuv=01;35:*.wmv=01;35:*.asf=01;35:*.rm=01;35:*.rmvb=01;35:*.flc=01;35:*.avi=01;35:*.fli=01;35:*.flv=01;35:*.gl=01;35:*.dl=01;35:*.xcf=01;35:*.xwd=01;35:*.yuv=01;35:*.cgm=01;35:*.emf=01;35:*.axv=01;35:*.anx=01;35:*.ogv=01;35:*.ogx=01;35:*.aac=00;36:*.au=00;36:*.flac=00;36:*.mid=00;36:*.midi=00;36:*.mka=00;36:*.mp3=00;36:*.mpc=00;36:*.ogg=00;36:*.ra=00;36:*.wav=00;36:*.axa=00;36:*.oga=00;36:*.spx=00;36:*.xspf=00;36:","XDG_SESSION_PATH=/org/freedesktop/DisplayManager/Session0","XDG_SEAT_PATH=/org/freedesktop/DisplayManager/Seat0","PVM_ROOT=/usr/lib/pvm3","SSH_AUTH_SOCK=/tmp/keyring-yTUMmt/ssh","SESSION_MANAGER=local/onAir:@/tmp/.ICE-unix/1781,unix/onAir:/tmp/.ICE-unix/1781","DEFAULTS_PATH=/usr/share/gconf/gnome-fallback.default.path","PVM_ARCH=LINUX64","XDG_CONFIG_DIRS=/etc/xdg/xdg-gnome-fallback:/etc/xdg","PATH=/home/jost/bin:/home/jost/bin:/usr/lib/lightdm/lightdm:/usr/local/sbin:/usr/local/bin:/usr/sbin:/usr/bin:/sbin:/bin:/usr/games:/home/jost/.cabal/bin","DESKTOP_SESSION=gnome-fallback","PWD=/opt/Eden/edentv/fixFor783","GNOME_KEYRING_PID=1770","LANG=en_US.UTF-8","MANDATORY_PATH=/usr/share/gconf/gnome-fallback.mandatory.path","UBUNTU_MENUPROXY=libappmenu.so","GDMSESSION=gnome-fallback","SHLVL=1","HOME=/home/jost","LANGUAGE=en_US:en","GNOME_DESKTOP_SESSION_ID=this-is-deprecated","LOGNAME=jost","PVM_EXPORT=DISPLAY","XDG_DATA_DIRS=/usr/share/gnome-fallback:/usr/share/gnome:/usr/local/share/:/usr/share/","DBUS_SESSION_BUS_ADDRESS=unix:abstract=/tmp/dbus-Mviy2n6D5M,guid=3677210ad991dc7e0dc3a1ae00000012","LESSOPEN=| /usr/bin/lesspipe %s","DISPLAY=:0.0","XDG_CURRENT_DESKTOP=GNOME","LESSCLOSE=/usr/bin/lesspipe %s %s","COLORTERM=gnome-terminal","XAUTHORITY=/home/jost/.Xauthority","_=./wrongeventlog2"] +716554: cap 0: creating thread 1 +724337: cap 0: running thread 1 +777249: cap 0: stopping thread 1 (heap overflow) +4206233: cap 0: running thread 1 +4371098: cap 0: stopping thread 1 (making a foreign call) +4373253: cap 0: running thread 1 +4468468: cap 0: forking child thread +4628142: cap 0: creating thread 2 +4629931: cap 0: stopping thread 1 (thread yielding) +4631259: cap 0: running thread 2 +4635338: cap 0: stopping thread 2 (heap overflow) +5624512: cap 0: running thread 2 +5633862: cap 0: child +10558539: cap 0: stopping thread 2 (thread yielding) +10560195: cap 0: running thread 1 +10571646: cap 0: stopping thread 1 (blocked on black hole owned by thread 2) +10571821: cap 0: running thread 2 190091289: cap 0: stopping thread 2 (heap overflow) 190645077: cap 0: running thread 2 324320577: cap 0: stopping thread 2 (heap overflow) @@ -137,4 +137,3 @@ Events: 819827079: deleted capset 0 819827133: deleted capset 1 - diff --git a/test/queens-ghc-6.12.1.eventlog.reference b/test/queens-ghc-6.12.1.eventlog.reference index e2bb7d7..bb3f4c9 100644 --- a/test/queens-ghc-6.12.1.eventlog.reference +++ b/test/queens-ghc-6.12.1.eventlog.reference @@ -1,510 +1,509 @@ Event Types: - 0: Create thread (size 8) - 1: Run thread (size 8) - 2: Stop thread (size 10) - 3: Thread runnable (size 8) - 4: Migrate thread (size 10) - 5: Run spark (size 8) - 6: Steal spark (size 10) - 7: Shutdown (size 0) - 8: Wakeup thread (size 10) - 9: Starting GC (size 0) - 10: Finished GC (size 0) - 11: Request sequential GC (size 0) - 12: Request parallel GC (size 0) - 15: Create spark thread (size 8) - 16: Log message (size variable) - 17: Startup (size 0) - 18: Block marker (size 14) - 19: User message (size variable) +0: Create thread (size 8) +1: Run thread (size 8) +2: Stop thread (size 10) +3: Thread runnable (size 8) +4: Migrate thread (size 10) +5: Run spark (size 8) +6: Steal spark (size 10) +7: Shutdown (size 0) +8: Wakeup thread (size 10) +9: Starting GC (size 0) +10: Finished GC (size 0) +11: Request sequential GC (size 0) +12: Request parallel GC (size 0) +15: Create spark thread (size 8) +16: Log message (size variable) +17: Startup (size 0) +18: Block marker (size 14) +19: User message (size variable) Events: - 106000: startup: 4 capabilities - 431000: cap 3: creating thread 1 - 431000: cap 3: thread 1 is runnable - 432000: cap 3: running thread 1 - 471000: cap 3: creating thread 2 - 471000: cap 3: thread 2 is runnable - 471000: cap 3: stopping thread 1 (thread finished) - 478000: cap 3: creating thread 3 - 479000: cap 3: thread 3 is runnable - 517000: cap 3: running thread 2 - 580000: cap 3: stopping thread 2 (making a foreign call) - 585000: cap 3: running thread 2 - 606000: cap 3: stopping thread 2 (making a foreign call) - 612000: cap 3: running thread 3 - 667000: cap 3: stopping thread 3 (thread yielding) - 668000: cap 3: thread 3 is runnable - 668000: cap 3: running thread 3 - 834000: cap 3: stopping thread 3 (stack overflow) - 839000: cap 3: running thread 3 - 1459000: cap 3: stopping thread 3 (heap overflow) - 1460000: cap 3: requesting parallel GC - 1470000: cap 0: starting GC - 1473000: cap 1: starting GC - 1473000: cap 2: starting GC - 1474000: cap 3: starting GC - 1631000: cap 3: finished GC - 1632000: cap 0: finished GC - 1632000: cap 1: finished GC - 1632000: cap 2: finished GC - 1633000: cap 3: running thread 3 - 1637000: cap 2: creating thread 4 - 1637000: cap 2: creating spark thread 4 - 1637000: cap 2: thread 4 is runnable - 1637000: cap 2: running thread 4 - 1638000: cap 0: creating thread 5 - 1638000: cap 0: creating spark thread 5 - 1638000: cap 3: stopping thread 3 (thread yielding) - 1638000: cap 3: thread 3 is runnable - 1639000: cap 0: thread 5 is runnable - 1639000: cap 0: running thread 5 - 1639000: cap 1: creating thread 6 - 1639000: cap 1: creating spark thread 6 - 1639000: cap 1: thread 6 is runnable - 1639000: cap 3: running thread 3 - 1640000: cap 1: running thread 6 - 1642000: cap 2: stealing a spark from cap 3 - 1647000: cap 0: stealing a spark from cap 3 - 1647000: cap 1: stealing a spark from cap 3 - 1652000: cap 2: stopping thread 4 (thread yielding) - 1653000: cap 2: thread 4 is runnable - 1653000: cap 2: running thread 4 - 1663000: cap 0: stopping thread 5 (thread yielding) - 1663000: cap 1: stopping thread 6 (thread yielding) - 1664000: cap 0: thread 5 is runnable - 1664000: cap 0: running thread 5 - 1664000: cap 1: thread 6 is runnable - 1664000: cap 1: running thread 6 - 1672000: cap 2: stopping thread 4 (stack overflow) - 1676000: cap 2: running thread 4 - 1684000: cap 0: stopping thread 5 (stack overflow) - 1687000: cap 1: stopping thread 6 (stack overflow) - 1688000: cap 0: running thread 5 - 1691000: cap 1: running thread 6 - 1974000: cap 3: stopping thread 3 (heap overflow) - 1974000: cap 3: requesting parallel GC - 1975000: cap 1: stopping thread 6 (thread yielding) - 1975000: cap 1: thread 6 is runnable - 1975000: cap 2: stopping thread 4 (thread yielding) - 1976000: cap 1: starting GC - 1976000: cap 2: thread 4 is runnable - 1976000: cap 2: starting GC - 1977000: cap 0: stopping thread 5 (thread yielding) - 1977000: cap 0: thread 5 is runnable - 1977000: cap 0: starting GC - 1978000: cap 3: starting GC - 2054000: cap 3: finished GC - 2055000: cap 0: finished GC - 2055000: cap 1: finished GC - 2055000: cap 2: finished GC - 2056000: cap 0: running thread 5 - 2056000: cap 1: running thread 6 - 2056000: cap 2: running thread 4 - 2056000: cap 3: running thread 3 - 2066000: cap 0: stopping thread 5 (thread yielding) - 2066000: cap 0: thread 5 is runnable - 2066000: cap 1: stopping thread 6 (thread yielding) - 2066000: cap 2: stopping thread 4 (thread yielding) - 2066000: cap 2: thread 4 is runnable - 2066000: cap 3: stopping thread 3 (thread yielding) - 2066000: cap 3: thread 3 is runnable - 2067000: cap 0: running thread 5 - 2067000: cap 1: thread 6 is runnable - 2067000: cap 1: running thread 6 - 2067000: cap 2: running thread 4 - 2067000: cap 3: running thread 3 - 2413000: cap 3: stopping thread 3 (heap overflow) - 2414000: cap 3: requesting parallel GC - 2417000: cap 0: stopping thread 5 (thread yielding) - 2417000: cap 0: thread 5 is runnable - 2417000: cap 0: starting GC - 2417000: cap 1: stopping thread 6 (thread yielding) - 2417000: cap 1: thread 6 is runnable - 2417000: cap 1: starting GC - 2417000: cap 2: stopping thread 4 (thread yielding) - 2418000: cap 2: thread 4 is runnable - 2418000: cap 2: starting GC - 2419000: cap 3: starting GC - 2457000: cap 3: finished GC - 2458000: cap 0: finished GC - 2458000: cap 0: running thread 5 - 2458000: cap 1: finished GC - 2458000: cap 2: finished GC - 2458000: cap 3: running thread 3 - 2459000: cap 1: running thread 6 - 2459000: cap 2: running thread 4 - 2462000: cap 0: stopping thread 5 (thread yielding) - 2462000: cap 0: thread 5 is runnable - 2462000: cap 2: stopping thread 4 (thread yielding) - 2463000: cap 0: running thread 5 - 2463000: cap 1: stopping thread 6 (thread yielding) - 2463000: cap 2: thread 4 is runnable - 2463000: cap 2: running thread 4 - 2463000: cap 3: stopping thread 3 (thread yielding) - 2463000: cap 3: thread 3 is runnable - 2463000: cap 3: running thread 3 - 2464000: cap 1: thread 6 is runnable - 2464000: cap 1: running thread 6 - 2573000: cap 3: stopping thread 3 (thread blocked) - 2612000: cap 3: creating thread 7 - 2612000: cap 3: creating spark thread 7 - 2612000: cap 3: thread 7 is runnable - 2613000: cap 3: running thread 7 - 2616000: cap 3: running a local spark - 2629000: cap 3: stopping thread 7 (stack overflow) - 2630000: cap 3: running thread 7 - 2845000: cap 3: stopping thread 7 (heap overflow) - 2846000: cap 3: requesting parallel GC - 2848000: cap 1: stopping thread 6 (thread yielding) - 2848000: cap 1: thread 6 is runnable - 2848000: cap 2: stopping thread 4 (thread yielding) - 2848000: cap 2: thread 4 is runnable - 2849000: cap 0: stopping thread 5 (thread yielding) - 2849000: cap 1: starting GC - 2849000: cap 2: starting GC - 2850000: cap 0: thread 5 is runnable - 2850000: cap 0: starting GC - 2851000: cap 3: starting GC - 2890000: cap 0: finished GC - 2890000: cap 1: finished GC - 2890000: cap 3: finished GC - 2891000: cap 0: running thread 5 - 2891000: cap 1: running thread 6 - 2891000: cap 2: finished GC - 2891000: cap 2: running thread 4 - 2891000: cap 3: running thread 7 - 2894000: cap 3: stopping thread 7 (thread yielding) - 2895000: cap 0: stopping thread 5 (thread yielding) - 2895000: cap 1: stopping thread 6 (thread yielding) - 2895000: cap 2: stopping thread 4 (thread yielding) - 2895000: cap 3: thread 7 is runnable - 2895000: cap 3: running thread 7 - 2896000: cap 0: thread 5 is runnable - 2896000: cap 0: running thread 5 - 2896000: cap 1: thread 6 is runnable - 2896000: cap 1: running thread 6 - 2896000: cap 2: thread 4 is runnable - 2896000: cap 2: running thread 4 - 3231000: cap 3: stopping thread 7 (heap overflow) - 3231000: cap 3: requesting parallel GC - 3232000: cap 2: stopping thread 4 (thread yielding) - 3232000: cap 2: thread 4 is runnable - 3232000: cap 2: starting GC - 3233000: cap 0: stopping thread 5 (thread yielding) - 3233000: cap 0: thread 5 is runnable - 3233000: cap 0: starting GC - 3233000: cap 1: stopping thread 6 (thread yielding) - 3233000: cap 1: thread 6 is runnable - 3233000: cap 1: starting GC - 3234000: cap 3: starting GC - 3268000: cap 3: finished GC - 3269000: cap 0: finished GC - 3269000: cap 0: running thread 5 - 3269000: cap 1: finished GC - 3269000: cap 1: running thread 6 - 3269000: cap 2: finished GC - 3269000: cap 3: running thread 7 - 3270000: cap 2: running thread 4 - 3273000: cap 0: stopping thread 5 (thread yielding) - 3274000: cap 0: thread 5 is runnable - 3274000: cap 0: running thread 5 - 3274000: cap 2: stopping thread 4 (thread yielding) - 3274000: cap 2: thread 4 is runnable - 3274000: cap 3: stopping thread 7 (thread yielding) - 3274000: cap 3: thread 7 is runnable - 3275000: cap 1: stopping thread 6 (thread yielding) - 3275000: cap 1: thread 6 is runnable - 3275000: cap 1: running thread 6 - 3275000: cap 2: running thread 4 - 3275000: cap 3: running thread 7 - 3507000: cap 2: stealing a spark from cap 3 - 3524000: cap 0: stealing a spark from cap 2 - 3540000: cap 1: stealing a spark from cap 0 - 3607000: cap 3: stopping thread 7 (heap overflow) - 3607000: cap 3: requesting parallel GC - 3609000: cap 0: stopping thread 5 (thread yielding) - 3609000: cap 0: thread 5 is runnable - 3609000: cap 0: starting GC - 3609000: cap 1: stopping thread 6 (thread yielding) - 3609000: cap 1: thread 6 is runnable - 3609000: cap 1: starting GC - 3609000: cap 2: stopping thread 4 (thread yielding) - 3609000: cap 2: thread 4 is runnable - 3610000: cap 2: starting GC - 3610000: cap 3: thread 3 is runnable - 3610000: cap 3: waking up thread 3 on cap 3 - 3611000: cap 3: starting GC - 3642000: cap 3: finished GC - 3643000: cap 0: finished GC - 3643000: cap 0: running thread 5 - 3643000: cap 1: finished GC - 3643000: cap 2: finished GC - 3643000: cap 2: running thread 4 - 3644000: cap 1: running thread 6 - 3644000: cap 3: running thread 7 - 3647000: cap 0: stopping thread 5 (thread yielding) - 3647000: cap 2: stopping thread 4 (thread yielding) - 3647000: cap 2: thread 4 is runnable - 3648000: cap 0: thread 5 is runnable - 3648000: cap 0: running thread 5 - 3648000: cap 1: stopping thread 6 (thread yielding) - 3648000: cap 1: thread 6 is runnable - 3648000: cap 1: running thread 6 - 3648000: cap 2: running thread 4 - 3648000: cap 3: stopping thread 7 (thread yielding) - 3648000: cap 3: thread 7 is runnable - 3662000: cap 3: running thread 3 - 3666000: cap 3: stopping thread 3 (thread blocked) - 3668000: cap 3: running thread 7 - 3684000: cap 1: stealing a spark from cap 2 - 3692000: cap 0: stealing a spark from cap 1 - 3729000: cap 2: stopping thread 4 (thread blocked) - 3730000: cap 2: creating thread 8 - 3730000: cap 2: creating spark thread 8 - 3731000: cap 2: thread 8 is runnable - 3731000: cap 2: running thread 8 - 3731000: cap 2: running a local spark - 3770000: cap 0: stealing a spark from cap 1 - 3810000: cap 1: stopping thread 6 (thread blocked) - 3812000: cap 1: creating thread 9 - 3813000: cap 1: creating spark thread 9 - 3813000: cap 1: thread 9 is runnable - 3813000: cap 1: running thread 9 - 3814000: cap 1: stealing a spark from cap 2 - 3865000: cap 0: stealing a spark from cap 1 - 3883000: cap 1: stopping thread 9 (thread blocked) - 3884000: cap 1: thread 6 is runnable - 3884000: cap 1: waking up thread 6 on cap 1 - 3884000: cap 1: running thread 6 - 3885000: cap 1: stopping thread 6 (thread yielding) - 3885000: cap 1: thread 6 is runnable - 3885000: cap 1: running thread 6 - 3886000: cap 1: running a local spark - 3955000: cap 0: stealing a spark from cap 1 - 3985000: cap 2: stopping thread 8 (heap overflow) - 3986000: cap 2: requesting parallel GC - 3987000: cap 0: stopping thread 5 (heap overflow) - 3987000: cap 0: thread 5 is runnable - 3987000: cap 0: starting GC - 3987000: cap 1: stealing a spark from cap 3 - 3988000: cap 1: stopping thread 6 (thread yielding) - 3988000: cap 1: thread 6 is runnable - 3988000: cap 1: starting GC - 3988000: cap 3: stopping thread 7 (thread yielding) - 3988000: cap 3: thread 7 is runnable - 3988000: cap 3: starting GC - 3989000: cap 2: waking up thread 9 on cap 1 - 3990000: cap 2: thread 4 is runnable - 3990000: cap 2: waking up thread 4 on cap 2 - 3990000: cap 2: starting GC - 4032000: cap 0: finished GC - 4032000: cap 2: finished GC - 4033000: cap 0: running thread 5 - 4033000: cap 1: finished GC - 4033000: cap 1: running thread 6 - 4033000: cap 2: running thread 8 - 4033000: cap 3: finished GC - 4033000: cap 3: running thread 7 - 4037000: cap 0: stopping thread 5 (thread yielding) - 4037000: cap 0: thread 5 is runnable - 4037000: cap 0: running thread 5 - 4037000: cap 3: stopping thread 7 (thread yielding) - 4037000: cap 3: thread 7 is runnable - 4037000: cap 3: running thread 7 - 4038000: cap 1: stopping thread 6 (thread yielding) - 4038000: cap 1: thread 6 is runnable - 4038000: cap 1: running thread 6 - 4038000: cap 2: stopping thread 8 (thread yielding) - 4038000: cap 2: thread 8 is runnable - 4038000: cap 2: running thread 4 - 4041000: cap 2: stopping thread 4 (thread blocked) - 4041000: cap 2: running thread 8 - 4053000: cap 2: stealing a spark from cap 1 - 4064000: cap 0: stealing a spark from cap 1 - 4102000: cap 3: running a local spark - 4296000: cap 0: stealing a spark from cap 1 - 4308000: cap 2: stealing a spark from cap 0 - 4312000: cap 1: stopping thread 6 (thread blocked) - 4313000: cap 1: running thread 9 - 4314000: cap 1: running a local spark - 4375000: cap 2: stopping thread 8 (heap overflow) - 4375000: cap 2: requesting parallel GC - 4376000: cap 0: stopping thread 5 (heap overflow) - 4376000: cap 0: thread 5 is runnable - 4376000: cap 0: starting GC - 4376000: cap 3: stopping thread 7 (thread yielding) - 4377000: cap 3: thread 7 is runnable - 4377000: cap 3: starting GC - 4378000: cap 1: stopping thread 9 (thread yielding) - 4379000: cap 1: thread 9 is runnable - 4379000: cap 1: starting GC - 4380000: cap 2: thread 4 is runnable - 4380000: cap 2: waking up thread 4 on cap 2 - 4380000: cap 2: waking up thread 3 on cap 3 - 4380000: cap 2: starting GC - 4419000: cap 2: finished GC - 4420000: cap 0: finished GC - 4420000: cap 1: finished GC - 4420000: cap 3: finished GC - 4421000: cap 0: running thread 5 - 4421000: cap 1: running thread 9 - 4421000: cap 2: running thread 8 - 4421000: cap 3: running thread 7 - 4424000: cap 0: stopping thread 5 (thread yielding) - 4424000: cap 0: thread 5 is runnable - 4424000: cap 3: stopping thread 7 (thread yielding) - 4424000: cap 3: thread 7 is runnable - 4425000: cap 0: running thread 5 - 4425000: cap 2: stopping thread 8 (thread yielding) - 4425000: cap 2: thread 8 is runnable - 4425000: cap 2: running thread 4 - 4425000: cap 3: running thread 7 - 4426000: cap 1: stopping thread 9 (thread yielding) - 4426000: cap 1: thread 9 is runnable - 4426000: cap 1: running thread 9 - 4428000: cap 2: stopping thread 4 (thread finished) - 4428000: cap 2: running thread 8 - 4440000: cap 2: stealing a spark from cap 0 - 4466000: cap 0: stopping thread 5 (thread blocked) - 4467000: cap 0: creating thread 10 - 4468000: cap 0: creating spark thread 10 - 4468000: cap 0: thread 10 is runnable - 4468000: cap 0: running thread 10 - 4468000: cap 0: running a local spark - 4497000: cap 2: stealing a spark from cap 1 - 4512000: cap 0: stealing a spark from cap 3 - 4515000: cap 3: stopping thread 7 (thread blocked) - 4527000: cap 3: running thread 3 - 4529000: cap 3: stopping thread 3 (thread blocked) - 4532000: cap 3: waking up thread 5 on cap 0 - 4532000: cap 3: creating thread 11 - 4532000: cap 3: creating spark thread 11 - 4533000: cap 3: thread 11 is runnable - 4533000: cap 3: running thread 11 - 4534000: cap 0: stopping thread 10 (thread yielding) - 4534000: cap 0: thread 10 is runnable - 4534000: cap 3: running a local spark - 4535000: cap 0: running thread 10 - 4547000: cap 1: stopping thread 9 (thread blocked) - 4549000: cap 1: creating thread 12 - 4549000: cap 1: creating spark thread 12 - 4549000: cap 1: thread 12 is runnable - 4549000: cap 1: running thread 12 - 4550000: cap 1: stealing a spark from cap 0 - 4562000: cap 2: stealing a spark from cap 0 - 4595000: cap 2: stealing a spark from cap 3 - 4600000: cap 0: stopping thread 10 (thread blocked) - 4600000: cap 0: running thread 5 - 4601000: cap 0: stealing a spark from cap 2 - 4608000: cap 1: stealing a spark from cap 2 - 4625000: cap 2: stopping thread 8 (thread blocked) - 4626000: cap 2: waking up thread 10 on cap 0 - 4627000: cap 2: waking up thread 9 on cap 1 - 4627000: cap 2: waking up thread 6 on cap 1 - 4628000: cap 0: stopping thread 5 (thread yielding) - 4628000: cap 0: thread 5 is runnable - 4628000: cap 2: creating thread 13 - 4628000: cap 2: creating spark thread 13 - 4628000: cap 2: thread 13 is runnable - 4629000: cap 0: running thread 5 - 4629000: cap 1: stopping thread 12 (thread yielding) - 4629000: cap 1: thread 12 is runnable - 4629000: cap 1: running thread 12 - 4629000: cap 2: running thread 13 - 4629000: cap 2: running a local spark - 4665000: cap 1: stopping thread 12 (thread finished) - 4665000: cap 1: running thread 9 - 4666000: cap 1: stopping thread 9 (thread finished) - 4666000: cap 1: running thread 6 - 4668000: cap 1: stealing a spark from cap 3 - 4669000: cap 0: stopping thread 5 (thread finished) - 4669000: cap 0: running thread 10 - 4670000: cap 0: stopping thread 10 (thread finished) - 4671000: cap 0: waking up thread 8 on cap 2 - 4672000: cap 0: waking up thread 3 on cap 3 - 4672000: cap 0: waking up thread 7 on cap 3 - 4672000: cap 0: creating thread 14 - 4673000: cap 0: creating spark thread 14 - 4673000: cap 0: thread 14 is runnable - 4673000: cap 0: running thread 14 - 4673000: cap 0: stealing a spark from cap 1 - 4673000: cap 3: stopping thread 11 (thread yielding) - 4673000: cap 3: thread 11 is runnable - 4674000: cap 2: stopping thread 13 (thread yielding) - 4674000: cap 2: thread 13 is runnable - 4674000: cap 3: running thread 11 - 4675000: cap 1: stopping thread 6 (thread blocked) - 4675000: cap 1: creating thread 15 - 4675000: cap 2: running thread 13 - 4676000: cap 1: creating spark thread 15 - 4676000: cap 1: thread 15 is runnable - 4676000: cap 1: running thread 15 - 4676000: cap 1: running a local spark - 4685000: cap 2: stopping thread 13 (thread finished) - 4686000: cap 2: running thread 8 - 4687000: cap 2: stealing a spark from cap 1 - 4707000: cap 1: running a local spark - 4711000: cap 3: stopping thread 11 (thread finished) - 4719000: cap 0: stopping thread 14 (thread finished) - 4719000: cap 0: waking up thread 6 on cap 1 - 4721000: cap 1: stopping thread 15 (thread yielding) - 4721000: cap 1: thread 15 is runnable - 4721000: cap 3: running thread 3 - 4722000: cap 0: thread 6 is runnable - 4722000: cap 1: migrating thread 6 to cap 0 - 4724000: cap 3: stopping thread 3 (thread blocked) - 4725000: cap 1: running thread 15 - 4726000: cap 3: running thread 7 - 4728000: cap 0: running thread 6 - 4728000: cap 2: stopping thread 8 (thread finished) - 4732000: cap 3: stopping thread 7 (thread blocked) - 4734000: cap 0: stopping thread 6 (thread blocked) - 4778000: cap 1: stopping thread 15 (heap overflow) - 4779000: cap 1: requesting parallel GC - 4784000: cap 0: starting GC - 4790000: cap 2: starting GC - 4793000: cap 3: starting GC - 4794000: cap 1: starting GC - 4833000: cap 1: finished GC - 4834000: cap 0: finished GC - 4834000: cap 1: running thread 15 - 4834000: cap 2: finished GC - 4834000: cap 3: finished GC - 4838000: cap 1: stopping thread 15 (thread yielding) - 4838000: cap 1: thread 15 is runnable - 4839000: cap 1: running thread 15 - 4846000: cap 0: thread 6 is runnable - 4846000: cap 1: stopping thread 15 (thread finished) - 4849000: cap 1: waking up thread 6 on cap 0 - 4851000: cap 0: running thread 6 - 4852000: cap 0: stopping thread 6 (thread finished) - 4853000: cap 3: thread 7 is runnable - 4857000: cap 0: waking up thread 7 on cap 3 - 4859000: cap 3: running thread 7 - 4861000: cap 3: stopping thread 7 (thread finished) - 4861000: cap 3: thread 3 is runnable - 4861000: cap 3: waking up thread 3 on cap 3 - 4866000: cap 3: running thread 3 - 4903000: cap 3: stopping thread 3 (making a foreign call) - 4904000: cap 3: running thread 3 - 4905000: cap 3: stopping thread 3 (making a foreign call) - 4914000: cap 3: running thread 3 - 4918000: cap 3: stopping thread 3 (thread yielding) - 4918000: cap 3: thread 3 is runnable - 4919000: cap 3: running thread 3 - 4946000: cap 3: stopping thread 3 (thread finished) - 4962000: cap 3: running thread 2 - 4964000: cap 0: requesting sequential GC - 4965000: cap 3: stopping thread 2 (thread yielding) - 4966000: cap 3: thread 2 is runnable - 4972000: cap 0: starting GC - 5026000: cap 0: finished GC - 5037000: cap 3: running thread 2 - 5037000: cap 3: stopping thread 2 (thread finished) - 5053000: cap 0: shutting down - 5054000: cap 1: shutting down - 5104000: cap 2: shutting down - 5105000: cap 3: shutting down - +106000: startup: 4 capabilities +431000: cap 3: creating thread 1 +431000: cap 3: thread 1 is runnable +432000: cap 3: running thread 1 +471000: cap 3: creating thread 2 +471000: cap 3: thread 2 is runnable +471000: cap 3: stopping thread 1 (thread finished) +478000: cap 3: creating thread 3 +479000: cap 3: thread 3 is runnable +517000: cap 3: running thread 2 +580000: cap 3: stopping thread 2 (making a foreign call) +585000: cap 3: running thread 2 +606000: cap 3: stopping thread 2 (making a foreign call) +612000: cap 3: running thread 3 +667000: cap 3: stopping thread 3 (thread yielding) +668000: cap 3: thread 3 is runnable +668000: cap 3: running thread 3 +834000: cap 3: stopping thread 3 (stack overflow) +839000: cap 3: running thread 3 +1459000: cap 3: stopping thread 3 (heap overflow) +1460000: cap 3: requesting parallel GC +1470000: cap 0: starting GC +1473000: cap 1: starting GC +1473000: cap 2: starting GC +1474000: cap 3: starting GC +1631000: cap 3: finished GC +1632000: cap 0: finished GC +1632000: cap 1: finished GC +1632000: cap 2: finished GC +1633000: cap 3: running thread 3 +1637000: cap 2: creating thread 4 +1637000: cap 2: creating spark thread 4 +1637000: cap 2: thread 4 is runnable +1637000: cap 2: running thread 4 +1638000: cap 0: creating thread 5 +1638000: cap 0: creating spark thread 5 +1638000: cap 3: stopping thread 3 (thread yielding) +1638000: cap 3: thread 3 is runnable +1639000: cap 0: thread 5 is runnable +1639000: cap 0: running thread 5 +1639000: cap 1: creating thread 6 +1639000: cap 1: creating spark thread 6 +1639000: cap 1: thread 6 is runnable +1639000: cap 3: running thread 3 +1640000: cap 1: running thread 6 +1642000: cap 2: stealing a spark from cap 3 +1647000: cap 0: stealing a spark from cap 3 +1647000: cap 1: stealing a spark from cap 3 +1652000: cap 2: stopping thread 4 (thread yielding) +1653000: cap 2: thread 4 is runnable +1653000: cap 2: running thread 4 +1663000: cap 0: stopping thread 5 (thread yielding) +1663000: cap 1: stopping thread 6 (thread yielding) +1664000: cap 0: thread 5 is runnable +1664000: cap 0: running thread 5 +1664000: cap 1: thread 6 is runnable +1664000: cap 1: running thread 6 +1672000: cap 2: stopping thread 4 (stack overflow) +1676000: cap 2: running thread 4 +1684000: cap 0: stopping thread 5 (stack overflow) +1687000: cap 1: stopping thread 6 (stack overflow) +1688000: cap 0: running thread 5 +1691000: cap 1: running thread 6 +1974000: cap 3: stopping thread 3 (heap overflow) +1974000: cap 3: requesting parallel GC +1975000: cap 1: stopping thread 6 (thread yielding) +1975000: cap 1: thread 6 is runnable +1975000: cap 2: stopping thread 4 (thread yielding) +1976000: cap 1: starting GC +1976000: cap 2: thread 4 is runnable +1976000: cap 2: starting GC +1977000: cap 0: stopping thread 5 (thread yielding) +1977000: cap 0: thread 5 is runnable +1977000: cap 0: starting GC +1978000: cap 3: starting GC +2054000: cap 3: finished GC +2055000: cap 0: finished GC +2055000: cap 1: finished GC +2055000: cap 2: finished GC +2056000: cap 0: running thread 5 +2056000: cap 1: running thread 6 +2056000: cap 2: running thread 4 +2056000: cap 3: running thread 3 +2066000: cap 0: stopping thread 5 (thread yielding) +2066000: cap 0: thread 5 is runnable +2066000: cap 1: stopping thread 6 (thread yielding) +2066000: cap 2: stopping thread 4 (thread yielding) +2066000: cap 2: thread 4 is runnable +2066000: cap 3: stopping thread 3 (thread yielding) +2066000: cap 3: thread 3 is runnable +2067000: cap 0: running thread 5 +2067000: cap 1: thread 6 is runnable +2067000: cap 1: running thread 6 +2067000: cap 2: running thread 4 +2067000: cap 3: running thread 3 +2413000: cap 3: stopping thread 3 (heap overflow) +2414000: cap 3: requesting parallel GC +2417000: cap 0: stopping thread 5 (thread yielding) +2417000: cap 0: thread 5 is runnable +2417000: cap 0: starting GC +2417000: cap 1: stopping thread 6 (thread yielding) +2417000: cap 1: thread 6 is runnable +2417000: cap 1: starting GC +2417000: cap 2: stopping thread 4 (thread yielding) +2418000: cap 2: thread 4 is runnable +2418000: cap 2: starting GC +2419000: cap 3: starting GC +2457000: cap 3: finished GC +2458000: cap 0: finished GC +2458000: cap 0: running thread 5 +2458000: cap 1: finished GC +2458000: cap 2: finished GC +2458000: cap 3: running thread 3 +2459000: cap 1: running thread 6 +2459000: cap 2: running thread 4 +2462000: cap 0: stopping thread 5 (thread yielding) +2462000: cap 0: thread 5 is runnable +2462000: cap 2: stopping thread 4 (thread yielding) +2463000: cap 0: running thread 5 +2463000: cap 1: stopping thread 6 (thread yielding) +2463000: cap 2: thread 4 is runnable +2463000: cap 2: running thread 4 +2463000: cap 3: stopping thread 3 (thread yielding) +2463000: cap 3: thread 3 is runnable +2463000: cap 3: running thread 3 +2464000: cap 1: thread 6 is runnable +2464000: cap 1: running thread 6 +2573000: cap 3: stopping thread 3 (thread blocked) +2612000: cap 3: creating thread 7 +2612000: cap 3: creating spark thread 7 +2612000: cap 3: thread 7 is runnable +2613000: cap 3: running thread 7 +2616000: cap 3: running a local spark +2629000: cap 3: stopping thread 7 (stack overflow) +2630000: cap 3: running thread 7 +2845000: cap 3: stopping thread 7 (heap overflow) +2846000: cap 3: requesting parallel GC +2848000: cap 1: stopping thread 6 (thread yielding) +2848000: cap 1: thread 6 is runnable +2848000: cap 2: stopping thread 4 (thread yielding) +2848000: cap 2: thread 4 is runnable +2849000: cap 0: stopping thread 5 (thread yielding) +2849000: cap 1: starting GC +2849000: cap 2: starting GC +2850000: cap 0: thread 5 is runnable +2850000: cap 0: starting GC +2851000: cap 3: starting GC +2890000: cap 0: finished GC +2890000: cap 1: finished GC +2890000: cap 3: finished GC +2891000: cap 0: running thread 5 +2891000: cap 1: running thread 6 +2891000: cap 2: finished GC +2891000: cap 2: running thread 4 +2891000: cap 3: running thread 7 +2894000: cap 3: stopping thread 7 (thread yielding) +2895000: cap 0: stopping thread 5 (thread yielding) +2895000: cap 1: stopping thread 6 (thread yielding) +2895000: cap 2: stopping thread 4 (thread yielding) +2895000: cap 3: thread 7 is runnable +2895000: cap 3: running thread 7 +2896000: cap 0: thread 5 is runnable +2896000: cap 0: running thread 5 +2896000: cap 1: thread 6 is runnable +2896000: cap 1: running thread 6 +2896000: cap 2: thread 4 is runnable +2896000: cap 2: running thread 4 +3231000: cap 3: stopping thread 7 (heap overflow) +3231000: cap 3: requesting parallel GC +3232000: cap 2: stopping thread 4 (thread yielding) +3232000: cap 2: thread 4 is runnable +3232000: cap 2: starting GC +3233000: cap 0: stopping thread 5 (thread yielding) +3233000: cap 0: thread 5 is runnable +3233000: cap 0: starting GC +3233000: cap 1: stopping thread 6 (thread yielding) +3233000: cap 1: thread 6 is runnable +3233000: cap 1: starting GC +3234000: cap 3: starting GC +3268000: cap 3: finished GC +3269000: cap 0: finished GC +3269000: cap 0: running thread 5 +3269000: cap 1: finished GC +3269000: cap 1: running thread 6 +3269000: cap 2: finished GC +3269000: cap 3: running thread 7 +3270000: cap 2: running thread 4 +3273000: cap 0: stopping thread 5 (thread yielding) +3274000: cap 0: thread 5 is runnable +3274000: cap 0: running thread 5 +3274000: cap 2: stopping thread 4 (thread yielding) +3274000: cap 2: thread 4 is runnable +3274000: cap 3: stopping thread 7 (thread yielding) +3274000: cap 3: thread 7 is runnable +3275000: cap 1: stopping thread 6 (thread yielding) +3275000: cap 1: thread 6 is runnable +3275000: cap 1: running thread 6 +3275000: cap 2: running thread 4 +3275000: cap 3: running thread 7 +3507000: cap 2: stealing a spark from cap 3 +3524000: cap 0: stealing a spark from cap 2 +3540000: cap 1: stealing a spark from cap 0 +3607000: cap 3: stopping thread 7 (heap overflow) +3607000: cap 3: requesting parallel GC +3609000: cap 0: stopping thread 5 (thread yielding) +3609000: cap 0: thread 5 is runnable +3609000: cap 0: starting GC +3609000: cap 1: stopping thread 6 (thread yielding) +3609000: cap 1: thread 6 is runnable +3609000: cap 1: starting GC +3609000: cap 2: stopping thread 4 (thread yielding) +3609000: cap 2: thread 4 is runnable +3610000: cap 2: starting GC +3610000: cap 3: thread 3 is runnable +3610000: cap 3: waking up thread 3 on cap 3 +3611000: cap 3: starting GC +3642000: cap 3: finished GC +3643000: cap 0: finished GC +3643000: cap 0: running thread 5 +3643000: cap 1: finished GC +3643000: cap 2: finished GC +3643000: cap 2: running thread 4 +3644000: cap 1: running thread 6 +3644000: cap 3: running thread 7 +3647000: cap 0: stopping thread 5 (thread yielding) +3647000: cap 2: stopping thread 4 (thread yielding) +3647000: cap 2: thread 4 is runnable +3648000: cap 0: thread 5 is runnable +3648000: cap 0: running thread 5 +3648000: cap 1: stopping thread 6 (thread yielding) +3648000: cap 1: thread 6 is runnable +3648000: cap 1: running thread 6 +3648000: cap 2: running thread 4 +3648000: cap 3: stopping thread 7 (thread yielding) +3648000: cap 3: thread 7 is runnable +3662000: cap 3: running thread 3 +3666000: cap 3: stopping thread 3 (thread blocked) +3668000: cap 3: running thread 7 +3684000: cap 1: stealing a spark from cap 2 +3692000: cap 0: stealing a spark from cap 1 +3729000: cap 2: stopping thread 4 (thread blocked) +3730000: cap 2: creating thread 8 +3730000: cap 2: creating spark thread 8 +3731000: cap 2: thread 8 is runnable +3731000: cap 2: running thread 8 +3731000: cap 2: running a local spark +3770000: cap 0: stealing a spark from cap 1 +3810000: cap 1: stopping thread 6 (thread blocked) +3812000: cap 1: creating thread 9 +3813000: cap 1: creating spark thread 9 +3813000: cap 1: thread 9 is runnable +3813000: cap 1: running thread 9 +3814000: cap 1: stealing a spark from cap 2 +3865000: cap 0: stealing a spark from cap 1 +3883000: cap 1: stopping thread 9 (thread blocked) +3884000: cap 1: thread 6 is runnable +3884000: cap 1: waking up thread 6 on cap 1 +3884000: cap 1: running thread 6 +3885000: cap 1: stopping thread 6 (thread yielding) +3885000: cap 1: thread 6 is runnable +3885000: cap 1: running thread 6 +3886000: cap 1: running a local spark +3955000: cap 0: stealing a spark from cap 1 +3985000: cap 2: stopping thread 8 (heap overflow) +3986000: cap 2: requesting parallel GC +3987000: cap 0: stopping thread 5 (heap overflow) +3987000: cap 0: thread 5 is runnable +3987000: cap 0: starting GC +3987000: cap 1: stealing a spark from cap 3 +3988000: cap 1: stopping thread 6 (thread yielding) +3988000: cap 1: thread 6 is runnable +3988000: cap 1: starting GC +3988000: cap 3: stopping thread 7 (thread yielding) +3988000: cap 3: thread 7 is runnable +3988000: cap 3: starting GC +3989000: cap 2: waking up thread 9 on cap 1 +3990000: cap 2: thread 4 is runnable +3990000: cap 2: waking up thread 4 on cap 2 +3990000: cap 2: starting GC +4032000: cap 0: finished GC +4032000: cap 2: finished GC +4033000: cap 0: running thread 5 +4033000: cap 1: finished GC +4033000: cap 1: running thread 6 +4033000: cap 2: running thread 8 +4033000: cap 3: finished GC +4033000: cap 3: running thread 7 +4037000: cap 0: stopping thread 5 (thread yielding) +4037000: cap 0: thread 5 is runnable +4037000: cap 0: running thread 5 +4037000: cap 3: stopping thread 7 (thread yielding) +4037000: cap 3: thread 7 is runnable +4037000: cap 3: running thread 7 +4038000: cap 1: stopping thread 6 (thread yielding) +4038000: cap 1: thread 6 is runnable +4038000: cap 1: running thread 6 +4038000: cap 2: stopping thread 8 (thread yielding) +4038000: cap 2: thread 8 is runnable +4038000: cap 2: running thread 4 +4041000: cap 2: stopping thread 4 (thread blocked) +4041000: cap 2: running thread 8 +4053000: cap 2: stealing a spark from cap 1 +4064000: cap 0: stealing a spark from cap 1 +4102000: cap 3: running a local spark +4296000: cap 0: stealing a spark from cap 1 +4308000: cap 2: stealing a spark from cap 0 +4312000: cap 1: stopping thread 6 (thread blocked) +4313000: cap 1: running thread 9 +4314000: cap 1: running a local spark +4375000: cap 2: stopping thread 8 (heap overflow) +4375000: cap 2: requesting parallel GC +4376000: cap 0: stopping thread 5 (heap overflow) +4376000: cap 0: thread 5 is runnable +4376000: cap 0: starting GC +4376000: cap 3: stopping thread 7 (thread yielding) +4377000: cap 3: thread 7 is runnable +4377000: cap 3: starting GC +4378000: cap 1: stopping thread 9 (thread yielding) +4379000: cap 1: thread 9 is runnable +4379000: cap 1: starting GC +4380000: cap 2: thread 4 is runnable +4380000: cap 2: waking up thread 4 on cap 2 +4380000: cap 2: waking up thread 3 on cap 3 +4380000: cap 2: starting GC +4419000: cap 2: finished GC +4420000: cap 0: finished GC +4420000: cap 1: finished GC +4420000: cap 3: finished GC +4421000: cap 0: running thread 5 +4421000: cap 1: running thread 9 +4421000: cap 2: running thread 8 +4421000: cap 3: running thread 7 +4424000: cap 0: stopping thread 5 (thread yielding) +4424000: cap 0: thread 5 is runnable +4424000: cap 3: stopping thread 7 (thread yielding) +4424000: cap 3: thread 7 is runnable +4425000: cap 0: running thread 5 +4425000: cap 2: stopping thread 8 (thread yielding) +4425000: cap 2: thread 8 is runnable +4425000: cap 2: running thread 4 +4425000: cap 3: running thread 7 +4426000: cap 1: stopping thread 9 (thread yielding) +4426000: cap 1: thread 9 is runnable +4426000: cap 1: running thread 9 +4428000: cap 2: stopping thread 4 (thread finished) +4428000: cap 2: running thread 8 +4440000: cap 2: stealing a spark from cap 0 +4466000: cap 0: stopping thread 5 (thread blocked) +4467000: cap 0: creating thread 10 +4468000: cap 0: creating spark thread 10 +4468000: cap 0: thread 10 is runnable +4468000: cap 0: running thread 10 +4468000: cap 0: running a local spark +4497000: cap 2: stealing a spark from cap 1 +4512000: cap 0: stealing a spark from cap 3 +4515000: cap 3: stopping thread 7 (thread blocked) +4527000: cap 3: running thread 3 +4529000: cap 3: stopping thread 3 (thread blocked) +4532000: cap 3: waking up thread 5 on cap 0 +4532000: cap 3: creating thread 11 +4532000: cap 3: creating spark thread 11 +4533000: cap 3: thread 11 is runnable +4533000: cap 3: running thread 11 +4534000: cap 0: stopping thread 10 (thread yielding) +4534000: cap 0: thread 10 is runnable +4534000: cap 3: running a local spark +4535000: cap 0: running thread 10 +4547000: cap 1: stopping thread 9 (thread blocked) +4549000: cap 1: creating thread 12 +4549000: cap 1: creating spark thread 12 +4549000: cap 1: thread 12 is runnable +4549000: cap 1: running thread 12 +4550000: cap 1: stealing a spark from cap 0 +4562000: cap 2: stealing a spark from cap 0 +4595000: cap 2: stealing a spark from cap 3 +4600000: cap 0: stopping thread 10 (thread blocked) +4600000: cap 0: running thread 5 +4601000: cap 0: stealing a spark from cap 2 +4608000: cap 1: stealing a spark from cap 2 +4625000: cap 2: stopping thread 8 (thread blocked) +4626000: cap 2: waking up thread 10 on cap 0 +4627000: cap 2: waking up thread 9 on cap 1 +4627000: cap 2: waking up thread 6 on cap 1 +4628000: cap 0: stopping thread 5 (thread yielding) +4628000: cap 0: thread 5 is runnable +4628000: cap 2: creating thread 13 +4628000: cap 2: creating spark thread 13 +4628000: cap 2: thread 13 is runnable +4629000: cap 0: running thread 5 +4629000: cap 1: stopping thread 12 (thread yielding) +4629000: cap 1: thread 12 is runnable +4629000: cap 1: running thread 12 +4629000: cap 2: running thread 13 +4629000: cap 2: running a local spark +4665000: cap 1: stopping thread 12 (thread finished) +4665000: cap 1: running thread 9 +4666000: cap 1: stopping thread 9 (thread finished) +4666000: cap 1: running thread 6 +4668000: cap 1: stealing a spark from cap 3 +4669000: cap 0: stopping thread 5 (thread finished) +4669000: cap 0: running thread 10 +4670000: cap 0: stopping thread 10 (thread finished) +4671000: cap 0: waking up thread 8 on cap 2 +4672000: cap 0: waking up thread 3 on cap 3 +4672000: cap 0: waking up thread 7 on cap 3 +4672000: cap 0: creating thread 14 +4673000: cap 0: creating spark thread 14 +4673000: cap 0: thread 14 is runnable +4673000: cap 0: running thread 14 +4673000: cap 0: stealing a spark from cap 1 +4673000: cap 3: stopping thread 11 (thread yielding) +4673000: cap 3: thread 11 is runnable +4674000: cap 2: stopping thread 13 (thread yielding) +4674000: cap 2: thread 13 is runnable +4674000: cap 3: running thread 11 +4675000: cap 1: stopping thread 6 (thread blocked) +4675000: cap 1: creating thread 15 +4675000: cap 2: running thread 13 +4676000: cap 1: creating spark thread 15 +4676000: cap 1: thread 15 is runnable +4676000: cap 1: running thread 15 +4676000: cap 1: running a local spark +4685000: cap 2: stopping thread 13 (thread finished) +4686000: cap 2: running thread 8 +4687000: cap 2: stealing a spark from cap 1 +4707000: cap 1: running a local spark +4711000: cap 3: stopping thread 11 (thread finished) +4719000: cap 0: stopping thread 14 (thread finished) +4719000: cap 0: waking up thread 6 on cap 1 +4721000: cap 1: stopping thread 15 (thread yielding) +4721000: cap 1: thread 15 is runnable +4721000: cap 3: running thread 3 +4722000: cap 0: thread 6 is runnable +4722000: cap 1: migrating thread 6 to cap 0 +4724000: cap 3: stopping thread 3 (thread blocked) +4725000: cap 1: running thread 15 +4726000: cap 3: running thread 7 +4728000: cap 0: running thread 6 +4728000: cap 2: stopping thread 8 (thread finished) +4732000: cap 3: stopping thread 7 (thread blocked) +4734000: cap 0: stopping thread 6 (thread blocked) +4778000: cap 1: stopping thread 15 (heap overflow) +4779000: cap 1: requesting parallel GC +4784000: cap 0: starting GC +4790000: cap 2: starting GC +4793000: cap 3: starting GC +4794000: cap 1: starting GC +4833000: cap 1: finished GC +4834000: cap 0: finished GC +4834000: cap 1: running thread 15 +4834000: cap 2: finished GC +4834000: cap 3: finished GC +4838000: cap 1: stopping thread 15 (thread yielding) +4838000: cap 1: thread 15 is runnable +4839000: cap 1: running thread 15 +4846000: cap 0: thread 6 is runnable +4846000: cap 1: stopping thread 15 (thread finished) +4849000: cap 1: waking up thread 6 on cap 0 +4851000: cap 0: running thread 6 +4852000: cap 0: stopping thread 6 (thread finished) +4853000: cap 3: thread 7 is runnable +4857000: cap 0: waking up thread 7 on cap 3 +4859000: cap 3: running thread 7 +4861000: cap 3: stopping thread 7 (thread finished) +4861000: cap 3: thread 3 is runnable +4861000: cap 3: waking up thread 3 on cap 3 +4866000: cap 3: running thread 3 +4903000: cap 3: stopping thread 3 (making a foreign call) +4904000: cap 3: running thread 3 +4905000: cap 3: stopping thread 3 (making a foreign call) +4914000: cap 3: running thread 3 +4918000: cap 3: stopping thread 3 (thread yielding) +4918000: cap 3: thread 3 is runnable +4919000: cap 3: running thread 3 +4946000: cap 3: stopping thread 3 (thread finished) +4962000: cap 3: running thread 2 +4964000: cap 0: requesting sequential GC +4965000: cap 3: stopping thread 2 (thread yielding) +4966000: cap 3: thread 2 is runnable +4972000: cap 0: starting GC +5026000: cap 0: finished GC +5037000: cap 3: running thread 2 +5037000: cap 3: stopping thread 2 (thread finished) +5053000: cap 0: shutting down +5054000: cap 1: shutting down +5104000: cap 2: shutting down +5105000: cap 3: shutting down diff --git a/test/queens-ghc-7.0.2.eventlog.reference b/test/queens-ghc-7.0.2.eventlog.reference index 03cb4ad..b3cc422 100644 --- a/test/queens-ghc-7.0.2.eventlog.reference +++ b/test/queens-ghc-7.0.2.eventlog.reference @@ -1,944 +1,943 @@ Event Types: - 0: Create thread (size 4) - 1: Run thread (size 4) - 2: Stop thread (size 6) - 3: Thread runnable (size 4) - 4: Migrate thread (size 6) - 5: Run spark (size 4) - 6: Steal spark (size 6) - 7: Shutdown (size 0) - 8: Wakeup thread (size 6) - 9: Starting GC (size 0) - 10: Finished GC (size 0) - 11: Request sequential GC (size 0) - 12: Request parallel GC (size 0) - 15: Create spark thread (size 4) - 16: Log message (size variable) - 17: Startup (size 2) - 18: Block marker (size 14) - 19: User message (size variable) - 20: GC idle (size 0) - 21: GC working (size 0) - 22: GC done (size 0) +0: Create thread (size 4) +1: Run thread (size 4) +2: Stop thread (size 6) +3: Thread runnable (size 4) +4: Migrate thread (size 6) +5: Run spark (size 4) +6: Steal spark (size 6) +7: Shutdown (size 0) +8: Wakeup thread (size 6) +9: Starting GC (size 0) +10: Finished GC (size 0) +11: Request sequential GC (size 0) +12: Request parallel GC (size 0) +15: Create spark thread (size 4) +16: Log message (size variable) +17: Startup (size 2) +18: Block marker (size 14) +19: User message (size variable) +20: GC idle (size 0) +21: GC working (size 0) +22: GC done (size 0) Events: - 115000: startup: 4 capabilities - 430000: cap 3: creating thread 1 - 430000: cap 3: thread 1 is runnable - 433000: cap 3: running thread 1 - 512000: cap 3: stopping thread 1 (making a foreign call) - 513000: cap 3: running thread 1 - 516000: cap 3: stopping thread 1 (making a foreign call) - 517000: cap 3: running thread 1 - 554000: cap 3: creating thread 2 - 554000: cap 3: thread 2 is runnable - 572000: cap 3: stopping thread 1 (thread finished) - 580000: cap 3: creating thread 3 - 580000: cap 3: thread 3 is runnable - 619000: cap 3: running thread 2 - 635000: cap 3: stopping thread 2 (thread yielding) - 635000: cap 3: thread 2 is runnable - 637000: cap 0: thread 2 is runnable - 637000: cap 3: migrating thread 2 to cap 0 - 648000: cap 0: running thread 2 - 655000: cap 3: running thread 3 - 672000: cap 0: stopping thread 2 (making a foreign call) - 893000: cap 3: stopping thread 3 (stack overflow) - 897000: cap 3: running thread 3 - 1466000: cap 3: stopping thread 3 (heap overflow) - 1467000: cap 3: requesting parallel GC - 1476000: cap 0: starting GC - 1480000: cap 1: starting GC - 1481000: cap 2: starting GC - 1483000: cap 3: starting GC - 1503000: cap 1: GC working - 1503000: cap 2: GC working - 1506000: cap 2: GC idle - 1507000: cap 1: GC idle - 1509000: cap 0: GC working - 1514000: cap 3: GC working - 1566000: cap 0: GC idle - 1628000: cap 0: GC done - 1628000: cap 1: GC done - 1628000: cap 3: GC idle - 1628000: cap 3: GC done - 1629000: cap 2: GC done - 1629000: cap 3: GC working - 1630000: cap 3: GC idle - 1630000: cap 3: GC done - 1630000: cap 3: GC working - 1631000: cap 3: GC idle - 1631000: cap 3: GC done - 1631000: cap 3: GC working - 1631000: cap 3: GC idle - 1632000: cap 3: GC done - 1653000: cap 0: finished GC - 1653000: cap 3: finished GC - 1654000: cap 1: finished GC - 1654000: cap 2: finished GC - 1654000: cap 3: running thread 3 - 1658000: cap 3: stopping thread 3 (thread yielding) - 1659000: cap 2: creating thread 4 - 1659000: cap 2: creating spark thread 4 - 1659000: cap 3: thread 3 is runnable - 1659000: cap 3: running thread 3 - 1660000: cap 0: creating thread 5 - 1660000: cap 0: creating spark thread 5 - 1660000: cap 0: thread 5 is runnable - 1660000: cap 2: thread 4 is runnable - 1660000: cap 2: running thread 4 - 1661000: cap 0: running thread 5 - 1663000: cap 1: creating thread 6 - 1663000: cap 1: creating spark thread 6 - 1663000: cap 1: thread 6 is runnable - 1664000: cap 1: running thread 6 - 1665000: cap 2: stealing a spark from cap 3 - 1667000: cap 0: stealing a spark from cap 3 - 1669000: cap 1: stealing a spark from cap 3 - 1675000: cap 2: stopping thread 4 (thread yielding) - 1675000: cap 2: thread 4 is runnable - 1676000: cap 2: running thread 4 - 1681000: cap 0: stopping thread 5 (thread yielding) - 1681000: cap 0: thread 5 is runnable - 1681000: cap 0: running thread 5 - 1681000: cap 1: stopping thread 6 (thread yielding) - 1681000: cap 1: thread 6 is runnable - 1681000: cap 1: running thread 6 - 1692000: cap 2: stopping thread 4 (stack overflow) - 1694000: cap 2: running thread 4 - 1699000: cap 0: stopping thread 5 (stack overflow) - 1700000: cap 1: stopping thread 6 (stack overflow) - 1705000: cap 0: running thread 5 - 1705000: cap 1: running thread 6 - 1949000: cap 3: stopping thread 3 (heap overflow) - 1950000: cap 3: requesting parallel GC - 1951000: cap 0: stopping thread 5 (thread yielding) - 1951000: cap 0: thread 5 is runnable - 1951000: cap 0: starting GC - 1951000: cap 1: stopping thread 6 (thread yielding) - 1951000: cap 1: thread 6 is runnable - 1951000: cap 1: starting GC - 1951000: cap 2: stopping thread 4 (thread yielding) - 1951000: cap 2: thread 4 is runnable - 1952000: cap 2: starting GC - 1953000: cap 3: starting GC - 1962000: cap 1: GC working - 1963000: cap 2: GC working - 1964000: cap 0: GC working - 1969000: cap 3: GC working - 1990000: cap 2: GC idle - 1991000: cap 0: GC idle - 1992000: cap 1: GC idle - 1999000: cap 0: GC done - 1999000: cap 1: GC done - 1999000: cap 2: GC done - 1999000: cap 3: GC idle - 1999000: cap 3: GC done - 2000000: cap 3: GC working - 2000000: cap 3: GC idle - 2000000: cap 3: GC done - 2000000: cap 3: GC working - 2001000: cap 3: GC idle - 2001000: cap 3: GC done - 2002000: cap 3: GC working - 2002000: cap 3: GC idle - 2002000: cap 3: GC done - 2013000: cap 3: finished GC - 2014000: cap 0: finished GC - 2014000: cap 0: running thread 5 - 2014000: cap 1: finished GC - 2014000: cap 2: finished GC - 2014000: cap 3: running thread 3 - 2015000: cap 1: running thread 6 - 2015000: cap 2: running thread 4 - 2017000: cap 0: stopping thread 5 (thread yielding) - 2018000: cap 0: thread 5 is runnable - 2018000: cap 0: running thread 5 - 2018000: cap 2: stopping thread 4 (thread yielding) - 2018000: cap 2: thread 4 is runnable - 2019000: cap 1: stopping thread 6 (thread yielding) - 2019000: cap 1: thread 6 is runnable - 2019000: cap 2: running thread 4 - 2019000: cap 3: stopping thread 3 (thread yielding) - 2019000: cap 3: thread 3 is runnable - 2019000: cap 3: running thread 3 - 2020000: cap 1: running thread 6 - 2307000: cap 3: stopping thread 3 (heap overflow) - 2307000: cap 3: requesting parallel GC - 2308000: cap 1: stopping thread 6 (thread yielding) - 2309000: cap 1: thread 6 is runnable - 2309000: cap 1: starting GC - 2310000: cap 0: stopping thread 5 (thread yielding) - 2310000: cap 2: stopping thread 4 (thread yielding) - 2310000: cap 2: thread 4 is runnable - 2310000: cap 2: starting GC - 2311000: cap 0: thread 5 is runnable - 2311000: cap 0: starting GC - 2311000: cap 3: starting GC - 2319000: cap 1: GC working - 2320000: cap 2: GC working - 2323000: cap 0: GC working - 2327000: cap 3: GC working - 2333000: cap 2: GC idle - 2334000: cap 0: GC idle - 2335000: cap 3: GC idle - 2336000: cap 0: GC done - 2336000: cap 1: GC idle - 2336000: cap 1: GC done - 2336000: cap 2: GC done - 2336000: cap 3: GC done - 2337000: cap 3: GC working - 2337000: cap 3: GC idle - 2337000: cap 3: GC done - 2337000: cap 3: GC working - 2337000: cap 3: GC idle - 2337000: cap 3: GC done - 2338000: cap 3: GC working - 2338000: cap 3: GC idle - 2338000: cap 3: GC done - 2351000: cap 3: finished GC - 2352000: cap 0: finished GC - 2352000: cap 0: running thread 5 - 2352000: cap 1: finished GC - 2352000: cap 2: finished GC - 2353000: cap 1: running thread 6 - 2353000: cap 2: running thread 4 - 2353000: cap 3: running thread 3 - 2356000: cap 0: stopping thread 5 (thread yielding) - 2356000: cap 0: thread 5 is runnable - 2356000: cap 1: stopping thread 6 (thread yielding) - 2356000: cap 1: thread 6 is runnable - 2356000: cap 2: stopping thread 4 (thread yielding) - 2356000: cap 2: thread 4 is runnable - 2357000: cap 0: running thread 5 - 2357000: cap 1: running thread 6 - 2357000: cap 2: running thread 4 - 2357000: cap 3: stopping thread 3 (thread yielding) - 2357000: cap 3: thread 3 is runnable - 2357000: cap 3: running thread 3 - 2451000: cap 2: stopping thread 4 (thread yielding) - 2451000: cap 2: thread 4 is runnable - 2452000: cap 3: stopping thread 3 (thread blocked) - 2452000: cap 3: creating thread 7 - 2453000: cap 2: running thread 4 - 2453000: cap 3: creating spark thread 7 - 2453000: cap 3: thread 7 is runnable - 2463000: cap 3: running thread 7 - 2465000: cap 3: running a local spark - 2480000: cap 3: stopping thread 7 (stack overflow) - 2481000: cap 3: running thread 7 - 2749000: cap 2: stopping thread 4 (heap overflow) - 2750000: cap 2: requesting parallel GC - 2751000: cap 1: stopping thread 6 (thread yielding) - 2751000: cap 3: stopping thread 7 (thread yielding) - 2752000: cap 1: thread 6 is runnable - 2752000: cap 1: starting GC - 2752000: cap 3: thread 7 is runnable - 2752000: cap 3: starting GC - 6061000: cap 0: stopping thread 5 (thread yielding) - 6062000: cap 0: thread 5 is runnable - 6062000: cap 0: starting GC - 6063000: cap 2: starting GC - 6074000: cap 1: GC working - 6075000: cap 0: GC working - 6075000: cap 2: GC working - 6076000: cap 3: GC working - 6079000: cap 2: GC idle - 6082000: cap 1: GC idle - 6084000: cap 0: GC idle - 6090000: cap 0: GC done - 6090000: cap 1: GC done - 6090000: cap 2: GC done - 6090000: cap 3: GC idle - 6090000: cap 3: GC done - 6091000: cap 2: GC working - 6091000: cap 2: GC idle - 6091000: cap 2: GC done - 6091000: cap 2: GC working - 6091000: cap 2: GC idle - 6091000: cap 2: GC done - 6092000: cap 2: GC working - 6092000: cap 2: GC idle - 6092000: cap 2: GC done - 6107000: cap 0: finished GC - 6107000: cap 2: finished GC - 6108000: cap 0: running thread 5 - 6108000: cap 1: finished GC - 6108000: cap 1: running thread 6 - 6108000: cap 2: running thread 4 - 6108000: cap 3: finished GC - 6109000: cap 3: running thread 7 - 6113000: cap 1: stopping thread 6 (thread yielding) - 6113000: cap 1: thread 6 is runnable - 6114000: cap 1: running thread 6 - 6114000: cap 2: stopping thread 4 (thread yielding) - 6115000: cap 0: stopping thread 5 (thread yielding) - 6115000: cap 2: thread 4 is runnable - 6115000: cap 2: running thread 4 - 6115000: cap 3: stopping thread 7 (thread yielding) - 6115000: cap 3: thread 7 is runnable - 6116000: cap 0: thread 5 is runnable - 6116000: cap 0: running thread 5 - 6116000: cap 3: running thread 7 - 6403000: cap 2: stopping thread 4 (heap overflow) - 6403000: cap 2: requesting parallel GC - 6404000: cap 0: stopping thread 5 (thread yielding) - 6404000: cap 0: thread 5 is runnable - 6404000: cap 1: stopping thread 6 (heap overflow) - 6404000: cap 1: thread 6 is runnable - 6404000: cap 3: stopping thread 7 (thread yielding) - 6405000: cap 0: starting GC - 6405000: cap 1: starting GC - 6405000: cap 3: thread 7 is runnable - 6405000: cap 3: starting GC - 6406000: cap 2: starting GC - 6414000: cap 3: GC working - 6415000: cap 0: GC working - 6415000: cap 1: GC working - 6417000: cap 2: GC working - 6420000: cap 1: GC idle - 6421000: cap 0: GC idle - 6422000: cap 2: GC idle - 6425000: cap 0: GC done - 6425000: cap 1: GC done - 6425000: cap 2: GC done - 6425000: cap 3: GC idle - 6425000: cap 3: GC done - 6426000: cap 2: GC working - 6426000: cap 2: GC idle - 6426000: cap 2: GC done - 6426000: cap 2: GC working - 6426000: cap 2: GC idle - 6427000: cap 2: GC done - 6427000: cap 2: GC working - 6427000: cap 2: GC idle - 6427000: cap 2: GC done - 6440000: cap 0: finished GC - 6440000: cap 2: finished GC - 6441000: cap 0: running thread 5 - 6441000: cap 1: finished GC - 6441000: cap 1: running thread 6 - 6441000: cap 2: running thread 4 - 6441000: cap 3: finished GC - 6442000: cap 3: running thread 7 - 6445000: cap 0: stopping thread 5 (thread yielding) - 6445000: cap 0: thread 5 is runnable - 6445000: cap 1: stopping thread 6 (thread yielding) - 6445000: cap 3: stopping thread 7 (thread yielding) - 6445000: cap 3: thread 7 is runnable - 6445000: cap 3: running thread 7 - 6446000: cap 0: running thread 5 - 6446000: cap 1: thread 6 is runnable - 6446000: cap 1: running thread 6 - 6446000: cap 2: stopping thread 4 (thread yielding) - 6446000: cap 2: thread 4 is runnable - 6446000: cap 2: running thread 4 - 6648000: cap 1: stealing a spark from cap 0 - 6653000: cap 0: stopping thread 5 (thread blocked) - 6653000: cap 0: creating thread 8 - 6653000: cap 1: stopping thread 6 (thread yielding) - 6653000: cap 1: thread 6 is runnable - 6654000: cap 0: creating spark thread 8 - 6654000: cap 0: thread 8 is runnable - 6654000: cap 0: running thread 8 - 6655000: cap 0: running a local spark - 6655000: cap 1: running thread 6 - 6656000: cap 2: waking up thread 3 on cap 3 - 6658000: cap 2: stealing a spark from cap 1 - 6658000: cap 3: stopping thread 7 (thread yielding) - 6658000: cap 3: thread 7 is runnable - 6659000: cap 3: waking up thread 3 on cap 3 - 6659000: cap 3: thread 3 is runnable - 6660000: cap 3: running thread 7 - 6727000: cap 2: stopping thread 4 (heap overflow) - 6728000: cap 1: stopping thread 6 (thread yielding) - 6728000: cap 2: requesting parallel GC - 6729000: cap 0: stopping thread 8 (thread yielding) - 6729000: cap 0: thread 8 is runnable - 6729000: cap 0: starting GC - 6729000: cap 1: thread 6 is runnable - 6729000: cap 1: starting GC - 6729000: cap 3: stopping thread 7 (thread yielding) - 6729000: cap 3: thread 7 is runnable - 6730000: cap 2: starting GC - 6730000: cap 3: starting GC - 6737000: cap 0: GC working - 6737000: cap 2: GC working - 6738000: cap 1: GC working - 6739000: cap 3: GC working - 6741000: cap 2: GC idle - 6744000: cap 1: GC idle - 6747000: cap 3: GC idle - 6748000: cap 0: GC idle - 6748000: cap 1: GC done - 6748000: cap 2: GC done - 6749000: cap 0: GC done - 6749000: cap 2: GC working - 6749000: cap 2: GC idle - 6749000: cap 2: GC done - 6749000: cap 3: GC done - 6750000: cap 2: GC working - 6750000: cap 2: GC idle - 6750000: cap 2: GC done - 6750000: cap 2: GC working - 6750000: cap 2: GC idle - 6750000: cap 2: GC done - 6764000: cap 0: finished GC - 6764000: cap 0: running thread 8 - 6764000: cap 1: finished GC - 6764000: cap 2: finished GC - 6765000: cap 1: running thread 6 - 6765000: cap 2: running thread 4 - 6765000: cap 3: finished GC - 6768000: cap 1: stopping thread 6 (thread yielding) - 6769000: cap 0: stopping thread 8 (thread yielding) - 6769000: cap 0: thread 8 is runnable - 6769000: cap 1: thread 6 is runnable - 6769000: cap 1: running thread 6 - 6769000: cap 2: stopping thread 4 (thread yielding) - 6769000: cap 2: thread 4 is runnable - 6770000: cap 2: running thread 4 - 6777000: cap 3: running thread 3 - 6780000: cap 3: stopping thread 3 (thread blocked) - 6782000: cap 1: stopping thread 6 (thread blocked) - 6782000: cap 2: stopping thread 4 (thread yielding) - 6782000: cap 2: thread 4 is runnable - 6784000: cap 1: creating thread 9 - 6784000: cap 1: creating spark thread 9 - 6784000: cap 2: running thread 4 - 6785000: cap 1: thread 9 is runnable - 6785000: cap 1: running thread 9 - 6786000: cap 1: stealing a spark from cap 0 - 6790000: cap 3: running thread 7 - 6791000: cap 0: running thread 8 - 6794000: cap 3: stopping thread 7 (thread yielding) - 6794000: cap 3: thread 7 is runnable - 6795000: cap 0: stopping thread 8 (thread yielding) - 6795000: cap 0: thread 8 is runnable - 6795000: cap 3: running thread 7 - 6796000: cap 0: running thread 8 - 6802000: cap 2: waking up thread 6 on cap 1 - 6803000: cap 2: stealing a spark from cap 0 - 6804000: cap 1: stopping thread 9 (thread yielding) - 6804000: cap 1: thread 9 is runnable - 6805000: cap 1: waking up thread 6 on cap 1 - 6805000: cap 1: thread 6 is runnable - 6805000: cap 1: running thread 9 - 6818000: cap 1: stopping thread 9 (thread finished) - 6819000: cap 1: running thread 6 - 6819000: cap 1: waking up thread 5 on cap 0 - 6820000: cap 0: stopping thread 8 (thread yielding) - 6820000: cap 1: stealing a spark from cap 3 - 6821000: cap 0: thread 8 is runnable - 6821000: cap 0: waking up thread 5 on cap 0 - 6821000: cap 0: thread 5 is runnable - 6821000: cap 0: running thread 8 - 6828000: cap 0: stopping thread 8 (thread blocked) - 6828000: cap 0: running thread 5 - 6828000: cap 2: stopping thread 4 (thread yielding) - 6829000: cap 2: thread 4 is runnable - 6829000: cap 2: running thread 4 - 6830000: cap 0: stopping thread 5 (thread blocked) - 6831000: cap 0: creating thread 10 - 6831000: cap 0: creating spark thread 10 - 6831000: cap 0: thread 10 is runnable - 6831000: cap 0: running thread 10 - 6832000: cap 0: stealing a spark from cap 1 - 6857000: cap 2: waking up thread 8 on cap 0 - 6857000: cap 2: stealing a spark from cap 0 - 6858000: cap 0: stopping thread 10 (thread yielding) - 6858000: cap 0: thread 10 is runnable - 6858000: cap 0: waking up thread 8 on cap 0 - 6859000: cap 0: thread 8 is runnable - 6859000: cap 0: running thread 10 - 6940000: cap 0: stopping thread 10 (thread blocked) - 6940000: cap 0: running thread 8 - 6940000: cap 2: stopping thread 4 (thread yielding) - 6941000: cap 0: waking up thread 5 on cap 0 - 6941000: cap 0: thread 5 is runnable - 6941000: cap 0: stopping thread 8 (thread finished) - 6941000: cap 0: running thread 5 - 6941000: cap 2: thread 4 is runnable - 6941000: cap 2: running thread 4 - 6942000: cap 0: waking up thread 3 on cap 3 - 6942000: cap 0: stealing a spark from cap 1 - 6943000: cap 3: stopping thread 7 (thread yielding) - 6943000: cap 3: thread 7 is runnable - 6944000: cap 2: waking up thread 10 on cap 0 - 6944000: cap 3: waking up thread 3 on cap 3 - 6944000: cap 3: thread 3 is runnable - 6944000: cap 3: running thread 7 - 6945000: cap 0: stopping thread 5 (thread yielding) - 6945000: cap 0: thread 5 is runnable - 6945000: cap 2: stealing a spark from cap 0 - 6946000: cap 0: waking up thread 10 on cap 0 - 6946000: cap 0: thread 10 is runnable - 6946000: cap 0: running thread 5 - 6949000: cap 0: stopping thread 5 (thread blocked) - 6949000: cap 0: running thread 10 - 6950000: cap 0: running a local spark - 6950000: cap 2: stopping thread 4 (thread yielding) - 6950000: cap 2: thread 4 is runnable - 6950000: cap 2: running thread 4 - 6974000: cap 0: stopping thread 10 (thread yielding) - 6974000: cap 1: stopping thread 6 (thread blocked) - 6975000: cap 0: thread 10 is runnable - 6975000: cap 0: running thread 10 - 6975000: cap 1: creating thread 11 - 6975000: cap 1: creating spark thread 11 - 6976000: cap 1: thread 11 is runnable - 6976000: cap 1: running thread 11 - 6977000: cap 1: running a local spark - 7019000: cap 0: running a local spark - 7046000: cap 2: waking up thread 5 on cap 0 - 7047000: cap 0: stopping thread 10 (thread yielding) - 7047000: cap 0: thread 10 is runnable - 7047000: cap 0: waking up thread 5 on cap 0 - 7047000: cap 0: thread 5 is runnable - 7047000: cap 2: stealing a spark from cap 1 - 7048000: cap 0: running thread 10 - 7066000: cap 2: stopping thread 4 (heap overflow) - 7066000: cap 2: requesting parallel GC - 7067000: cap 1: stopping thread 11 (thread yielding) - 7068000: cap 1: thread 11 is runnable - 7068000: cap 1: starting GC - 7068000: cap 3: stopping thread 7 (thread yielding) - 7068000: cap 3: thread 7 is runnable - 7068000: cap 3: starting GC - 7069000: cap 0: stopping thread 10 (thread yielding) - 7069000: cap 0: thread 10 is runnable - 7070000: cap 0: starting GC - 7070000: cap 2: starting GC - 7078000: cap 0: GC working - 7078000: cap 2: GC working - 7083000: cap 2: GC idle - 7090000: cap 0: GC idle - 7111000: cap 1: GC working - 7121000: cap 1: GC idle - 7141000: cap 3: GC working - 7150000: cap 0: GC done - 7150000: cap 1: GC done - 7150000: cap 2: GC done - 7150000: cap 3: GC idle - 7150000: cap 3: GC done - 7151000: cap 2: GC working - 7151000: cap 2: GC idle - 7151000: cap 2: GC done - 7151000: cap 2: GC working - 7152000: cap 2: GC idle - 7152000: cap 2: GC done - 7152000: cap 2: GC working - 7152000: cap 2: GC idle - 7152000: cap 2: GC done - 7166000: cap 2: finished GC - 7167000: cap 0: finished GC - 7167000: cap 0: running thread 5 - 7167000: cap 1: finished GC - 7168000: cap 1: running thread 11 - 7168000: cap 2: running thread 4 - 7168000: cap 3: finished GC - 7169000: cap 0: stopping thread 5 (thread blocked) - 7170000: cap 0: running thread 10 - 7172000: cap 1: stopping thread 11 (thread yielding) - 7172000: cap 1: thread 11 is runnable - 7172000: cap 2: stopping thread 4 (thread yielding) - 7172000: cap 2: thread 4 is runnable - 7174000: cap 0: stopping thread 10 (thread yielding) - 7174000: cap 0: thread 10 is runnable - 7174000: cap 0: running thread 10 - 7174000: cap 2: running thread 4 - 7175000: cap 1: running thread 11 - 7228000: cap 0: waking up thread 5 on cap 0 - 7228000: cap 0: thread 5 is runnable - 7228000: cap 0: stopping thread 10 (thread finished) - 7228000: cap 0: running thread 5 - 7229000: cap 0: waking up thread 6 on cap 1 - 7230000: cap 0: stealing a spark from cap 1 - 7231000: cap 1: stopping thread 11 (thread yielding) - 7231000: cap 1: thread 11 is runnable - 7231000: cap 1: waking up thread 6 on cap 1 - 7232000: cap 1: thread 6 is runnable - 7232000: cap 1: running thread 11 - 7249000: cap 1: stopping thread 11 (thread blocked) - 7249000: cap 1: running thread 6 - 7250000: cap 0: stopping thread 5 (thread yielding) - 7250000: cap 0: thread 5 is runnable - 7251000: cap 0: running thread 5 - 7253000: cap 1: stopping thread 6 (thread blocked) - 7254000: cap 1: creating thread 12 - 7254000: cap 1: creating spark thread 12 - 7254000: cap 1: thread 12 is runnable - 7254000: cap 1: running thread 12 - 7255000: cap 1: stealing a spark from cap 2 - 7294000: cap 1: stopping thread 12 (thread yielding) - 7294000: cap 2: stopping thread 4 (thread blocked) - 7295000: cap 1: thread 12 is runnable - 7295000: cap 1: running thread 12 - 7295000: cap 2: creating thread 13 - 7295000: cap 2: creating spark thread 13 - 7295000: cap 2: thread 13 is runnable - 7296000: cap 2: running thread 13 - 7297000: cap 2: running a local spark - 7300000: cap 0: waking up thread 11 on cap 1 - 7301000: cap 0: stealing a spark from cap 3 - 7301000: cap 1: stopping thread 12 (thread yielding) - 7301000: cap 1: thread 12 is runnable - 7302000: cap 1: waking up thread 11 on cap 1 - 7302000: cap 1: thread 11 is runnable - 7303000: cap 1: running thread 12 - 7341000: cap 1: waking up thread 4 on cap 2 - 7342000: cap 1: stopping thread 12 (thread finished) - 7342000: cap 1: running thread 11 - 7342000: cap 2: stopping thread 13 (thread yielding) - 7342000: cap 2: thread 13 is runnable - 7343000: cap 1: waking up thread 6 on cap 1 - 7343000: cap 2: waking up thread 4 on cap 2 - 7343000: cap 2: thread 4 is runnable - 7344000: cap 1: thread 6 is runnable - 7344000: cap 1: stopping thread 11 (thread finished) - 7344000: cap 1: running thread 6 - 7344000: cap 2: running thread 13 - 7346000: cap 1: stopping thread 6 (thread blocked) - 7346000: cap 1: creating thread 14 - 7346000: cap 2: stopping thread 13 (thread yielding) - 7346000: cap 2: thread 13 is runnable - 7347000: cap 1: creating spark thread 14 - 7347000: cap 1: thread 14 is runnable - 7347000: cap 1: running thread 14 - 7347000: cap 2: running thread 4 - 7347000: cap 2: stopping thread 4 (thread blocked) - 7348000: cap 1: stealing a spark from cap 0 - 7348000: cap 2: running thread 13 - 7349000: cap 2: waking up thread 4 on cap 2 - 7349000: cap 2: thread 4 is runnable - 7349000: cap 2: stopping thread 13 (thread finished) - 7350000: cap 2: running thread 4 - 7350000: cap 2: waking up thread 6 on cap 1 - 7350000: cap 2: stealing a spark from cap 0 - 7351000: cap 1: stopping thread 14 (thread yielding) - 7351000: cap 1: thread 14 is runnable - 7351000: cap 1: waking up thread 6 on cap 1 - 7352000: cap 1: thread 6 is runnable - 7353000: cap 1: running thread 14 - 7468000: cap 2: stopping thread 4 (heap overflow) - 7468000: cap 2: requesting parallel GC - 7469000: cap 1: stopping thread 14 (thread yielding) - 7469000: cap 1: thread 14 is runnable - 7471000: cap 1: starting GC - 7472000: cap 0: stopping thread 5 (thread yielding) - 7472000: cap 0: thread 5 is runnable - 7473000: cap 0: starting GC - 7502000: cap 3: starting GC - 7503000: cap 2: starting GC - 7510000: cap 1: GC working - 7514000: cap 2: GC working - 7518000: cap 2: GC idle - 7518000: cap 3: GC working - 7523000: cap 3: GC idle - 7524000: cap 1: GC idle - 8359000: cap 0: GC working - 8368000: cap 0: GC idle - 8368000: cap 0: GC done - 8368000: cap 1: GC done - 8368000: cap 2: GC done - 8368000: cap 3: GC done - 8369000: cap 2: GC working - 8369000: cap 2: GC idle - 8369000: cap 2: GC done - 8369000: cap 2: GC working - 8369000: cap 2: GC idle - 8369000: cap 2: GC done - 8370000: cap 2: GC working - 8370000: cap 2: GC idle - 8370000: cap 2: GC done - 8383000: cap 0: finished GC - 8383000: cap 2: finished GC - 8384000: cap 0: running thread 5 - 8384000: cap 1: finished GC - 8384000: cap 1: running thread 6 - 8384000: cap 2: running thread 4 - 8384000: cap 3: finished GC - 8384000: cap 3: running thread 3 - 8385000: cap 1: stopping thread 6 (thread finished) - 8386000: cap 1: running thread 14 - 8389000: cap 2: stopping thread 4 (thread yielding) - 8389000: cap 2: thread 4 is runnable - 8389000: cap 2: running thread 4 - 8389000: cap 3: stopping thread 3 (thread blocked) - 8390000: cap 1: stopping thread 14 (thread yielding) - 8390000: cap 1: thread 14 is runnable - 8393000: cap 0: stopping thread 5 (thread yielding) - 8393000: cap 0: thread 5 is runnable - 8400000: cap 3: running thread 7 - 8403000: cap 3: stopping thread 7 (thread yielding) - 8403000: cap 3: thread 7 is runnable - 8403000: cap 3: running thread 7 - 8404000: cap 1: running thread 14 - 8465000: cap 2: stealing a spark from cap 0 - 8504000: cap 1: stealing a spark from cap 0 - 8623000: cap 3: waking up thread 3 on cap 3 - 8623000: cap 3: thread 3 is runnable - 8623000: cap 3: stopping thread 7 (thread finished) - 8634000: cap 0: running thread 5 - 8635000: cap 3: running thread 3 - 8640000: cap 0: stopping thread 5 (thread yielding) - 8640000: cap 0: thread 5 is runnable - 8640000: cap 3: stopping thread 3 (thread blocked) - 8641000: cap 3: creating thread 15 - 8641000: cap 3: creating spark thread 15 - 8641000: cap 3: thread 15 is runnable - 8649000: cap 3: running thread 15 - 8650000: cap 3: running a local spark - 8661000: cap 3: stopping thread 15 (stack overflow) - 8663000: cap 3: running thread 15 - 8670000: cap 2: stopping thread 4 (heap overflow) - 8670000: cap 2: requesting parallel GC - 8671000: cap 1: stopping thread 14 (thread yielding) - 8671000: cap 1: thread 14 is runnable - 8671000: cap 3: stopping thread 15 (thread yielding) - 8671000: cap 3: thread 15 is runnable - 8671000: cap 3: starting GC - 8672000: cap 1: starting GC - 13162000: cap 0: starting GC - 13162000: cap 2: starting GC - 13170000: cap 1: GC working - 13171000: cap 0: GC working - 13172000: cap 2: GC working - 13177000: cap 1: GC idle - 13178000: cap 0: GC idle - 13178000: cap 2: GC idle - 13186000: cap 3: GC working - 13204000: cap 1: GC done - 13204000: cap 2: GC done - 13204000: cap 3: GC idle - 13204000: cap 3: GC done - 13205000: cap 2: GC working - 13205000: cap 2: GC idle - 13205000: cap 2: GC done - 13205000: cap 2: GC working - 13205000: cap 2: GC idle - 13205000: cap 2: GC done - 13206000: cap 2: GC working - 13206000: cap 2: GC idle - 13206000: cap 2: GC done - 13229000: cap 0: GC done - 13244000: cap 0: finished GC - 13244000: cap 2: finished GC - 13245000: cap 0: running thread 5 - 13245000: cap 1: finished GC - 13245000: cap 1: running thread 14 - 13245000: cap 2: running thread 4 - 13249000: cap 1: stopping thread 14 (thread yielding) - 13249000: cap 1: thread 14 is runnable - 13249000: cap 2: stopping thread 4 (thread yielding) - 13249000: cap 2: thread 4 is runnable - 13249000: cap 2: running thread 4 - 13250000: cap 0: stopping thread 5 (thread yielding) - 13250000: cap 0: thread 5 is runnable - 13250000: cap 1: running thread 14 - 13251000: cap 0: running thread 5 - 13292000: cap 2: stealing a spark from cap 0 - 13294000: cap 1: stealing a spark from cap 3 - 13312000: cap 0: stopping thread 5 (thread blocked) - 13312000: cap 2: stopping thread 4 (thread yielding) - 13312000: cap 2: thread 4 is runnable - 13313000: cap 0: creating thread 16 - 13313000: cap 0: creating spark thread 16 - 13313000: cap 0: thread 16 is runnable - 13314000: cap 0: running thread 16 - 13314000: cap 0: stealing a spark from cap 1 - 13314000: cap 2: running thread 4 - 13340000: cap 2: waking up thread 5 on cap 0 - 13341000: cap 0: stopping thread 16 (thread yielding) - 13341000: cap 0: thread 16 is runnable - 13341000: cap 2: stealing a spark from cap 1 - 13342000: cap 0: waking up thread 5 on cap 0 - 13342000: cap 0: thread 5 is runnable - 13342000: cap 0: running thread 16 - 13364000: cap 0: stopping thread 16 (thread yielding) - 13364000: cap 0: thread 16 is runnable - 13364000: cap 0: running thread 16 - 13364000: cap 1: stopping thread 14 (thread blocked) - 13365000: cap 1: creating thread 17 - 13365000: cap 1: creating spark thread 17 - 13365000: cap 1: thread 17 is runnable - 13365000: cap 1: running thread 17 - 13365000: cap 1: stealing a spark from cap 3 - 13375000: cap 2: stealing a spark from cap 1 - 13423000: cap 2: stealing a spark from cap 1 - 13428000: cap 0: waking up thread 14 on cap 1 - 13429000: cap 0: stopping thread 16 (thread finished) - 13429000: cap 0: running thread 5 - 13430000: cap 1: stopping thread 17 (thread yielding) - 13430000: cap 1: thread 17 is runnable - 13431000: cap 1: waking up thread 14 on cap 1 - 13431000: cap 1: thread 14 is runnable - 13431000: cap 1: running thread 17 - 13432000: cap 0: waking up thread 3 on cap 3 - 13433000: cap 0: stealing a spark from cap 3 - 13442000: cap 1: stopping thread 17 (thread blocked) - 13442000: cap 1: running thread 14 - 13442000: cap 2: stopping thread 4 (thread yielding) - 13442000: cap 2: thread 4 is runnable - 13443000: cap 1: stealing a spark from cap 0 - 13443000: cap 2: running thread 4 - 13453000: cap 2: waking up thread 17 on cap 1 - 13454000: cap 2: stealing a spark from cap 0 - 13455000: cap 1: stopping thread 14 (thread yielding) - 13455000: cap 1: thread 14 is runnable - 13456000: cap 1: waking up thread 17 on cap 1 - 13456000: cap 1: thread 17 is runnable - 13456000: cap 1: running thread 14 - 13476000: cap 1: stopping thread 14 (thread finished) - 13476000: cap 1: running thread 17 - 13476000: cap 1: stealing a spark from cap 3 - 13505000: cap 2: stealing a spark from cap 1 - 13539000: cap 2: stopping thread 4 (heap overflow) - 13539000: cap 2: requesting parallel GC - 13541000: cap 0: stopping thread 5 (thread yielding) - 13541000: cap 0: thread 5 is runnable - 13541000: cap 0: starting GC - 13541000: cap 1: stopping thread 17 (thread yielding) - 13541000: cap 1: thread 17 is runnable - 13541000: cap 1: starting GC - 13578000: cap 3: finished GC - 13578000: cap 3: starting GC - 13579000: cap 2: starting GC - 13585000: cap 1: GC working - 13591000: cap 2: GC working - 13593000: cap 3: GC working - 13595000: cap 2: GC idle - 13596000: cap 1: GC idle - 13603000: cap 3: GC idle - 13880000: cap 0: GC working - 13885000: cap 0: GC idle - 13885000: cap 0: GC done - 13885000: cap 2: GC done - 13886000: cap 1: GC done - 13886000: cap 2: GC working - 13886000: cap 2: GC idle - 13886000: cap 2: GC done - 13886000: cap 2: GC working - 13886000: cap 2: GC idle - 13886000: cap 2: GC done - 13887000: cap 2: GC working - 13887000: cap 2: GC idle - 13887000: cap 2: GC done - 13911000: cap 3: GC done - 13924000: cap 2: finished GC - 13925000: cap 1: finished GC - 13925000: cap 1: running thread 17 - 13925000: cap 2: running thread 4 - 13925000: cap 3: finished GC - 13926000: cap 3: running thread 15 - 13928000: cap 1: stopping thread 17 (thread yielding) - 13928000: cap 2: stopping thread 4 (thread yielding) - 13929000: cap 1: thread 17 is runnable - 13929000: cap 1: running thread 17 - 13929000: cap 2: thread 4 is runnable - 13929000: cap 2: running thread 4 - 13931000: cap 3: stopping thread 15 (thread yielding) - 13931000: cap 3: thread 15 is runnable - 13931000: cap 3: waking up thread 3 on cap 3 - 13931000: cap 3: thread 3 is runnable - 13932000: cap 3: running thread 15 - 13941000: cap 2: stealing a spark from cap 1 - 13944000: cap 1: stopping thread 17 (thread blocked) - 13944000: cap 2: stopping thread 4 (thread yielding) - 13945000: cap 1: creating thread 18 - 13945000: cap 1: creating spark thread 18 - 13945000: cap 1: thread 18 is runnable - 13945000: cap 1: running thread 18 - 13945000: cap 2: thread 4 is runnable - 13946000: cap 1: stealing a spark from cap 3 - 13946000: cap 2: running thread 4 - 13990000: cap 2: waking up thread 17 on cap 1 - 13991000: cap 2: stealing a spark from cap 1 - 13992000: cap 1: stopping thread 18 (thread yielding) - 13992000: cap 1: thread 18 is runnable - 13992000: cap 1: waking up thread 17 on cap 1 - 13992000: cap 1: thread 17 is runnable - 13993000: cap 1: running thread 18 - 14018000: cap 1: stopping thread 18 (thread blocked) - 14018000: cap 1: running thread 17 - 14018000: cap 1: running a local spark - 14019000: cap 2: stopping thread 4 (thread yielding) - 14019000: cap 2: thread 4 is runnable - 14020000: cap 2: running thread 4 - 14029000: cap 2: waking up thread 18 on cap 1 - 14030000: cap 1: stopping thread 17 (thread yielding) - 14030000: cap 1: thread 17 is runnable - 14030000: cap 1: waking up thread 18 on cap 1 - 14030000: cap 2: stealing a spark from cap 3 - 14031000: cap 1: thread 18 is runnable - 14031000: cap 1: running thread 17 - 14035000: cap 3: stopping thread 15 (thread blocked) - 14036000: cap 2: stopping thread 4 (thread yielding) - 14036000: cap 2: thread 4 is runnable - 14036000: cap 2: running thread 4 - 14042000: cap 0: finished GC - 14042000: cap 0: running thread 5 - 14042000: cap 3: running thread 3 - 14045000: cap 3: stopping thread 3 (thread blocked) - 14047000: cap 0: stopping thread 5 (thread yielding) - 14047000: cap 0: thread 5 is runnable - 14048000: cap 0: running thread 5 - 14052000: cap 0: stopping thread 5 (thread finished) - 14057000: cap 2: waking up thread 15 on cap 3 - 14061000: cap 2: stopping thread 4 (thread finished) - 14064000: cap 3: waking up thread 15 on cap 3 - 14065000: cap 3: thread 15 is runnable - 14065000: cap 3: running thread 15 - 14068000: cap 1: stopping thread 17 (thread yielding) - 14068000: cap 1: thread 17 is runnable - 14068000: cap 3: stopping thread 15 (thread blocked) - 14070000: cap 0: thread 17 is runnable - 14070000: cap 1: migrating thread 17 to cap 0 - 14075000: cap 0: running thread 17 - 14078000: cap 1: running thread 18 - 14079000: cap 1: stopping thread 18 (thread blocked) - 14080000: cap 0: stopping thread 17 (thread yielding) - 14080000: cap 0: thread 17 is runnable - 14081000: cap 0: running thread 17 - 14094000: cap 0: waking up thread 18 on cap 1 - 14096000: cap 0: stopping thread 17 (thread finished) - 14098000: cap 1: waking up thread 18 on cap 1 - 14098000: cap 1: thread 18 is runnable - 14099000: cap 1: running thread 18 - 14099000: cap 1: waking up thread 15 on cap 3 - 14102000: cap 1: stopping thread 18 (thread finished) - 14103000: cap 3: waking up thread 15 on cap 3 - 14103000: cap 3: thread 15 is runnable - 14103000: cap 3: running thread 15 - 14103000: cap 3: waking up thread 3 on cap 3 - 14104000: cap 3: thread 3 is runnable - 14104000: cap 3: stopping thread 15 (thread finished) - 14110000: cap 3: running thread 3 - 14146000: cap 3: stopping thread 3 (making a foreign call) - 14147000: cap 3: running thread 3 - 14147000: cap 3: stopping thread 3 (making a foreign call) - 14157000: cap 3: running thread 3 - 14191000: cap 3: stopping thread 3 (thread finished) - 14204000: cap 3: requesting sequential GC - 14206000: cap 3: starting GC - 14229000: cap 0: GC working - 14242000: cap 0: GC idle - 14242000: cap 0: GC done - 14243000: cap 0: GC working - 14243000: cap 0: GC idle - 14244000: cap 0: GC done - 14244000: cap 0: GC working - 14244000: cap 0: GC idle - 14244000: cap 0: GC done - 14244000: cap 0: GC working - 14244000: cap 0: GC idle - 14245000: cap 0: GC done - 14254000: cap 3: finished GC - 14261000: cap 0: running thread 2 - 14306000: cap 0: stopping thread 2 (thread finished) - 14344000: cap 0: shutting down - 14345000: cap 1: shutting down - 14346000: cap 2: shutting down - 14346000: cap 3: shutting down - +115000: startup: 4 capabilities +430000: cap 3: creating thread 1 +430000: cap 3: thread 1 is runnable +433000: cap 3: running thread 1 +512000: cap 3: stopping thread 1 (making a foreign call) +513000: cap 3: running thread 1 +516000: cap 3: stopping thread 1 (making a foreign call) +517000: cap 3: running thread 1 +554000: cap 3: creating thread 2 +554000: cap 3: thread 2 is runnable +572000: cap 3: stopping thread 1 (thread finished) +580000: cap 3: creating thread 3 +580000: cap 3: thread 3 is runnable +619000: cap 3: running thread 2 +635000: cap 3: stopping thread 2 (thread yielding) +635000: cap 3: thread 2 is runnable +637000: cap 0: thread 2 is runnable +637000: cap 3: migrating thread 2 to cap 0 +648000: cap 0: running thread 2 +655000: cap 3: running thread 3 +672000: cap 0: stopping thread 2 (making a foreign call) +893000: cap 3: stopping thread 3 (stack overflow) +897000: cap 3: running thread 3 +1466000: cap 3: stopping thread 3 (heap overflow) +1467000: cap 3: requesting parallel GC +1476000: cap 0: starting GC +1480000: cap 1: starting GC +1481000: cap 2: starting GC +1483000: cap 3: starting GC +1503000: cap 1: GC working +1503000: cap 2: GC working +1506000: cap 2: GC idle +1507000: cap 1: GC idle +1509000: cap 0: GC working +1514000: cap 3: GC working +1566000: cap 0: GC idle +1628000: cap 0: GC done +1628000: cap 1: GC done +1628000: cap 3: GC idle +1628000: cap 3: GC done +1629000: cap 2: GC done +1629000: cap 3: GC working +1630000: cap 3: GC idle +1630000: cap 3: GC done +1630000: cap 3: GC working +1631000: cap 3: GC idle +1631000: cap 3: GC done +1631000: cap 3: GC working +1631000: cap 3: GC idle +1632000: cap 3: GC done +1653000: cap 0: finished GC +1653000: cap 3: finished GC +1654000: cap 1: finished GC +1654000: cap 2: finished GC +1654000: cap 3: running thread 3 +1658000: cap 3: stopping thread 3 (thread yielding) +1659000: cap 2: creating thread 4 +1659000: cap 2: creating spark thread 4 +1659000: cap 3: thread 3 is runnable +1659000: cap 3: running thread 3 +1660000: cap 0: creating thread 5 +1660000: cap 0: creating spark thread 5 +1660000: cap 0: thread 5 is runnable +1660000: cap 2: thread 4 is runnable +1660000: cap 2: running thread 4 +1661000: cap 0: running thread 5 +1663000: cap 1: creating thread 6 +1663000: cap 1: creating spark thread 6 +1663000: cap 1: thread 6 is runnable +1664000: cap 1: running thread 6 +1665000: cap 2: stealing a spark from cap 3 +1667000: cap 0: stealing a spark from cap 3 +1669000: cap 1: stealing a spark from cap 3 +1675000: cap 2: stopping thread 4 (thread yielding) +1675000: cap 2: thread 4 is runnable +1676000: cap 2: running thread 4 +1681000: cap 0: stopping thread 5 (thread yielding) +1681000: cap 0: thread 5 is runnable +1681000: cap 0: running thread 5 +1681000: cap 1: stopping thread 6 (thread yielding) +1681000: cap 1: thread 6 is runnable +1681000: cap 1: running thread 6 +1692000: cap 2: stopping thread 4 (stack overflow) +1694000: cap 2: running thread 4 +1699000: cap 0: stopping thread 5 (stack overflow) +1700000: cap 1: stopping thread 6 (stack overflow) +1705000: cap 0: running thread 5 +1705000: cap 1: running thread 6 +1949000: cap 3: stopping thread 3 (heap overflow) +1950000: cap 3: requesting parallel GC +1951000: cap 0: stopping thread 5 (thread yielding) +1951000: cap 0: thread 5 is runnable +1951000: cap 0: starting GC +1951000: cap 1: stopping thread 6 (thread yielding) +1951000: cap 1: thread 6 is runnable +1951000: cap 1: starting GC +1951000: cap 2: stopping thread 4 (thread yielding) +1951000: cap 2: thread 4 is runnable +1952000: cap 2: starting GC +1953000: cap 3: starting GC +1962000: cap 1: GC working +1963000: cap 2: GC working +1964000: cap 0: GC working +1969000: cap 3: GC working +1990000: cap 2: GC idle +1991000: cap 0: GC idle +1992000: cap 1: GC idle +1999000: cap 0: GC done +1999000: cap 1: GC done +1999000: cap 2: GC done +1999000: cap 3: GC idle +1999000: cap 3: GC done +2000000: cap 3: GC working +2000000: cap 3: GC idle +2000000: cap 3: GC done +2000000: cap 3: GC working +2001000: cap 3: GC idle +2001000: cap 3: GC done +2002000: cap 3: GC working +2002000: cap 3: GC idle +2002000: cap 3: GC done +2013000: cap 3: finished GC +2014000: cap 0: finished GC +2014000: cap 0: running thread 5 +2014000: cap 1: finished GC +2014000: cap 2: finished GC +2014000: cap 3: running thread 3 +2015000: cap 1: running thread 6 +2015000: cap 2: running thread 4 +2017000: cap 0: stopping thread 5 (thread yielding) +2018000: cap 0: thread 5 is runnable +2018000: cap 0: running thread 5 +2018000: cap 2: stopping thread 4 (thread yielding) +2018000: cap 2: thread 4 is runnable +2019000: cap 1: stopping thread 6 (thread yielding) +2019000: cap 1: thread 6 is runnable +2019000: cap 2: running thread 4 +2019000: cap 3: stopping thread 3 (thread yielding) +2019000: cap 3: thread 3 is runnable +2019000: cap 3: running thread 3 +2020000: cap 1: running thread 6 +2307000: cap 3: stopping thread 3 (heap overflow) +2307000: cap 3: requesting parallel GC +2308000: cap 1: stopping thread 6 (thread yielding) +2309000: cap 1: thread 6 is runnable +2309000: cap 1: starting GC +2310000: cap 0: stopping thread 5 (thread yielding) +2310000: cap 2: stopping thread 4 (thread yielding) +2310000: cap 2: thread 4 is runnable +2310000: cap 2: starting GC +2311000: cap 0: thread 5 is runnable +2311000: cap 0: starting GC +2311000: cap 3: starting GC +2319000: cap 1: GC working +2320000: cap 2: GC working +2323000: cap 0: GC working +2327000: cap 3: GC working +2333000: cap 2: GC idle +2334000: cap 0: GC idle +2335000: cap 3: GC idle +2336000: cap 0: GC done +2336000: cap 1: GC idle +2336000: cap 1: GC done +2336000: cap 2: GC done +2336000: cap 3: GC done +2337000: cap 3: GC working +2337000: cap 3: GC idle +2337000: cap 3: GC done +2337000: cap 3: GC working +2337000: cap 3: GC idle +2337000: cap 3: GC done +2338000: cap 3: GC working +2338000: cap 3: GC idle +2338000: cap 3: GC done +2351000: cap 3: finished GC +2352000: cap 0: finished GC +2352000: cap 0: running thread 5 +2352000: cap 1: finished GC +2352000: cap 2: finished GC +2353000: cap 1: running thread 6 +2353000: cap 2: running thread 4 +2353000: cap 3: running thread 3 +2356000: cap 0: stopping thread 5 (thread yielding) +2356000: cap 0: thread 5 is runnable +2356000: cap 1: stopping thread 6 (thread yielding) +2356000: cap 1: thread 6 is runnable +2356000: cap 2: stopping thread 4 (thread yielding) +2356000: cap 2: thread 4 is runnable +2357000: cap 0: running thread 5 +2357000: cap 1: running thread 6 +2357000: cap 2: running thread 4 +2357000: cap 3: stopping thread 3 (thread yielding) +2357000: cap 3: thread 3 is runnable +2357000: cap 3: running thread 3 +2451000: cap 2: stopping thread 4 (thread yielding) +2451000: cap 2: thread 4 is runnable +2452000: cap 3: stopping thread 3 (thread blocked) +2452000: cap 3: creating thread 7 +2453000: cap 2: running thread 4 +2453000: cap 3: creating spark thread 7 +2453000: cap 3: thread 7 is runnable +2463000: cap 3: running thread 7 +2465000: cap 3: running a local spark +2480000: cap 3: stopping thread 7 (stack overflow) +2481000: cap 3: running thread 7 +2749000: cap 2: stopping thread 4 (heap overflow) +2750000: cap 2: requesting parallel GC +2751000: cap 1: stopping thread 6 (thread yielding) +2751000: cap 3: stopping thread 7 (thread yielding) +2752000: cap 1: thread 6 is runnable +2752000: cap 1: starting GC +2752000: cap 3: thread 7 is runnable +2752000: cap 3: starting GC +6061000: cap 0: stopping thread 5 (thread yielding) +6062000: cap 0: thread 5 is runnable +6062000: cap 0: starting GC +6063000: cap 2: starting GC +6074000: cap 1: GC working +6075000: cap 0: GC working +6075000: cap 2: GC working +6076000: cap 3: GC working +6079000: cap 2: GC idle +6082000: cap 1: GC idle +6084000: cap 0: GC idle +6090000: cap 0: GC done +6090000: cap 1: GC done +6090000: cap 2: GC done +6090000: cap 3: GC idle +6090000: cap 3: GC done +6091000: cap 2: GC working +6091000: cap 2: GC idle +6091000: cap 2: GC done +6091000: cap 2: GC working +6091000: cap 2: GC idle +6091000: cap 2: GC done +6092000: cap 2: GC working +6092000: cap 2: GC idle +6092000: cap 2: GC done +6107000: cap 0: finished GC +6107000: cap 2: finished GC +6108000: cap 0: running thread 5 +6108000: cap 1: finished GC +6108000: cap 1: running thread 6 +6108000: cap 2: running thread 4 +6108000: cap 3: finished GC +6109000: cap 3: running thread 7 +6113000: cap 1: stopping thread 6 (thread yielding) +6113000: cap 1: thread 6 is runnable +6114000: cap 1: running thread 6 +6114000: cap 2: stopping thread 4 (thread yielding) +6115000: cap 0: stopping thread 5 (thread yielding) +6115000: cap 2: thread 4 is runnable +6115000: cap 2: running thread 4 +6115000: cap 3: stopping thread 7 (thread yielding) +6115000: cap 3: thread 7 is runnable +6116000: cap 0: thread 5 is runnable +6116000: cap 0: running thread 5 +6116000: cap 3: running thread 7 +6403000: cap 2: stopping thread 4 (heap overflow) +6403000: cap 2: requesting parallel GC +6404000: cap 0: stopping thread 5 (thread yielding) +6404000: cap 0: thread 5 is runnable +6404000: cap 1: stopping thread 6 (heap overflow) +6404000: cap 1: thread 6 is runnable +6404000: cap 3: stopping thread 7 (thread yielding) +6405000: cap 0: starting GC +6405000: cap 1: starting GC +6405000: cap 3: thread 7 is runnable +6405000: cap 3: starting GC +6406000: cap 2: starting GC +6414000: cap 3: GC working +6415000: cap 0: GC working +6415000: cap 1: GC working +6417000: cap 2: GC working +6420000: cap 1: GC idle +6421000: cap 0: GC idle +6422000: cap 2: GC idle +6425000: cap 0: GC done +6425000: cap 1: GC done +6425000: cap 2: GC done +6425000: cap 3: GC idle +6425000: cap 3: GC done +6426000: cap 2: GC working +6426000: cap 2: GC idle +6426000: cap 2: GC done +6426000: cap 2: GC working +6426000: cap 2: GC idle +6427000: cap 2: GC done +6427000: cap 2: GC working +6427000: cap 2: GC idle +6427000: cap 2: GC done +6440000: cap 0: finished GC +6440000: cap 2: finished GC +6441000: cap 0: running thread 5 +6441000: cap 1: finished GC +6441000: cap 1: running thread 6 +6441000: cap 2: running thread 4 +6441000: cap 3: finished GC +6442000: cap 3: running thread 7 +6445000: cap 0: stopping thread 5 (thread yielding) +6445000: cap 0: thread 5 is runnable +6445000: cap 1: stopping thread 6 (thread yielding) +6445000: cap 3: stopping thread 7 (thread yielding) +6445000: cap 3: thread 7 is runnable +6445000: cap 3: running thread 7 +6446000: cap 0: running thread 5 +6446000: cap 1: thread 6 is runnable +6446000: cap 1: running thread 6 +6446000: cap 2: stopping thread 4 (thread yielding) +6446000: cap 2: thread 4 is runnable +6446000: cap 2: running thread 4 +6648000: cap 1: stealing a spark from cap 0 +6653000: cap 0: stopping thread 5 (thread blocked) +6653000: cap 0: creating thread 8 +6653000: cap 1: stopping thread 6 (thread yielding) +6653000: cap 1: thread 6 is runnable +6654000: cap 0: creating spark thread 8 +6654000: cap 0: thread 8 is runnable +6654000: cap 0: running thread 8 +6655000: cap 0: running a local spark +6655000: cap 1: running thread 6 +6656000: cap 2: waking up thread 3 on cap 3 +6658000: cap 2: stealing a spark from cap 1 +6658000: cap 3: stopping thread 7 (thread yielding) +6658000: cap 3: thread 7 is runnable +6659000: cap 3: waking up thread 3 on cap 3 +6659000: cap 3: thread 3 is runnable +6660000: cap 3: running thread 7 +6727000: cap 2: stopping thread 4 (heap overflow) +6728000: cap 1: stopping thread 6 (thread yielding) +6728000: cap 2: requesting parallel GC +6729000: cap 0: stopping thread 8 (thread yielding) +6729000: cap 0: thread 8 is runnable +6729000: cap 0: starting GC +6729000: cap 1: thread 6 is runnable +6729000: cap 1: starting GC +6729000: cap 3: stopping thread 7 (thread yielding) +6729000: cap 3: thread 7 is runnable +6730000: cap 2: starting GC +6730000: cap 3: starting GC +6737000: cap 0: GC working +6737000: cap 2: GC working +6738000: cap 1: GC working +6739000: cap 3: GC working +6741000: cap 2: GC idle +6744000: cap 1: GC idle +6747000: cap 3: GC idle +6748000: cap 0: GC idle +6748000: cap 1: GC done +6748000: cap 2: GC done +6749000: cap 0: GC done +6749000: cap 2: GC working +6749000: cap 2: GC idle +6749000: cap 2: GC done +6749000: cap 3: GC done +6750000: cap 2: GC working +6750000: cap 2: GC idle +6750000: cap 2: GC done +6750000: cap 2: GC working +6750000: cap 2: GC idle +6750000: cap 2: GC done +6764000: cap 0: finished GC +6764000: cap 0: running thread 8 +6764000: cap 1: finished GC +6764000: cap 2: finished GC +6765000: cap 1: running thread 6 +6765000: cap 2: running thread 4 +6765000: cap 3: finished GC +6768000: cap 1: stopping thread 6 (thread yielding) +6769000: cap 0: stopping thread 8 (thread yielding) +6769000: cap 0: thread 8 is runnable +6769000: cap 1: thread 6 is runnable +6769000: cap 1: running thread 6 +6769000: cap 2: stopping thread 4 (thread yielding) +6769000: cap 2: thread 4 is runnable +6770000: cap 2: running thread 4 +6777000: cap 3: running thread 3 +6780000: cap 3: stopping thread 3 (thread blocked) +6782000: cap 1: stopping thread 6 (thread blocked) +6782000: cap 2: stopping thread 4 (thread yielding) +6782000: cap 2: thread 4 is runnable +6784000: cap 1: creating thread 9 +6784000: cap 1: creating spark thread 9 +6784000: cap 2: running thread 4 +6785000: cap 1: thread 9 is runnable +6785000: cap 1: running thread 9 +6786000: cap 1: stealing a spark from cap 0 +6790000: cap 3: running thread 7 +6791000: cap 0: running thread 8 +6794000: cap 3: stopping thread 7 (thread yielding) +6794000: cap 3: thread 7 is runnable +6795000: cap 0: stopping thread 8 (thread yielding) +6795000: cap 0: thread 8 is runnable +6795000: cap 3: running thread 7 +6796000: cap 0: running thread 8 +6802000: cap 2: waking up thread 6 on cap 1 +6803000: cap 2: stealing a spark from cap 0 +6804000: cap 1: stopping thread 9 (thread yielding) +6804000: cap 1: thread 9 is runnable +6805000: cap 1: waking up thread 6 on cap 1 +6805000: cap 1: thread 6 is runnable +6805000: cap 1: running thread 9 +6818000: cap 1: stopping thread 9 (thread finished) +6819000: cap 1: running thread 6 +6819000: cap 1: waking up thread 5 on cap 0 +6820000: cap 0: stopping thread 8 (thread yielding) +6820000: cap 1: stealing a spark from cap 3 +6821000: cap 0: thread 8 is runnable +6821000: cap 0: waking up thread 5 on cap 0 +6821000: cap 0: thread 5 is runnable +6821000: cap 0: running thread 8 +6828000: cap 0: stopping thread 8 (thread blocked) +6828000: cap 0: running thread 5 +6828000: cap 2: stopping thread 4 (thread yielding) +6829000: cap 2: thread 4 is runnable +6829000: cap 2: running thread 4 +6830000: cap 0: stopping thread 5 (thread blocked) +6831000: cap 0: creating thread 10 +6831000: cap 0: creating spark thread 10 +6831000: cap 0: thread 10 is runnable +6831000: cap 0: running thread 10 +6832000: cap 0: stealing a spark from cap 1 +6857000: cap 2: waking up thread 8 on cap 0 +6857000: cap 2: stealing a spark from cap 0 +6858000: cap 0: stopping thread 10 (thread yielding) +6858000: cap 0: thread 10 is runnable +6858000: cap 0: waking up thread 8 on cap 0 +6859000: cap 0: thread 8 is runnable +6859000: cap 0: running thread 10 +6940000: cap 0: stopping thread 10 (thread blocked) +6940000: cap 0: running thread 8 +6940000: cap 2: stopping thread 4 (thread yielding) +6941000: cap 0: waking up thread 5 on cap 0 +6941000: cap 0: thread 5 is runnable +6941000: cap 0: stopping thread 8 (thread finished) +6941000: cap 0: running thread 5 +6941000: cap 2: thread 4 is runnable +6941000: cap 2: running thread 4 +6942000: cap 0: waking up thread 3 on cap 3 +6942000: cap 0: stealing a spark from cap 1 +6943000: cap 3: stopping thread 7 (thread yielding) +6943000: cap 3: thread 7 is runnable +6944000: cap 2: waking up thread 10 on cap 0 +6944000: cap 3: waking up thread 3 on cap 3 +6944000: cap 3: thread 3 is runnable +6944000: cap 3: running thread 7 +6945000: cap 0: stopping thread 5 (thread yielding) +6945000: cap 0: thread 5 is runnable +6945000: cap 2: stealing a spark from cap 0 +6946000: cap 0: waking up thread 10 on cap 0 +6946000: cap 0: thread 10 is runnable +6946000: cap 0: running thread 5 +6949000: cap 0: stopping thread 5 (thread blocked) +6949000: cap 0: running thread 10 +6950000: cap 0: running a local spark +6950000: cap 2: stopping thread 4 (thread yielding) +6950000: cap 2: thread 4 is runnable +6950000: cap 2: running thread 4 +6974000: cap 0: stopping thread 10 (thread yielding) +6974000: cap 1: stopping thread 6 (thread blocked) +6975000: cap 0: thread 10 is runnable +6975000: cap 0: running thread 10 +6975000: cap 1: creating thread 11 +6975000: cap 1: creating spark thread 11 +6976000: cap 1: thread 11 is runnable +6976000: cap 1: running thread 11 +6977000: cap 1: running a local spark +7019000: cap 0: running a local spark +7046000: cap 2: waking up thread 5 on cap 0 +7047000: cap 0: stopping thread 10 (thread yielding) +7047000: cap 0: thread 10 is runnable +7047000: cap 0: waking up thread 5 on cap 0 +7047000: cap 0: thread 5 is runnable +7047000: cap 2: stealing a spark from cap 1 +7048000: cap 0: running thread 10 +7066000: cap 2: stopping thread 4 (heap overflow) +7066000: cap 2: requesting parallel GC +7067000: cap 1: stopping thread 11 (thread yielding) +7068000: cap 1: thread 11 is runnable +7068000: cap 1: starting GC +7068000: cap 3: stopping thread 7 (thread yielding) +7068000: cap 3: thread 7 is runnable +7068000: cap 3: starting GC +7069000: cap 0: stopping thread 10 (thread yielding) +7069000: cap 0: thread 10 is runnable +7070000: cap 0: starting GC +7070000: cap 2: starting GC +7078000: cap 0: GC working +7078000: cap 2: GC working +7083000: cap 2: GC idle +7090000: cap 0: GC idle +7111000: cap 1: GC working +7121000: cap 1: GC idle +7141000: cap 3: GC working +7150000: cap 0: GC done +7150000: cap 1: GC done +7150000: cap 2: GC done +7150000: cap 3: GC idle +7150000: cap 3: GC done +7151000: cap 2: GC working +7151000: cap 2: GC idle +7151000: cap 2: GC done +7151000: cap 2: GC working +7152000: cap 2: GC idle +7152000: cap 2: GC done +7152000: cap 2: GC working +7152000: cap 2: GC idle +7152000: cap 2: GC done +7166000: cap 2: finished GC +7167000: cap 0: finished GC +7167000: cap 0: running thread 5 +7167000: cap 1: finished GC +7168000: cap 1: running thread 11 +7168000: cap 2: running thread 4 +7168000: cap 3: finished GC +7169000: cap 0: stopping thread 5 (thread blocked) +7170000: cap 0: running thread 10 +7172000: cap 1: stopping thread 11 (thread yielding) +7172000: cap 1: thread 11 is runnable +7172000: cap 2: stopping thread 4 (thread yielding) +7172000: cap 2: thread 4 is runnable +7174000: cap 0: stopping thread 10 (thread yielding) +7174000: cap 0: thread 10 is runnable +7174000: cap 0: running thread 10 +7174000: cap 2: running thread 4 +7175000: cap 1: running thread 11 +7228000: cap 0: waking up thread 5 on cap 0 +7228000: cap 0: thread 5 is runnable +7228000: cap 0: stopping thread 10 (thread finished) +7228000: cap 0: running thread 5 +7229000: cap 0: waking up thread 6 on cap 1 +7230000: cap 0: stealing a spark from cap 1 +7231000: cap 1: stopping thread 11 (thread yielding) +7231000: cap 1: thread 11 is runnable +7231000: cap 1: waking up thread 6 on cap 1 +7232000: cap 1: thread 6 is runnable +7232000: cap 1: running thread 11 +7249000: cap 1: stopping thread 11 (thread blocked) +7249000: cap 1: running thread 6 +7250000: cap 0: stopping thread 5 (thread yielding) +7250000: cap 0: thread 5 is runnable +7251000: cap 0: running thread 5 +7253000: cap 1: stopping thread 6 (thread blocked) +7254000: cap 1: creating thread 12 +7254000: cap 1: creating spark thread 12 +7254000: cap 1: thread 12 is runnable +7254000: cap 1: running thread 12 +7255000: cap 1: stealing a spark from cap 2 +7294000: cap 1: stopping thread 12 (thread yielding) +7294000: cap 2: stopping thread 4 (thread blocked) +7295000: cap 1: thread 12 is runnable +7295000: cap 1: running thread 12 +7295000: cap 2: creating thread 13 +7295000: cap 2: creating spark thread 13 +7295000: cap 2: thread 13 is runnable +7296000: cap 2: running thread 13 +7297000: cap 2: running a local spark +7300000: cap 0: waking up thread 11 on cap 1 +7301000: cap 0: stealing a spark from cap 3 +7301000: cap 1: stopping thread 12 (thread yielding) +7301000: cap 1: thread 12 is runnable +7302000: cap 1: waking up thread 11 on cap 1 +7302000: cap 1: thread 11 is runnable +7303000: cap 1: running thread 12 +7341000: cap 1: waking up thread 4 on cap 2 +7342000: cap 1: stopping thread 12 (thread finished) +7342000: cap 1: running thread 11 +7342000: cap 2: stopping thread 13 (thread yielding) +7342000: cap 2: thread 13 is runnable +7343000: cap 1: waking up thread 6 on cap 1 +7343000: cap 2: waking up thread 4 on cap 2 +7343000: cap 2: thread 4 is runnable +7344000: cap 1: thread 6 is runnable +7344000: cap 1: stopping thread 11 (thread finished) +7344000: cap 1: running thread 6 +7344000: cap 2: running thread 13 +7346000: cap 1: stopping thread 6 (thread blocked) +7346000: cap 1: creating thread 14 +7346000: cap 2: stopping thread 13 (thread yielding) +7346000: cap 2: thread 13 is runnable +7347000: cap 1: creating spark thread 14 +7347000: cap 1: thread 14 is runnable +7347000: cap 1: running thread 14 +7347000: cap 2: running thread 4 +7347000: cap 2: stopping thread 4 (thread blocked) +7348000: cap 1: stealing a spark from cap 0 +7348000: cap 2: running thread 13 +7349000: cap 2: waking up thread 4 on cap 2 +7349000: cap 2: thread 4 is runnable +7349000: cap 2: stopping thread 13 (thread finished) +7350000: cap 2: running thread 4 +7350000: cap 2: waking up thread 6 on cap 1 +7350000: cap 2: stealing a spark from cap 0 +7351000: cap 1: stopping thread 14 (thread yielding) +7351000: cap 1: thread 14 is runnable +7351000: cap 1: waking up thread 6 on cap 1 +7352000: cap 1: thread 6 is runnable +7353000: cap 1: running thread 14 +7468000: cap 2: stopping thread 4 (heap overflow) +7468000: cap 2: requesting parallel GC +7469000: cap 1: stopping thread 14 (thread yielding) +7469000: cap 1: thread 14 is runnable +7471000: cap 1: starting GC +7472000: cap 0: stopping thread 5 (thread yielding) +7472000: cap 0: thread 5 is runnable +7473000: cap 0: starting GC +7502000: cap 3: starting GC +7503000: cap 2: starting GC +7510000: cap 1: GC working +7514000: cap 2: GC working +7518000: cap 2: GC idle +7518000: cap 3: GC working +7523000: cap 3: GC idle +7524000: cap 1: GC idle +8359000: cap 0: GC working +8368000: cap 0: GC idle +8368000: cap 0: GC done +8368000: cap 1: GC done +8368000: cap 2: GC done +8368000: cap 3: GC done +8369000: cap 2: GC working +8369000: cap 2: GC idle +8369000: cap 2: GC done +8369000: cap 2: GC working +8369000: cap 2: GC idle +8369000: cap 2: GC done +8370000: cap 2: GC working +8370000: cap 2: GC idle +8370000: cap 2: GC done +8383000: cap 0: finished GC +8383000: cap 2: finished GC +8384000: cap 0: running thread 5 +8384000: cap 1: finished GC +8384000: cap 1: running thread 6 +8384000: cap 2: running thread 4 +8384000: cap 3: finished GC +8384000: cap 3: running thread 3 +8385000: cap 1: stopping thread 6 (thread finished) +8386000: cap 1: running thread 14 +8389000: cap 2: stopping thread 4 (thread yielding) +8389000: cap 2: thread 4 is runnable +8389000: cap 2: running thread 4 +8389000: cap 3: stopping thread 3 (thread blocked) +8390000: cap 1: stopping thread 14 (thread yielding) +8390000: cap 1: thread 14 is runnable +8393000: cap 0: stopping thread 5 (thread yielding) +8393000: cap 0: thread 5 is runnable +8400000: cap 3: running thread 7 +8403000: cap 3: stopping thread 7 (thread yielding) +8403000: cap 3: thread 7 is runnable +8403000: cap 3: running thread 7 +8404000: cap 1: running thread 14 +8465000: cap 2: stealing a spark from cap 0 +8504000: cap 1: stealing a spark from cap 0 +8623000: cap 3: waking up thread 3 on cap 3 +8623000: cap 3: thread 3 is runnable +8623000: cap 3: stopping thread 7 (thread finished) +8634000: cap 0: running thread 5 +8635000: cap 3: running thread 3 +8640000: cap 0: stopping thread 5 (thread yielding) +8640000: cap 0: thread 5 is runnable +8640000: cap 3: stopping thread 3 (thread blocked) +8641000: cap 3: creating thread 15 +8641000: cap 3: creating spark thread 15 +8641000: cap 3: thread 15 is runnable +8649000: cap 3: running thread 15 +8650000: cap 3: running a local spark +8661000: cap 3: stopping thread 15 (stack overflow) +8663000: cap 3: running thread 15 +8670000: cap 2: stopping thread 4 (heap overflow) +8670000: cap 2: requesting parallel GC +8671000: cap 1: stopping thread 14 (thread yielding) +8671000: cap 1: thread 14 is runnable +8671000: cap 3: stopping thread 15 (thread yielding) +8671000: cap 3: thread 15 is runnable +8671000: cap 3: starting GC +8672000: cap 1: starting GC +13162000: cap 0: starting GC +13162000: cap 2: starting GC +13170000: cap 1: GC working +13171000: cap 0: GC working +13172000: cap 2: GC working +13177000: cap 1: GC idle +13178000: cap 0: GC idle +13178000: cap 2: GC idle +13186000: cap 3: GC working +13204000: cap 1: GC done +13204000: cap 2: GC done +13204000: cap 3: GC idle +13204000: cap 3: GC done +13205000: cap 2: GC working +13205000: cap 2: GC idle +13205000: cap 2: GC done +13205000: cap 2: GC working +13205000: cap 2: GC idle +13205000: cap 2: GC done +13206000: cap 2: GC working +13206000: cap 2: GC idle +13206000: cap 2: GC done +13229000: cap 0: GC done +13244000: cap 0: finished GC +13244000: cap 2: finished GC +13245000: cap 0: running thread 5 +13245000: cap 1: finished GC +13245000: cap 1: running thread 14 +13245000: cap 2: running thread 4 +13249000: cap 1: stopping thread 14 (thread yielding) +13249000: cap 1: thread 14 is runnable +13249000: cap 2: stopping thread 4 (thread yielding) +13249000: cap 2: thread 4 is runnable +13249000: cap 2: running thread 4 +13250000: cap 0: stopping thread 5 (thread yielding) +13250000: cap 0: thread 5 is runnable +13250000: cap 1: running thread 14 +13251000: cap 0: running thread 5 +13292000: cap 2: stealing a spark from cap 0 +13294000: cap 1: stealing a spark from cap 3 +13312000: cap 0: stopping thread 5 (thread blocked) +13312000: cap 2: stopping thread 4 (thread yielding) +13312000: cap 2: thread 4 is runnable +13313000: cap 0: creating thread 16 +13313000: cap 0: creating spark thread 16 +13313000: cap 0: thread 16 is runnable +13314000: cap 0: running thread 16 +13314000: cap 0: stealing a spark from cap 1 +13314000: cap 2: running thread 4 +13340000: cap 2: waking up thread 5 on cap 0 +13341000: cap 0: stopping thread 16 (thread yielding) +13341000: cap 0: thread 16 is runnable +13341000: cap 2: stealing a spark from cap 1 +13342000: cap 0: waking up thread 5 on cap 0 +13342000: cap 0: thread 5 is runnable +13342000: cap 0: running thread 16 +13364000: cap 0: stopping thread 16 (thread yielding) +13364000: cap 0: thread 16 is runnable +13364000: cap 0: running thread 16 +13364000: cap 1: stopping thread 14 (thread blocked) +13365000: cap 1: creating thread 17 +13365000: cap 1: creating spark thread 17 +13365000: cap 1: thread 17 is runnable +13365000: cap 1: running thread 17 +13365000: cap 1: stealing a spark from cap 3 +13375000: cap 2: stealing a spark from cap 1 +13423000: cap 2: stealing a spark from cap 1 +13428000: cap 0: waking up thread 14 on cap 1 +13429000: cap 0: stopping thread 16 (thread finished) +13429000: cap 0: running thread 5 +13430000: cap 1: stopping thread 17 (thread yielding) +13430000: cap 1: thread 17 is runnable +13431000: cap 1: waking up thread 14 on cap 1 +13431000: cap 1: thread 14 is runnable +13431000: cap 1: running thread 17 +13432000: cap 0: waking up thread 3 on cap 3 +13433000: cap 0: stealing a spark from cap 3 +13442000: cap 1: stopping thread 17 (thread blocked) +13442000: cap 1: running thread 14 +13442000: cap 2: stopping thread 4 (thread yielding) +13442000: cap 2: thread 4 is runnable +13443000: cap 1: stealing a spark from cap 0 +13443000: cap 2: running thread 4 +13453000: cap 2: waking up thread 17 on cap 1 +13454000: cap 2: stealing a spark from cap 0 +13455000: cap 1: stopping thread 14 (thread yielding) +13455000: cap 1: thread 14 is runnable +13456000: cap 1: waking up thread 17 on cap 1 +13456000: cap 1: thread 17 is runnable +13456000: cap 1: running thread 14 +13476000: cap 1: stopping thread 14 (thread finished) +13476000: cap 1: running thread 17 +13476000: cap 1: stealing a spark from cap 3 +13505000: cap 2: stealing a spark from cap 1 +13539000: cap 2: stopping thread 4 (heap overflow) +13539000: cap 2: requesting parallel GC +13541000: cap 0: stopping thread 5 (thread yielding) +13541000: cap 0: thread 5 is runnable +13541000: cap 0: starting GC +13541000: cap 1: stopping thread 17 (thread yielding) +13541000: cap 1: thread 17 is runnable +13541000: cap 1: starting GC +13578000: cap 3: finished GC +13578000: cap 3: starting GC +13579000: cap 2: starting GC +13585000: cap 1: GC working +13591000: cap 2: GC working +13593000: cap 3: GC working +13595000: cap 2: GC idle +13596000: cap 1: GC idle +13603000: cap 3: GC idle +13880000: cap 0: GC working +13885000: cap 0: GC idle +13885000: cap 0: GC done +13885000: cap 2: GC done +13886000: cap 1: GC done +13886000: cap 2: GC working +13886000: cap 2: GC idle +13886000: cap 2: GC done +13886000: cap 2: GC working +13886000: cap 2: GC idle +13886000: cap 2: GC done +13887000: cap 2: GC working +13887000: cap 2: GC idle +13887000: cap 2: GC done +13911000: cap 3: GC done +13924000: cap 2: finished GC +13925000: cap 1: finished GC +13925000: cap 1: running thread 17 +13925000: cap 2: running thread 4 +13925000: cap 3: finished GC +13926000: cap 3: running thread 15 +13928000: cap 1: stopping thread 17 (thread yielding) +13928000: cap 2: stopping thread 4 (thread yielding) +13929000: cap 1: thread 17 is runnable +13929000: cap 1: running thread 17 +13929000: cap 2: thread 4 is runnable +13929000: cap 2: running thread 4 +13931000: cap 3: stopping thread 15 (thread yielding) +13931000: cap 3: thread 15 is runnable +13931000: cap 3: waking up thread 3 on cap 3 +13931000: cap 3: thread 3 is runnable +13932000: cap 3: running thread 15 +13941000: cap 2: stealing a spark from cap 1 +13944000: cap 1: stopping thread 17 (thread blocked) +13944000: cap 2: stopping thread 4 (thread yielding) +13945000: cap 1: creating thread 18 +13945000: cap 1: creating spark thread 18 +13945000: cap 1: thread 18 is runnable +13945000: cap 1: running thread 18 +13945000: cap 2: thread 4 is runnable +13946000: cap 1: stealing a spark from cap 3 +13946000: cap 2: running thread 4 +13990000: cap 2: waking up thread 17 on cap 1 +13991000: cap 2: stealing a spark from cap 1 +13992000: cap 1: stopping thread 18 (thread yielding) +13992000: cap 1: thread 18 is runnable +13992000: cap 1: waking up thread 17 on cap 1 +13992000: cap 1: thread 17 is runnable +13993000: cap 1: running thread 18 +14018000: cap 1: stopping thread 18 (thread blocked) +14018000: cap 1: running thread 17 +14018000: cap 1: running a local spark +14019000: cap 2: stopping thread 4 (thread yielding) +14019000: cap 2: thread 4 is runnable +14020000: cap 2: running thread 4 +14029000: cap 2: waking up thread 18 on cap 1 +14030000: cap 1: stopping thread 17 (thread yielding) +14030000: cap 1: thread 17 is runnable +14030000: cap 1: waking up thread 18 on cap 1 +14030000: cap 2: stealing a spark from cap 3 +14031000: cap 1: thread 18 is runnable +14031000: cap 1: running thread 17 +14035000: cap 3: stopping thread 15 (thread blocked) +14036000: cap 2: stopping thread 4 (thread yielding) +14036000: cap 2: thread 4 is runnable +14036000: cap 2: running thread 4 +14042000: cap 0: finished GC +14042000: cap 0: running thread 5 +14042000: cap 3: running thread 3 +14045000: cap 3: stopping thread 3 (thread blocked) +14047000: cap 0: stopping thread 5 (thread yielding) +14047000: cap 0: thread 5 is runnable +14048000: cap 0: running thread 5 +14052000: cap 0: stopping thread 5 (thread finished) +14057000: cap 2: waking up thread 15 on cap 3 +14061000: cap 2: stopping thread 4 (thread finished) +14064000: cap 3: waking up thread 15 on cap 3 +14065000: cap 3: thread 15 is runnable +14065000: cap 3: running thread 15 +14068000: cap 1: stopping thread 17 (thread yielding) +14068000: cap 1: thread 17 is runnable +14068000: cap 3: stopping thread 15 (thread blocked) +14070000: cap 0: thread 17 is runnable +14070000: cap 1: migrating thread 17 to cap 0 +14075000: cap 0: running thread 17 +14078000: cap 1: running thread 18 +14079000: cap 1: stopping thread 18 (thread blocked) +14080000: cap 0: stopping thread 17 (thread yielding) +14080000: cap 0: thread 17 is runnable +14081000: cap 0: running thread 17 +14094000: cap 0: waking up thread 18 on cap 1 +14096000: cap 0: stopping thread 17 (thread finished) +14098000: cap 1: waking up thread 18 on cap 1 +14098000: cap 1: thread 18 is runnable +14099000: cap 1: running thread 18 +14099000: cap 1: waking up thread 15 on cap 3 +14102000: cap 1: stopping thread 18 (thread finished) +14103000: cap 3: waking up thread 15 on cap 3 +14103000: cap 3: thread 15 is runnable +14103000: cap 3: running thread 15 +14103000: cap 3: waking up thread 3 on cap 3 +14104000: cap 3: thread 3 is runnable +14104000: cap 3: stopping thread 15 (thread finished) +14110000: cap 3: running thread 3 +14146000: cap 3: stopping thread 3 (making a foreign call) +14147000: cap 3: running thread 3 +14147000: cap 3: stopping thread 3 (making a foreign call) +14157000: cap 3: running thread 3 +14191000: cap 3: stopping thread 3 (thread finished) +14204000: cap 3: requesting sequential GC +14206000: cap 3: starting GC +14229000: cap 0: GC working +14242000: cap 0: GC idle +14242000: cap 0: GC done +14243000: cap 0: GC working +14243000: cap 0: GC idle +14244000: cap 0: GC done +14244000: cap 0: GC working +14244000: cap 0: GC idle +14244000: cap 0: GC done +14244000: cap 0: GC working +14244000: cap 0: GC idle +14245000: cap 0: GC done +14254000: cap 3: finished GC +14261000: cap 0: running thread 2 +14306000: cap 0: stopping thread 2 (thread finished) +14344000: cap 0: shutting down +14345000: cap 1: shutting down +14346000: cap 2: shutting down +14346000: cap 3: shutting down From bda6ac3b0e073febaea4c0266b565150b29cc089 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Thu, 9 Mar 2017 05:10:22 +0900 Subject: [PATCH 07/17] Implement following mode in printEventsIncremental --- GhcEvents.hs | 7 ++----- src/GHC/RTS/Events/Incremental.hs | 16 +++++++++++----- 2 files changed, 13 insertions(+), 10 deletions(-) diff --git a/GhcEvents.hs b/GhcEvents.hs index 6102f61..a0129f9 100644 --- a/GhcEvents.hs +++ b/GhcEvents.hs @@ -23,12 +23,9 @@ main = getArgs >>= command command :: [String] -> IO () command ["--help"] = putStr usage -command ["inc", file] = Inc.printEventsIncremental file +command ["inc", file] = Inc.printEventsIncremental False file -command ["inc", "force", file] = do - h <- openBinaryFile file ReadMode - eh <- ehOpen h 1024 - printEventsIncremental eh True +command ["inc", "force", file] = Inc.printEventsIncremental True file command ["show", file] = do evtLog <- readLogOrDie file diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs index f8b1051..3d7d0b1 100644 --- a/src/GHC/RTS/Events/Incremental.hs +++ b/src/GHC/RTS/Events/Incremental.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE MultiWayIf #-} module GHC.RTS.Events.Incremental ( -- * Incremental API Decoder(..) @@ -18,6 +19,7 @@ module GHC.RTS.Events.Incremental , hPrintEventsIncremental ) where import Control.Applicative +import Control.Concurrent import Control.Monad import Data.Either import Data.Maybe @@ -138,11 +140,12 @@ readEventLog bytes = do readEventLogFromFile :: FilePath -> IO (Either String EventLog) readEventLogFromFile path = fmap fst . readEventLog <$> BL.readFile path -printEventsIncremental :: FilePath -> IO () -printEventsIncremental path = withFile path ReadMode hPrintEventsIncremental +printEventsIncremental :: Bool -> FilePath -> IO () +printEventsIncremental follow path = + withFile path ReadMode (hPrintEventsIncremental follow) -hPrintEventsIncremental :: Handle -> IO () -hPrintEventsIncremental hdl = go decodeEventLog +hPrintEventsIncremental :: Bool -> Handle -> IO () +hPrintEventsIncremental follow hdl = go decodeEventLog where go decoder = case decoder of Produce event decoder' -> do @@ -150,7 +153,10 @@ hPrintEventsIncremental hdl = go decodeEventLog go decoder' Consume k -> do chunk <- B.hGetSome hdl 4096 - unless (B.null chunk) $ go $ k chunk + if + | not (B.null chunk) -> go $ k chunk + | follow -> threadDelay 1000000 >> go decoder + | otherwise -> return () Done {} -> return () Error _ err -> fail err From 585bbcad3b1f6d2ee115fcf5edd43b3ee1f22b9f Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Thu, 9 Mar 2017 05:36:43 +0900 Subject: [PATCH 08/17] Move writeEventLogToFile and serialiseEventLog to Incremental --- src/GHC/RTS/Events/Incremental.hs | 63 +++++++++++++++++++++++++++++-- 1 file changed, 60 insertions(+), 3 deletions(-) diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs index 3d7d0b1..8264599 100644 --- a/src/GHC/RTS/Events/Incremental.hs +++ b/src/GHC/RTS/Events/Incremental.hs @@ -17,6 +17,10 @@ module GHC.RTS.Events.Incremental , readEventLogFromFile , printEventsIncremental , hPrintEventsIncremental + + -- * Serialisation + , writeEventLogToFile + , serialiseEventLog ) where import Control.Applicative import Control.Concurrent @@ -29,6 +33,7 @@ import System.IO import Prelude import qualified Data.Binary.Get as G +import qualified Data.Binary.Put as P import qualified Data.ByteString as B import qualified Data.ByteString.Builder as BB import qualified Data.ByteString.Lazy as BL @@ -88,9 +93,6 @@ decodeEvents header = go (0 :: Int) Nothing decoder0 Consume $ \chunk -> go remaining blockCap $ k $ Just chunk G.Fail leftover _ err -> Error leftover err - mkCap cap = do - guard $ fromIntegral cap /= (-1 :: Word16) - return cap decodeEventLog :: Decoder Event decodeEventLog = withHeader $ \header leftover -> @@ -209,3 +211,58 @@ mkEventDecoder header = G.runGetIncremental $ getEvent parsers , perfParsers ] parsers = EventParsers $ mkEventTypeParsers imap event_parsers + +-- | Writes the 'EventLog' to file. The log is expected to __NOT__ have 'EventBlock' +-- markers/events - the parsers no longer emit them and they are handled behind +-- the scenes. +writeEventLogToFile :: FilePath -> EventLog -> IO () +writeEventLogToFile fp = BL.writeFile fp . serialiseEventLog + +-- | Serialises an 'EventLog' back to a 'ByteString', usually for writing it +-- back to a file. +serialiseEventLog :: EventLog -> BL.ByteString +serialiseEventLog el@(EventLog _ (Data events)) = + P.runPut $ putEventLog blockedEl + where + eventsMap = capSplitEvents events + blockedEventsMap = IM.mapWithKey addBlockMarker eventsMap + blockedEl = el{dat = Data blockedEvents} + blockedEvents = IM.foldr (++) [] blockedEventsMap + +-- Gets the Capability of an event in numeric form +getIntCap :: Event -> Int +getIntCap Event{evCap = cap} = + case cap of + Just capNo -> capNo + Nothing -> -1 + +-- Creates an IntMap of the events with capability number as the key. +-- Key -1 indicates global (capless) event +capSplitEvents :: [Event] -> IM.IntMap [Event] +capSplitEvents evts = capSplitEvents' evts IM.empty + +capSplitEvents' :: [Event] -> IM.IntMap [Event] -> IM.IntMap [Event] +capSplitEvents' evts imap = + case evts of + (x:xs) -> capSplitEvents' xs (IM.insertWith (++) (getIntCap x) [x] imap) + [] -> imap + +-- Adds a block marker to the beginnng of a list of events, annotated with +-- its capability. All events are expected to belong to the same cap. +addBlockMarker :: Int -> [Event] -> [Event] +addBlockMarker cap evts = + (Event startTime (EventBlock endTime cap sz) (mkCap cap)) : sortedEvts + where + sz = fromIntegral . BL.length $ P.runPut $ mapM_ putEvent evts + startTime = case sortedEvts of + (x:_) -> evTime x + [] -> error "Cannot add block marker to an empty list of events" + sortedEvts = sortEvents evts + endTime = evTime $ last sortedEvts + +-- Checks if the capability is not -1 (which indicates a global eventblock), so +-- has no associated capability +mkCap :: Int -> Maybe Int +mkCap cap = do + guard $ fromIntegral cap /= (-1 :: Word16) + return cap From 2c39fc7b39cfa09f6f5dcbcbd0843bcf0ceee7fd Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Thu, 9 Mar 2017 05:41:04 +0900 Subject: [PATCH 09/17] Delete GHC.RTS.EventsIncremental --- GhcEvents.hs | 9 +- ghc-events.cabal | 1 - src/GHC/RTS/EventsIncremental.hs | 388 ------------------------------- 3 files changed, 4 insertions(+), 394 deletions(-) delete mode 100644 src/GHC/RTS/EventsIncremental.hs diff --git a/GhcEvents.hs b/GhcEvents.hs index a0129f9..4511741 100644 --- a/GhcEvents.hs +++ b/GhcEvents.hs @@ -3,8 +3,7 @@ module Main where import GHC.RTS.Events -import GHC.RTS.EventsIncremental -import qualified GHC.RTS.Events.Incremental as Inc +import GHC.RTS.Events.Incremental import GHC.RTS.Events.Merge import GHC.RTS.Events.Analysis import GHC.RTS.Events.Analysis.SparkThread @@ -23,9 +22,9 @@ main = getArgs >>= command command :: [String] -> IO () command ["--help"] = putStr usage -command ["inc", file] = Inc.printEventsIncremental False file +command ["inc", file] = printEventsIncremental False file -command ["inc", "force", file] = Inc.printEventsIncremental True file +command ["inc", "force", file] = printEventsIncremental True file command ["show", file] = do evtLog <- readLogOrDie file @@ -176,7 +175,7 @@ command _ = putStr usage >> die "Unrecognized command" readLogOrDie :: FilePath -> IO EventLog readLogOrDie file = do - e <- Inc.readEventLogFromFile file + e <- readEventLogFromFile file case e of Left s -> die ("Failed to parse " ++ file ++ ": " ++ s) Right evtLog -> return evtLog diff --git a/ghc-events.cabal b/ghc-events.cabal index 4df4740..be816e0 100644 --- a/ghc-events.cabal +++ b/ghc-events.cabal @@ -52,7 +52,6 @@ library bytestring >= 0.10.4, array >= 0.2 && < 0.6 exposed-modules: GHC.RTS.Events, - GHC.RTS.EventsIncremental GHC.RTS.Events.Incremental GHC.RTS.Events.Merge GHC.RTS.Events.Analysis diff --git a/src/GHC/RTS/EventsIncremental.hs b/src/GHC/RTS/EventsIncremental.hs deleted file mode 100644 index 7db07d0..0000000 --- a/src/GHC/RTS/EventsIncremental.hs +++ /dev/null @@ -1,388 +0,0 @@ -{-| -Module : GHC.RTS.EventsIncremental -Description : Incremental parser functions for GHC RTS EventLog framewrok -Maintainer : karolis.velicka@gmail.com - -This module contains functions used for parsing *.eventlog files emitted -by the GHC runtime sytem. --} -{-# LANGUAGE CPP #-} -{-# LANGUAGE OverloadedStrings #-} -{- --} - -module GHC.RTS.EventsIncremental ( - ParseResult(..), - - -- * ByteString interface - -- $bytestringapi - EventParserState, - newParserState, - pushBytes, readHeader, readEvent, - - -- * EventHandle interface - -- $eventhandleapi - EventHandle, - ehOpen, ehReadEvent, - -- * For compatibility with old clients - readEventLogFromFile, - writeEventLogToFile, - -- * Helper functions - serialiseEventLog, - readRemainingEvents, - printEventsIncremental, - - mkEventDecoder - ) where - -import GHC.RTS.Events -import GHC.RTS.EventParserUtils -import GHC.RTS.EventTypes hiding (time, spec) - -import Data.Binary.Get hiding (remaining) -import Data.Binary.Put -import qualified Data.ByteString as B -import qualified Data.ByteString.Builder as BB -import qualified Data.ByteString.Lazy as BL -import Control.Concurrent (threadDelay) -import qualified Data.IntMap.Strict as M -import Data.IORef (IORef, newIORef, readIORef, writeIORef) -import System.IO (Handle, hPutStrLn, stderr, stdout) -import Data.Monoid ((<>)) -import Data.Word (Word16, Word32) - - - -#define EVENTLOG_CONSTANTS_ONLY -#include "EventLogFormat.h" - --- | Keeps the currently pushed input and other necessary state for the parsing -data EventParserState = ParsingHeader (Decoder Header) - | ParsingEvents EventDecoder - --- | An abstraction over 'Handle' and 'EventParserState' for a simple incemental --- parsing interface. -data EventHandle = - EH { ehHandle :: Handle -- Handle to read from - , ehChunkSize :: Int -- Chunk size for incremental reading - , ehState :: IORef EventParserState -- state for the parser - } - -data EventDecoder = - ED { -- If in EventBlock, we track it's capability - edCap :: Maybe Int - -- Tracks the number of remaining bytes in an EventBlock - , edRemaining :: Word32 - -- The full parsed header that is used to create a new decoder once - -- edPartial returns an 'Item' - , edHeader :: Header - -- A decoder that keeps the currently unconsumed bytestring (and possibly) - -- the next event to be returned by readEvent - , edPartial :: Decoder (Maybe Event) - -- | Initial decoder cache. - -- - -- It is expensive to construct a new decoder from a header. We cache - -- it for later reuse. - , edInitial :: Decoder (Maybe Event) - } - --- | Datatype that describes the result of a parse. -data ParseResult a = - -- | Successfully parsed an item - Item a - -- | The log is not finished yet but the input did not contain any more - -- complete items - | Incomplete - -- | Parsing was completed successfully - | Complete - -- | An error in parsing has occurred, contains an error message that the - -- parser may provide - | ParseError String - --- $bytestringapi --- The 'ByteString' based API uses 'EventParserState' to hold input --- that it has received so far. This API takes input in form of 'B.ByteString's --- so it is up to the user to generate it. - --- | Creates a new, empty 'EventParserState' that is required to run the --- 'readEvent' function. -newParserState :: EventParserState -newParserState = ParsingHeader (getToDecoder getHeader) - --- Creates a new parser state for events --- ByteString is fed to the partial decoder -newParserState' :: Maybe Int -> Word32 -> Header - -> Decoder (Maybe Event) -> B.ByteString - -> EventParserState -newParserState' cap remaining header initial bss = - ParsingEvents ED { edCap = cap - , edRemaining = remaining - , edHeader = header - , edPartial = initial `pushChunk` bss - , edInitial = initial - } - --- | Pushes a 'ByteString' to 'EventParserState'. This function is the only --- supported way of providing input in the ByteString interface. --- 'pushBytes' expects its input to follow the structure of a .eventlog file. -pushBytes :: EventParserState -> B.ByteString -> EventParserState -pushBytes (ParsingHeader headerDecoder) bs = - ParsingHeader $ headerDecoder `pushChunk` bs -pushBytes (ParsingEvents ed) bs = - ParsingEvents $ ed { edPartial = (edPartial ed) `pushChunk` bs} - --- Reads the header and returns it as a result. Is only required for --- readEventLogFromFile functionality, so may be removed in a future version -parseHeader :: Decoder Header -> (ParseResult Event, EventParserState) -parseHeader (Done bs _ header) = - let emptyDecoder = mkEventDecoder header - newState = newParserState' Nothing 0 header emptyDecoder bs - in (Incomplete, newState) -parseHeader dec@(Partial {}) = (Incomplete, ParsingHeader dec) -parseHeader dec@(Fail _ _ errMsg) = (ParseError errMsg, ParsingHeader dec) - --- | Returns the 'Header' if 'EventParserState' was provided with enough input --- to parse the it already. -readHeader :: EventParserState -> Maybe Header -readHeader (ParsingHeader _ ) = Nothing -readHeader (ParsingEvents ed) = Just $ edHeader ed - --- | Parses at most one event from the state (cf. 'ParseResult') and --- returns the updated state that can be used to parse the next event. -readEvent :: EventParserState -> (ParseResult Event, EventParserState) -readEvent (ParsingHeader hd) = parseHeader hd -readEvent (ParsingEvents ed) = readEvent' ed - -readEvent' :: EventDecoder -> (ParseResult Event, EventParserState) -readEvent' (ed@(ED _ remaining header partial initial)) = - case partial of - (Done bs sz (Just event)) -> - case evSpec event of - EventBlock _ blockCap newRemaining -> do -- process a new block - let newState = newParserState' (isCap blockCap) newRemaining - header initial bs - readEvent newState - _ -> do -- other, non-EventBlock event - let newRemaining = remaining - fromIntegral sz - newState = newParserState' (mkCap ed sz) newRemaining - header initial bs - (Item (Event (evTime event) (evSpec event) (mkCap ed 0)), newState) - -- Parse returning Nothing means that the event log is complete - (Done _ _ Nothing) -> (Complete, ParsingEvents ed) - (Partial _) -> (Incomplete, ParsingEvents ed) - (Fail _ _ errMsg) -> (ParseError errMsg, ParsingEvents ed) - --- $eventhandleapi --- This API uses 'EventHandle' datatype that abstracts away the mutation of --- state and provides a simple interface for parsing events coming from a file --- descriptor. Just like the ByteString-based API, the contents of the 'Handle' --- are expected to follow the order of an .eventlog file. - --- | Instantiates a new EventHandle. -ehOpen :: Handle -- ^ Handle to read the input from. Its contents are expected - -- to begin with an .eventlog format header. - -> Int -- ^ The size of the chunk that the parser will read at once - -> IO EventHandle -ehOpen handle sz = do - ioref <- newIORef $ newParserState - return EH { ehHandle = handle, ehChunkSize = sz, ehState = ioref } - --- | Reads at most one event from the EventHandle. It is intended called --- repeadetly, returning one event at a time. -ehReadEvent :: EventHandle -> IO (ParseResult Event) -ehReadEvent (EH handle chunkSize stateRef) = do - state <- readIORef stateRef - let (result, state') = readEvent state - case result of - (Item _) -> do - writeIORef stateRef state' - return result - (Incomplete) -> do - bs <- B.hGetSome handle chunkSize - if bs == B.empty - then return Incomplete - else do - writeIORef stateRef $ state' `pushBytes` bs - ehReadEvent $ EH handle chunkSize stateRef - (Complete) -> return Complete - (ParseError errMsg) -> return (ParseError errMsg) - --- | Reads a full 'EventLog' from file. If the file is incomplete, will still --- return a properly formed 'EventLog' object with all the events until the point --- of malformation/cutoff. __NOTE__: in this case user will only be informed via --- an error message to stderr since this interface does not provide a better --- alternative. --- This function will load the entire file to --- memory, so it is better to not use it with large event logs. -{-# DEPRECATED readEventLogFromFile "The incremental parser interface \ -should be used" #-} -readEventLogFromFile :: FilePath -> IO (Either String EventLog) -readEventLogFromFile f = do - bytes <- B.readFile f - let (events, finalState, status) = - readRemainingEvents (newParserState `pushBytes` bytes) - let mbHeader = readHeader finalState - case (mbHeader, status) of - (_, ParseError errMsg) -> return $ Left $ "Parse error: " ++ errMsg - (Nothing, _) -> do return $ Left $ \ - concat $ ["Header was lost during parsing. This " - ,"should never happen. Please report a bug."] - (Just header, Complete) -> do - -- We reverse the list of events since the original list has them - -- in reverse order and reversing ensures stability for sorting. - return $ Right $ EventLog header (Data $ reverse events) - (Just header, Incomplete) -> do - hPutStrLn stderr $ concat ["Warning: The event log was not fully ", - "parsed. It could have been malformed or incomplete."] - return $ Right $ EventLog header (Data $ reverse events) - _ -> error $ concat ["Error: There was no parse error, Header is intact ", - "but the log\ \ is not. This should never happen, ", - "please report a bug."] - --- | Repeadetly consumes events until 'EventParserState' contains less than a --- single 'Event'. The last item of output triple indicates whether the full --- log was parsed or not, or whether there was a parse error, --- hence the ParseResult of unit datatype. -readRemainingEvents :: EventParserState -> ([Event], EventParserState, ParseResult ()) -readRemainingEvents eps = readRemainingEvents' eps [] - -readRemainingEvents' :: EventParserState -> [Event] - -> ([Event], EventParserState, ParseResult ()) -readRemainingEvents' eps events = - case newEvent of - (Item ev) -> readRemainingEvents' newState (ev:events) - (Complete) -> (events, newState, Complete) - -- In incomplete cases we try to call readEvent once more since the first - -- event may require two readEvent calls to be acquired - (Incomplete) -> let (newEvent', newState') = readEvent newState - in case newEvent' of - (Item e) -> readRemainingEvents' newState' (e:events) - _ -> (events, newState', Incomplete) - (ParseError err) -> (events, newState, ParseError err) - where (newEvent, newState) = readEvent eps - --- | Writes the 'EventLog' to file. The log is expected to __NOT__ have 'EventBlock' --- markers/events - the parsers no longer emit them and they are handled behind --- the scenes. -writeEventLogToFile :: FilePath -> EventLog -> IO () -writeEventLogToFile fp el = do - BL.writeFile fp $ serialiseEventLog el - --- | Serialises an 'EventLog' back to a 'ByteString', usually for writing it --- back to a file. -serialiseEventLog :: EventLog -> BL.ByteString -serialiseEventLog el@(EventLog _ (Data events)) = - runPut $ putEventLog blockedEl - where - eventsMap = capSplitEvents events - blockedEventsMap = M.mapWithKey addBlockMarker eventsMap - blockedEl = el{dat = Data blockedEvents} - blockedEvents = M.foldr (++) [] blockedEventsMap - --- Gets the Capability of an event in numeric form -getIntCap :: Event -> Int -getIntCap Event{evCap = cap} = - case cap of - Just capNo -> capNo - Nothing -> -1 - --- Creates an IntMap of the events with capability number as the key. --- Key -1 indicates global (capless) event -capSplitEvents :: [Event] -> M.IntMap [Event] -capSplitEvents evts = capSplitEvents' evts M.empty - -capSplitEvents' :: [Event] -> M.IntMap [Event] -> M.IntMap [Event] -capSplitEvents' evts imap = - case evts of - (x:xs) -> capSplitEvents' xs (M.insertWith (++) (getIntCap x) [x] imap) - [] -> imap - --- Adds a block marker to the beginnng of a list of events, annotated with --- its capability. All events are expected to belong to the same cap. -addBlockMarker :: Int -> [Event] -> [Event] -addBlockMarker cap evts = - (Event startTime (EventBlock endTime cap sz) (isCap cap)) : sortedEvts - where sz = fromIntegral . BL.length $ runPut $ mapM_ putEvent evts - startTime = case sortedEvts of - (x:_) -> evTime x - [] -> error "Cannot add block marker to an empty list of events" - sortedEvts = sortEvents evts - endTime = evTime $ last sortedEvts - --- Checks if the capability is not -1 (which indicates a global eventblock), so --- has no associated capability -isCap :: Int -> Maybe Int -isCap blockCap = if fromIntegral blockCap /= ((-1) :: Word16) - then Just blockCap - else Nothing - --- Checks if there are any bytes left in the current EventBlock. That number --- could be negative because exist some blockless events. -mkCap :: EventDecoder -> ByteOffset -> Maybe Int -mkCap ed sz - | (edRemaining ed - fromIntegral sz) > 0 = edCap ed - | otherwise = Nothing - --- Makes a decoder with all the required parsers when given a Header -mkEventDecoder :: Header -> Decoder (Maybe Event) -mkEventDecoder header = - getToDecoder (getEvent parsers) - where - imap = M.fromList [ (fromIntegral (num t),t) | t <- eventTypes header] - -- This test is complete, no-one has extended this event yet and all future - -- extensions will use newly allocated event IDs. - is_ghc_6 = Just sz_old_tid == do create_et <- M.lookup EVENT_CREATE_THREAD imap - size create_et - -- GHC6 writes an invalid header, we handle it here by using a - -- different set of event parsers. Note that the ghc7 event parsers - -- are standard events, and can be used by other runtime systems that - -- make use of threadscope. - - -- GHC-7.8.2 uses a different thread block status encoding, - -- and therefore requires a different parser for the stop - -- event. Later, in GHC-7.8.3, the old encoding was restored. - -- GHC-7.8.2 can be recognised by presence and absence of - -- events in the header: - -- * User markers were added in GHC-7.8 - -- * an empty event HACK_BUG_T9003 was added in GHC-7.8.3 - -- This fix breaks software which uses ghc-events and combines - -- user markers with the older stop status encoding. We don't - -- know of any such software, though. - is_pre77 = M.notMember EVENT_USER_MARKER imap - is_ghc782 = M.member EVENT_USER_MARKER imap && - M.notMember EVENT_HACK_BUG_T9003 imap - - stopParsers = if is_pre77 then pre77StopParsers - else if is_ghc782 then [ghc782StopParser] - else [post782StopParser] - - event_parsers = if is_ghc_6 - then standardParsers ++ ghc6Parsers ++ - parRTSParsers sz_old_tid - else standardParsers ++ ghc7Parsers ++ - stopParsers ++ parRTSParsers sz_tid ++ - mercuryParsers ++ perfParsers - parsers = EventParsers $ mkEventTypeParsers imap event_parsers - --- Turns an instance of Get into a Decoder -getToDecoder :: Get a -> Decoder a -getToDecoder = runGetIncremental - --- | Pretty-prints events coming from a handle -printEventsIncremental :: EventHandle - -> Bool -- Whether to retry on incomplete logs - -> IO () -printEventsIncremental eh dashf = do - event <- ehReadEvent eh - case event of - Item ev -> do - BB.hPutBuilder stdout (buildEvent' ev <> "\n") -- if actual printing is needed - printEventsIncremental eh dashf - Incomplete -> - if dashf - then print "Log Incomplete. Waiting for more input." >> threadDelay 1000000 >> printEventsIncremental eh dashf - else putStrLn "Finished (NOT all file was parsed successfully)" - Complete -> - putStrLn "Finished (file was parsed successfully)" - ParseError errMsg -> - putStrLn $ "Error: " ++ errMsg From fd234b63f682a37ccf63aef7802ed897e46941f2 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Thu, 9 Mar 2017 06:26:41 +0900 Subject: [PATCH 10/17] Add Haddock comments --- src/GHC/RTS/Events/Incremental.hs | 47 +++++++++++++++++++++++++++++-- 1 file changed, 44 insertions(+), 3 deletions(-) diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs index 8264599..6cc944a 100644 --- a/src/GHC/RTS/Events/Incremental.hs +++ b/src/GHC/RTS/Events/Incremental.hs @@ -47,12 +47,21 @@ import GHC.RTS.Events #define EVENTLOG_CONSTANTS_ONLY #include "EventLogFormat.h" +-- | The unfolding of the decoding process. data Decoder a = Consume (B.ByteString -> Decoder a) + -- ^ The decoder has consumed all the available input and needs more to + -- continue. | Produce !a (Decoder a) + -- ^ The decoder has returned a decoded value and the next decoder state to + -- continue. | Done B.ByteString + -- ^ The decoder has ended with leftover input. | Error B.ByteString String + -- ^ The decoder has encountered an error with lefover input and an error + -- message. +-- | Push an input chunk to the decoder pushChunk :: Decoder a -> B.ByteString -> Decoder a pushChunk decoder chunk = case decoder of Consume k -> k chunk @@ -60,7 +69,11 @@ pushChunk decoder chunk = case decoder of Done leftover -> Done $ leftover `B.append` chunk Error leftover err -> Error (leftover `B.append` chunk) err -withHeader :: (Header -> B.ByteString -> Decoder r) -> Decoder r +-- | Decode a header and continue with the provided decoder +withHeader + :: (Header -> B.ByteString -> Decoder r) + -- ^ Continuation + -> Decoder r withHeader f = go $ G.runGetIncremental getHeader where go decoder = case decoder of @@ -68,9 +81,11 @@ withHeader f = go $ G.runGetIncremental getHeader G.Partial k -> Consume $ \chunk -> go $ k $ Just chunk G.Fail leftover _ err -> Error leftover err +-- | Decode a header decodeHeader :: Decoder Header decodeHeader = withHeader $ \header leftover -> Produce header $ Done leftover +-- | Decode events decodeEvents :: Header -> Decoder Event decodeEvents header = go (0 :: Int) Nothing decoder0 where @@ -94,10 +109,13 @@ decodeEvents header = go (0 :: Int) Nothing decoder0 G.Fail leftover _ err -> Error leftover err +-- | Decode a header and events decodeEventLog :: Decoder Event decodeEventLog = withHeader $ \header leftover -> decodeEvents header `pushChunk` leftover +-- | Read a header from a lazy bytestring and return the header and the +-- leftover input for subsequent decoding. readHeader :: BL.ByteString -> Either String (Header, BL.ByteString) readHeader = go $ Left decodeHeader where @@ -113,6 +131,11 @@ readHeader = go $ Left decodeHeader Error _ err -> fail err Right header -> Right (header, bytes) +-- | Read events from a lazy bytestring. It returns an error message if it +-- encouters an error while decoding. +-- +-- Note that it doesn't fail if it consumes all input in the middle of decoding +-- of an event. readEvents :: Header -> BL.ByteString -> ([Event], Maybe String) readEvents header = f . go (decodeEvents header) where @@ -133,20 +156,38 @@ readEvents header = f . go (decodeEvents header) Done {} -> [] Error _ err -> [Left err] +-- | Read an entire eventlog from a lazy bytestring. It returns an error message if it +-- encouters an error while decoding. +-- +-- Note that it doesn't fail if it consumes all input in the middle of decoding +-- of an event. readEventLog :: BL.ByteString -> Either String (EventLog, Maybe String) readEventLog bytes = do (header, bytes') <- readHeader bytes case readEvents header bytes' of (events, err) -> return (EventLog header (Data events), err) +-- | Read an entire eventlog file. It returns an error message if it +-- encouters an error while decoding. +-- +-- Note that it doesn't fail if it consumes all input in the middle of decoding +-- of an event. readEventLogFromFile :: FilePath -> IO (Either String EventLog) readEventLogFromFile path = fmap fst . readEventLog <$> BL.readFile path -printEventsIncremental :: Bool -> FilePath -> IO () +-- | Read an eventlog file and pretty print it to stdout +printEventsIncremental + :: Bool -- ^ Follow the file or not + -> FilePath + -> IO () printEventsIncremental follow path = withFile path ReadMode (hPrintEventsIncremental follow) -hPrintEventsIncremental :: Bool -> Handle -> IO () +-- | Read an eventlog from the Handle and pretty print it to stdout +hPrintEventsIncremental + :: Bool -- ^ Follow the handle or not + -> Handle + -> IO () hPrintEventsIncremental follow hdl = go decodeEventLog where go decoder = case decoder of From 1fef97a20f67dd31b0828305c5e8be9ffc300f0a Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Fri, 10 Mar 2017 07:04:05 +0900 Subject: [PATCH 11/17] Enable -Wall and fix warnings --- ghc-events.cabal | 1 + src/GHC/RTS/Events.hs | 47 +++++++++++++++++----------------- src/GHC/RTS/Events/Analysis.hs | 12 +-------- src/GHC/RTS/Events/Merge.hs | 1 + 4 files changed, 26 insertions(+), 35 deletions(-) diff --git a/ghc-events.cabal b/ghc-events.cabal index be816e0..608bd6a 100644 --- a/ghc-events.cabal +++ b/ghc-events.cabal @@ -64,6 +64,7 @@ library include-dirs: include extensions: RecordWildCards, NamedFieldPuns, BangPatterns, PatternGuards other-extensions: FlexibleContexts, CPP + ghc-options: -Wall executable ghc-events main-is: GhcEvents.hs diff --git a/src/GHC/RTS/Events.hs b/src/GHC/RTS/Events.hs index 1d43e2b..d5e790f 100644 --- a/src/GHC/RTS/Events.hs +++ b/src/GHC/RTS/Events.hs @@ -76,9 +76,8 @@ import qualified Data.IntMap as M import Data.Foldable (foldMap) import Data.Function hiding (id) import Data.List -import Data.Maybe (fromMaybe, fromJust) +import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) -import Text.Printf import Data.Array import Prelude hiding (gcd, rem, id) @@ -144,9 +143,9 @@ getEvent (EventParsers parsers) = do etRef <- get :: Get EventTypeNum if etRef == EVENT_DATA_END then return Nothing - else do !ts <- get - spec <- parsers ! fromIntegral etRef - return $ Just (Event ts spec undefined) + else do !evTime <- get + evSpec <- parsers ! fromIntegral etRef + return $ Just Event { evCap = undefined, .. } -- -- standardEventParsers. @@ -593,7 +592,7 @@ ghc6Parsers = [ -- Parsers for parallel events. Parameter is the thread_id size, to create -- ghc6-parsers (using the wrong size) where necessary. parRTSParsers :: EventTypeSize -> [EventParser EventInfo] -parRTSParsers sz_tid = [ +parRTSParsers sz_tid' = [ (VariableSizeParser EVENT_VERSION (do -- (version) num <- get :: Get Word16 string <- getString num @@ -619,7 +618,7 @@ parRTSParsers sz_tid = [ return KillProcess{ process = p }) ), - (FixedSizeParser EVENT_ASSIGN_THREAD_TO_PROCESS (sz_tid + sz_procid) + (FixedSizeParser EVENT_ASSIGN_THREAD_TO_PROCESS (sz_tid' + sz_procid) (do t <- get p <- get return AssignThreadToProcess { thread = t, process = p }) @@ -637,7 +636,7 @@ parRTSParsers sz_tid = [ ), (FixedSizeParser EVENT_SEND_MESSAGE - (sz_msgtag + 2*sz_procid + 2*sz_tid + sz_mid) + (sz_msgtag + 2*sz_procid + 2*sz_tid' + sz_mid) (do tag <- get :: Get RawMsgTag sP <- get :: Get ProcessId sT <- get :: Get ThreadId @@ -654,7 +653,7 @@ parRTSParsers sz_tid = [ ), (FixedSizeParser EVENT_RECEIVE_MESSAGE - (sz_msgtag + 2*sz_procid + 2*sz_tid + sz_mid + sz_mes) + (sz_msgtag + 2*sz_procid + 2*sz_tid' + sz_mid + sz_mes) (do tag <- get :: Get Word8 rP <- get :: Get ProcessId rIP <- get :: Get PortId @@ -673,7 +672,7 @@ parRTSParsers sz_tid = [ ), (FixedSizeParser EVENT_SEND_RECEIVE_LOCAL_MESSAGE - (sz_msgtag + 2*sz_procid + 2*sz_tid) + (sz_msgtag + 2*sz_procid + 2*sz_tid') (do tag <- get :: Get Word8 sP <- get :: Get ProcessId sT <- get :: Get ThreadId @@ -786,8 +785,8 @@ showEventInfo :: EventInfo -> String showEventInfo = BL8.unpack . BB.toLazyByteString . buildEventInfo buildEventInfo :: EventInfo -> BB.Builder -buildEventInfo spec = - case spec of +buildEventInfo spec' = + case spec' of EventBlock end_time cap _block_events -> "event block: cap " <> BB.intDec cap <> ", end time: " <> BB.word64Dec end_time <> "\n" @@ -1073,24 +1072,24 @@ ppEvent :: IntMap EventType -> Event -> String ppEvent imap = BL8.unpack . BB.toLazyByteString . buildEvent imap buildEvent :: IntMap EventType -> Event -> BB.Builder -buildEvent imap (Event time spec evCap) = - BB.word64Dec time +buildEvent imap Event {..} = + BB.word64Dec evTime <> ": " <> maybe "" (\c -> "cap " <> BB.intDec c <> ": ") evCap - <> case spec of + <> case evSpec of UnknownEvent{ ref=ref } -> maybe "" (BB.stringUtf8 . desc) $ M.lookup (fromIntegral ref) imap - _ -> buildEventInfo spec + _ -> buildEventInfo evSpec buildEvent' :: Event -> BB.Builder -buildEvent' (Event time spec evCap) = - BB.word64Dec time +buildEvent' Event {..} = + BB.word64Dec evTime <> ": " <> maybe "" (\c -> "cap " <> BB.intDec c <> ": ") evCap - <> case spec of + <> case evSpec of UnknownEvent{ ref=ref } -> "Unknown Event (ref: " <> BB.word16Dec ref <> ")" - _ -> buildEventInfo spec + _ -> buildEventInfo evSpec type PutEvents a = PutM a @@ -1230,10 +1229,10 @@ nEVENT_PERF_COUNTER = EVENT_PERF_COUNTER nEVENT_PERF_TRACEPOINT = EVENT_PERF_TRACEPOINT putEvent :: Event -> PutEvents () -putEvent (Event {evTime = t , evSpec = spec}) = do - putType (eventTypeNum spec) - put t - putEventSpec spec +putEvent Event {..} = do + putType (eventTypeNum evSpec) + put evTime + putEventSpec evSpec putEventSpec :: EventInfo -> PutEvents () putEventSpec (Startup caps) = do diff --git a/src/GHC/RTS/Events/Analysis.hs b/src/GHC/RTS/Events/Analysis.hs index 404c924..cf72fde 100644 --- a/src/GHC/RTS/Events/Analysis.hs +++ b/src/GHC/RTS/Events/Analysis.hs @@ -41,16 +41,6 @@ data Machine s i = Machine , delta :: s -> i -> Maybe s -- ^ State transition function } --- | This machine always accepts, never terminates, and always has unit state. --- It is not used anywhere. -unitMachine :: Machine () i -unitMachine = Machine - { initial = () - , final = const False - , alpha = const True - , delta = (\_ _ -> Just ()) - } - -- | The `step` function runs a machine in a state against a single input. -- The state remains fixed once a final state is encountered. The -- result is `Left state input` if some `state` failed for an `ìnput`, and @@ -105,7 +95,7 @@ analyse :: Machine s i -- ^ The machine used -> (s -> i -> Maybe o) -- ^ An extraction function that may produce output -> [i] -- ^ A list of input -> Process (s, i) o -- ^ A process that produces output -analyse machine extract is = go (initial machine) is +analyse machine extract = go (initial machine) where -- go :: s -> [i] -> Process (s, i) o go _ [] = Done diff --git a/src/GHC/RTS/Events/Merge.hs b/src/GHC/RTS/Events/Merge.hs index 0492f5b..77a83e5 100644 --- a/src/GHC/RTS/Events/Merge.hs +++ b/src/GHC/RTS/Events/Merge.hs @@ -7,6 +7,7 @@ import Data.Monoid import Data.List (foldl') import qualified Data.Map as M import Data.Word (Word32) +import Prelude -- TODO: add a merge mode where the events are synchronized using -- the wall clock time event at the start of both eventlogs (for newer GHCs). From 2265915f69c81438c4e10aab975675881e662325 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Tue, 7 Mar 2017 16:11:00 +0900 Subject: [PATCH 12/17] Remove trailing space in code --- src/GHC/RTS/EventParserUtils.hs | 2 +- src/GHC/RTS/EventTypes.hs | 6 +++--- src/GHC/RTS/Events.hs | 6 +++--- src/GHC/RTS/Events/Merge.hs | 2 +- 4 files changed, 8 insertions(+), 8 deletions(-) diff --git a/src/GHC/RTS/EventParserUtils.hs b/src/GHC/RTS/EventParserUtils.hs index d1a4023..564981a 100644 --- a/src/GHC/RTS/EventParserUtils.hs +++ b/src/GHC/RTS/EventParserUtils.hs @@ -168,7 +168,7 @@ padParser size (FixedSizeParser t orig_size orig_p) = FixedSizeParser t size p makeParserMap :: [EventParser a] -> IntMap [EventParser a] makeParserMap = foldl buildParserMap M.empty - where buildParserMap map' parser = + where buildParserMap map' parser = M.alter (addParser parser) (getType parser) map' addParser p Nothing = Just [p] addParser p (Just ps) = Just (p:ps) diff --git a/src/GHC/RTS/EventTypes.hs b/src/GHC/RTS/EventTypes.hs index ac59ef8..b42e476 100644 --- a/src/GHC/RTS/EventTypes.hs +++ b/src/GHC/RTS/EventTypes.hs @@ -130,11 +130,11 @@ data Event = {-# DEPRECATED time "The field is now called evTime" #-} time :: Event -> Timestamp -time = evTime +time = evTime {-# DEPRECATED spec "The field is now called evSpec" #-} spec :: Event -> EventInfo -spec = evSpec +spec = evSpec data EventInfo @@ -471,7 +471,7 @@ mkStopStatus782 n = case n of 19 -> BlockedOnMsgGlobalise _ -> error "mkStat" -maxThreadStopStatusPre77, maxThreadStopStatus782, maxThreadStopStatus +maxThreadStopStatusPre77, maxThreadStopStatus782, maxThreadStopStatus :: RawThreadStopStatus maxThreadStopStatusPre77 = 18 -- see [Stop status in GHC-7.8.2] maxThreadStopStatus782 = 19 -- need to distinguish three cases diff --git a/src/GHC/RTS/Events.hs b/src/GHC/RTS/Events.hs index d5e790f..555bcd8 100644 --- a/src/GHC/RTS/Events.hs +++ b/src/GHC/RTS/Events.hs @@ -475,7 +475,7 @@ pre77StopParsers = [ -- older version of the event, no block info )), - (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) + (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) (do -- (thread, status, info) t <- get @@ -496,8 +496,8 @@ pre77StopParsers = [ -- parsers for GHC >= 7.8.3, always using block info field parser. -- See [Stop status in GHC-7.8.2] in EventTypes.hs post782StopParser :: EventParser EventInfo -post782StopParser = - (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) +post782StopParser = + (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) (do -- (thread, status, info) t <- get diff --git a/src/GHC/RTS/Events/Merge.hs b/src/GHC/RTS/Events/Merge.hs index 77a83e5..3a14c81 100644 --- a/src/GHC/RTS/Events/Merge.hs +++ b/src/GHC/RTS/Events/Merge.hs @@ -79,7 +79,7 @@ sh :: Num a => a -> a -> a sh x y = x + y updateSpec :: (EventInfo -> EventInfo) -> Event -> Event -updateSpec f (Event {evTime = t, evSpec = s, evCap = cap}) = +updateSpec f (Event {evTime = t, evSpec = s, evCap = cap}) = Event {evTime = t, evSpec = f s, evCap = cap} shift :: MaxVars -> [Event] -> [Event] From 3dd58cf9d9f872067ffefcf0b9975699222f7105 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Sun, 12 Mar 2017 07:09:00 +0900 Subject: [PATCH 13/17] Move all decoders and encoders to the Binary module --- ghc-events.cabal | 1 + src/GHC/RTS/Events.hs | 1219 +--------------------------- src/GHC/RTS/Events/Binary.hs | 1228 +++++++++++++++++++++++++++++ src/GHC/RTS/Events/Incremental.hs | 1 + 4 files changed, 1231 insertions(+), 1218 deletions(-) create mode 100644 src/GHC/RTS/Events/Binary.hs diff --git a/ghc-events.cabal b/ghc-events.cabal index 608bd6a..180a84d 100644 --- a/ghc-events.cabal +++ b/ghc-events.cabal @@ -60,6 +60,7 @@ library GHC.RTS.Events.Analysis.Thread other-modules: GHC.RTS.EventParserUtils, GHC.RTS.EventTypes + GHC.RTS.Events.Binary hs-source-dirs: src include-dirs: include extensions: RecordWildCards, NamedFieldPuns, BangPatterns, PatternGuards diff --git a/src/GHC/RTS/Events.hs b/src/GHC/RTS/Events.hs index 555bcd8..c727143 100644 --- a/src/GHC/RTS/Events.hs +++ b/src/GHC/RTS/Events.hs @@ -6,18 +6,6 @@ -} module GHC.RTS.Events ( - -- * Parsers - getHeader, - getEvent, - standardParsers, - ghc6Parsers, - ghc7Parsers, - mercuryParsers, - perfParsers, - pre77StopParsers, - ghc782StopParser, - post782StopParser, - parRTSParsers, -- * The event log types EventLog(..), Header(..), @@ -38,11 +26,6 @@ module GHC.RTS.Events ( MessageSize, MessageTag(..), - -- * Functions that assist reading and writing event logs - putEvent, - PutEvents, - putEventLog, - -- * Utilities CapEvent(..), sortEvents, buildEventTypeMap, @@ -64,711 +47,20 @@ module GHC.RTS.Events ( ) where {- Libraries. -} -import Data.Binary -import Data.Binary.Get () -import qualified Data.Binary.Get as G -import Data.Binary.Put import qualified Data.ByteString.Builder as BB import qualified Data.ByteString.Lazy.Char8 as BL8 -import Control.Monad (when, replicateM) import Data.IntMap (IntMap) import qualified Data.IntMap as M import Data.Foldable (foldMap) import Data.Function hiding (id) import Data.List -import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) -import Data.Array import Prelude hiding (gcd, rem, id) -import GHC.RTS.EventParserUtils import GHC.RTS.EventTypes +import GHC.RTS.Events.Binary -#define EVENTLOG_CONSTANTS_ONLY -#include "EventLogFormat.h" - -getEventType :: Get EventType -getEventType = do - etNum <- get - size <- get :: Get EventTypeSize - let etSize = if size == 0xffff then Nothing else Just size - -- 0xffff indicates variable-sized event - etDescLen <- get :: Get EventTypeDescLen - etDesc <- getEtDesc (fromIntegral etDescLen) - etExtraLen <- get :: Get Word32 - G.skip (fromIntegral etExtraLen) - ete <- get :: Get Marker - when (ete /= EVENT_ET_END) $ - fail "Event Type end marker not found." - return (EventType etNum etDesc etSize) - where - getEtDesc :: Int -> Get [Char] - getEtDesc s = replicateM s (get :: Get Char) - - - -getHeader :: Get Header -getHeader = do - hdrb <- get :: Get Marker - when (hdrb /= EVENT_HEADER_BEGIN) $ - fail "Header begin marker not found" - hetm <- get :: Get Marker - when (hetm /= EVENT_HET_BEGIN) $ - fail "Header Event Type begin marker not found" - ets <- getEventTypes - emark <- get :: Get Marker - when (emark /= EVENT_HEADER_END) $ - fail "Header end marker not found" - db <- get :: Get Marker - when (db /= EVENT_DATA_BEGIN) $ - fail "My Data begin marker not found" - return $ Header ets - where - getEventTypes :: Get [EventType] - getEventTypes = do - m <- get :: Get Marker - case m of - EVENT_ET_BEGIN -> do - et <- getEventType - nextET <- getEventTypes - return (et : nextET) - EVENT_HET_END -> - return [] - _ -> - fail "Malformed list of Event Types in header" - -getEvent :: EventParsers -> Get (Maybe Event) -getEvent (EventParsers parsers) = do - etRef <- get :: Get EventTypeNum - if etRef == EVENT_DATA_END - then return Nothing - else do !evTime <- get - evSpec <- parsers ! fromIntegral etRef - return $ Just Event { evCap = undefined, .. } - --- --- standardEventParsers. --- -standardParsers :: [EventParser EventInfo] -standardParsers = [ - (FixedSizeParser EVENT_STARTUP sz_cap (do -- (n_caps) - c <- get :: Get CapNo - return Startup{ n_caps = fromIntegral c } - )), - - (FixedSizeParser EVENT_BLOCK_MARKER (sz_block_size + sz_time + sz_cap) (do -- (size, end_time, cap) - block_size <- get :: Get BlockSize - end_time <- get :: Get Timestamp - c <- get :: Get CapNo - return EventBlock { end_time = end_time, - cap = fromIntegral c, - block_size = ((fromIntegral block_size) - - (fromIntegral sz_block_event)) - } - )), - - -- EVENT_SHUTDOWN is replaced by EVENT_CAP_DELETE and GHC 7.6+ - -- no longer generate the event; should be removed at some point - (simpleEvent EVENT_SHUTDOWN Shutdown), - - (simpleEvent EVENT_REQUEST_SEQ_GC RequestSeqGC), - - (simpleEvent EVENT_REQUEST_PAR_GC RequestParGC), - - (simpleEvent EVENT_GC_START StartGC), - - (simpleEvent EVENT_GC_WORK GCWork), - - (simpleEvent EVENT_GC_IDLE GCIdle), - - (simpleEvent EVENT_GC_DONE GCDone), - - (simpleEvent EVENT_GC_END EndGC), - - (simpleEvent EVENT_GC_GLOBAL_SYNC GlobalSyncGC), - - (FixedSizeParser EVENT_GC_STATS_GHC (sz_capset + 2 + 5*8 + 4) (do -- (heap_capset, generation, copied_bytes, slop_bytes, frag_bytes, par_n_threads, par_max_copied, par_tot_copied) - heapCapset <- get - gen <- get :: Get Word16 - copied <- get :: Get Word64 - slop <- get :: Get Word64 - frag <- get :: Get Word64 - parNThreads <- get :: Get Word32 - parMaxCopied <- get :: Get Word64 - parTotCopied <- get :: Get Word64 - return GCStatsGHC{ gen = fromIntegral gen - , parNThreads = fromIntegral parNThreads - , ..} - )), - - (FixedSizeParser EVENT_HEAP_ALLOCATED (sz_capset + 8) (do -- (heap_capset, alloc_bytes) - heapCapset <- get - allocBytes <- get - return HeapAllocated{..} - )), - - (FixedSizeParser EVENT_HEAP_SIZE (sz_capset + 8) (do -- (heap_capset, size_bytes) - heapCapset <- get - sizeBytes <- get - return HeapSize{..} - )), - - (FixedSizeParser EVENT_HEAP_LIVE (sz_capset + 8) (do -- (heap_capset, live_bytes) - heapCapset <- get - liveBytes <- get - return HeapLive{..} - )), - - (FixedSizeParser EVENT_HEAP_INFO_GHC (sz_capset + 2 + 4*8) (do -- (heap_capset, n_generations, max_heap_size, alloc_area_size, mblock_size, block_size) - heapCapset <- get - gens <- get :: Get Word16 - maxHeapSize <- get :: Get Word64 - allocAreaSize <- get :: Get Word64 - mblockSize <- get :: Get Word64 - blockSize <- get :: Get Word64 - return HeapInfoGHC{gens = fromIntegral gens, ..} - )), - - (FixedSizeParser EVENT_CAP_CREATE (sz_cap) (do -- (cap) - cap <- get :: Get CapNo - return CapCreate{cap = fromIntegral cap} - )), - - (FixedSizeParser EVENT_CAP_DELETE (sz_cap) (do -- (cap) - cap <- get :: Get CapNo - return CapDelete{cap = fromIntegral cap} - )), - - (FixedSizeParser EVENT_CAP_DISABLE (sz_cap) (do -- (cap) - cap <- get :: Get CapNo - return CapDisable{cap = fromIntegral cap} - )), - - (FixedSizeParser EVENT_CAP_ENABLE (sz_cap) (do -- (cap) - cap <- get :: Get CapNo - return CapEnable{cap = fromIntegral cap} - )), - - (FixedSizeParser EVENT_CAPSET_CREATE (sz_capset + sz_capset_type) (do -- (capset, capset_type) - cs <- get - ct <- fmap mkCapsetType get - return CapsetCreate{capset=cs,capsetType=ct} - )), - - (FixedSizeParser EVENT_CAPSET_DELETE sz_capset (do -- (capset) - cs <- get - return CapsetDelete{capset=cs} - )), - - (FixedSizeParser EVENT_CAPSET_ASSIGN_CAP (sz_capset + sz_cap) (do -- (capset, cap) - cs <- get - cp <- get :: Get CapNo - return CapsetAssignCap{capset=cs,cap=fromIntegral cp} - )), - - (FixedSizeParser EVENT_CAPSET_REMOVE_CAP (sz_capset + sz_cap) (do -- (capset, cap) - cs <- get - cp <- get :: Get CapNo - return CapsetRemoveCap{capset=cs,cap=fromIntegral cp} - )), - - (FixedSizeParser EVENT_OSPROCESS_PID (sz_capset + sz_pid) (do -- (capset, pid) - cs <- get - pd <- get - return OsProcessPid{capset=cs,pid=pd} - )), - - (FixedSizeParser EVENT_OSPROCESS_PPID (sz_capset + sz_pid) (do -- (capset, ppid) - cs <- get - pd <- get - return OsProcessParentPid{capset=cs,ppid=pd} - )), - - (FixedSizeParser EVENT_WALL_CLOCK_TIME (sz_capset + 8 + 4) (do -- (capset, unix_epoch_seconds, nanoseconds) - cs <- get - s <- get - ns <- get - return WallClockTime{capset=cs,sec=s,nsec=ns} - )), - - (VariableSizeParser EVENT_LOG_MSG (do -- (msg) - num <- get :: Get Word16 - string <- getString num - return Message{ msg = string } - )), - (VariableSizeParser EVENT_USER_MSG (do -- (msg) - num <- get :: Get Word16 - string <- getString num - return UserMessage{ msg = string } - )), - (VariableSizeParser EVENT_USER_MARKER (do -- (markername) - num <- get :: Get Word16 - string <- getString num - return UserMarker{ markername = string } - )), - (VariableSizeParser EVENT_PROGRAM_ARGS (do -- (capset, [arg]) - num <- get :: Get Word16 - cs <- get - string <- getString (num - sz_capset) - return ProgramArgs{ capset = cs - , args = splitNull string } - )), - (VariableSizeParser EVENT_PROGRAM_ENV (do -- (capset, [arg]) - num <- get :: Get Word16 - cs <- get - string <- getString (num - sz_capset) - return ProgramEnv{ capset = cs - , env = splitNull string } - )), - (VariableSizeParser EVENT_RTS_IDENTIFIER (do -- (capset, str) - num <- get :: Get Word16 - cs <- get - string <- getString (num - sz_capset) - return RtsIdentifier{ capset = cs - , rtsident = string } - )), - - (VariableSizeParser EVENT_INTERN_STRING (do -- (str, id) - num <- get :: Get Word16 - string <- getString (num - sz_string_id) - sId <- get :: Get StringId - return (InternString string sId) - )), - - (VariableSizeParser EVENT_THREAD_LABEL (do -- (thread, str) - num <- get :: Get Word16 - tid <- get - str <- getString (num - sz_tid) - return ThreadLabel{ thread = tid - , threadlabel = str } - )) - ] - --- Parsers valid for GHC7 but not GHC6. -ghc7Parsers :: [EventParser EventInfo] -ghc7Parsers = [ - (FixedSizeParser EVENT_CREATE_THREAD sz_tid (do -- (thread) - t <- get - return CreateThread{thread=t} - )), - - (FixedSizeParser EVENT_RUN_THREAD sz_tid (do -- (thread) - t <- get - return RunThread{thread=t} - )), - - (FixedSizeParser EVENT_THREAD_RUNNABLE sz_tid (do -- (thread) - t <- get - return ThreadRunnable{thread=t} - )), - - (FixedSizeParser EVENT_MIGRATE_THREAD (sz_tid + sz_cap) (do -- (thread, newCap) - t <- get - nc <- get :: Get CapNo - return MigrateThread{thread=t,newCap=fromIntegral nc} - )), - - -- Yes, EVENT_RUN/STEAL_SPARK are deprecated, but see the explanation in the - -- 'ghc6Parsers' section below. Since we're parsing them anyway, we might - -- as well convert them to the new SparkRun/SparkSteal events. - (FixedSizeParser EVENT_RUN_SPARK sz_tid (do -- (thread) - _ <- get :: Get ThreadId - return SparkRun - )), - - (FixedSizeParser EVENT_STEAL_SPARK (sz_tid + sz_cap) (do -- (thread, victimCap) - _ <- get :: Get ThreadId - vc <- get :: Get CapNo - return SparkSteal{victimCap=fromIntegral vc} - )), - - (FixedSizeParser EVENT_CREATE_SPARK_THREAD sz_tid (do -- (sparkThread) - st <- get :: Get ThreadId - return CreateSparkThread{sparkThread=st} - )), - - (FixedSizeParser EVENT_SPARK_COUNTERS (7*8) (do -- (crt,dud,ovf,cnv,gcd,fiz,rem) - crt <- get :: Get Word64 - dud <- get :: Get Word64 - ovf <- get :: Get Word64 - cnv <- get :: Get Word64 - gcd <- get :: Get Word64 - fiz <- get :: Get Word64 - rem <- get :: Get Word64 - return SparkCounters{sparksCreated = crt, sparksDud = dud, - sparksOverflowed = ovf, sparksConverted = cnv, - -- Warning: order of fiz and gcd reversed! - sparksFizzled = fiz, sparksGCd = gcd, - sparksRemaining = rem} - )), - - (simpleEvent EVENT_SPARK_CREATE SparkCreate), - (simpleEvent EVENT_SPARK_DUD SparkDud), - (simpleEvent EVENT_SPARK_OVERFLOW SparkOverflow), - (simpleEvent EVENT_SPARK_RUN SparkRun), - (FixedSizeParser EVENT_SPARK_STEAL sz_cap (do -- (victimCap) - vc <- get :: Get CapNo - return SparkSteal{victimCap=fromIntegral vc} - )), - (simpleEvent EVENT_SPARK_FIZZLE SparkFizzle), - (simpleEvent EVENT_SPARK_GC SparkGC), - - (FixedSizeParser EVENT_TASK_CREATE (sz_taskid + sz_cap + sz_kernel_tid) (do -- (taskID, cap, tid) - taskId <- get :: Get TaskId - cap <- get :: Get CapNo - tid <- get :: Get KernelThreadId - return TaskCreate{ taskId, cap = fromIntegral cap, tid } - )), - (FixedSizeParser EVENT_TASK_MIGRATE (sz_taskid + sz_cap*2) (do -- (taskID, cap, new_cap) - taskId <- get :: Get TaskId - cap <- get :: Get CapNo - new_cap <- get :: Get CapNo - return TaskMigrate{ taskId, cap = fromIntegral cap - , new_cap = fromIntegral new_cap - } - )), - (FixedSizeParser EVENT_TASK_DELETE (sz_taskid) (do -- (taskID) - taskId <- get :: Get TaskId - return TaskDelete{ taskId } - )), - - (FixedSizeParser EVENT_THREAD_WAKEUP (sz_tid + sz_cap) (do -- (thread, other_cap) - t <- get - oc <- get :: Get CapNo - return WakeupThread{thread=t,otherCap=fromIntegral oc} - )) - ] - --- special thread stop event parsers for GHC version 7.8.2 --- see [Stop status in GHC-7.8.2] in EventTypes.hs -ghc782StopParser :: EventParser EventInfo -ghc782StopParser = - (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) (do - -- (thread, status, info) - t <- get - s <- get :: Get RawThreadStopStatus - i <- get :: Get ThreadId - return StopThread{thread = t, - status = case () of - _ | s > maxThreadStopStatus782 - -> NoStatus - | s == 9 {- XXX yeuch -} - -- GHC-7.8.2: 9 == BlockedOnBlackHole - -> BlockedOnBlackHoleOwnedBy i - | otherwise - -> mkStopStatus782 s} - )) - --- parsers for GHC < 7.8.2. Older versions do not use block info --- (different length). See [Stop status in GHC-7.8.2] in --- EventTypes.hs -pre77StopParsers :: [EventParser EventInfo] -pre77StopParsers = [ - (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status) (do - -- (thread, status) - t <- get - s <- get :: Get RawThreadStopStatus - return StopThread{thread=t, status = if s > maxThreadStopStatusPre77 - then NoStatus - else mkStopStatus s} - -- older version of the event, no block info - )), - - (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) - (do - -- (thread, status, info) - t <- get - s <- get :: Get RawThreadStopStatus - i <- get :: Get ThreadId - return StopThread{thread = t, - status = case () of - _ | s > maxThreadStopStatusPre77 - -> NoStatus - | s == 8 {- XXX yeuch -} - -- pre-7.7: 8==BlockedOnBlackhole - -> BlockedOnBlackHoleOwnedBy i - | otherwise - -> mkStopStatus s} - )) - ] - --- parsers for GHC >= 7.8.3, always using block info field parser. --- See [Stop status in GHC-7.8.2] in EventTypes.hs -post782StopParser :: EventParser EventInfo -post782StopParser = - (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) - (do - -- (thread, status, info) - t <- get - s <- get :: Get RawThreadStopStatus - i <- get :: Get ThreadId - return StopThread{thread = t, - status = case () of - _ | s > maxThreadStopStatus - -> NoStatus - | s == 8 {- XXX yeuch -} - -- post-7.8.2: 8==BlockedOnBlackhole - -> BlockedOnBlackHoleOwnedBy i - | otherwise - -> mkStopStatus s} - )) - - ----------------------- - -- GHC 6.12 compat: GHC 6.12 reported the wrong sizes for some events, - -- so we have to recognise those wrong sizes here for backwards - -- compatibility. -ghc6Parsers :: [EventParser EventInfo] -ghc6Parsers = [ - (FixedSizeParser EVENT_STARTUP 0 (do - -- BUG in GHC 6.12: the startup event was incorrectly - -- declared as size 0, so we accept it here. - c <- get :: Get CapNo - return Startup{ n_caps = fromIntegral c } - )), - - (FixedSizeParser EVENT_CREATE_THREAD sz_old_tid (do -- (thread) - t <- get - return CreateThread{thread=t} - )), - - (FixedSizeParser EVENT_RUN_THREAD sz_old_tid (do -- (thread) - t <- get - return RunThread{thread=t} - )), - - (FixedSizeParser EVENT_STOP_THREAD (sz_old_tid + 2) (do -- (thread, status) - t <- get - s <- get :: Get RawThreadStopStatus - return StopThread{thread=t, status = if s > maxThreadStopStatusPre77 - then NoStatus - else mkStopStatus s} - -- older version of the event uses pre-77 encoding - -- (actually, it only uses encodings 0 to 5) - -- see [Stop status in GHC-7.8.2] in EventTypes.hs - )), - - (FixedSizeParser EVENT_THREAD_RUNNABLE sz_old_tid (do -- (thread) - t <- get - return ThreadRunnable{thread=t} - )), - - (FixedSizeParser EVENT_MIGRATE_THREAD (sz_old_tid + sz_cap) (do -- (thread, newCap) - t <- get - nc <- get :: Get CapNo - return MigrateThread{thread=t,newCap=fromIntegral nc} - )), - - -- Note: it is vital that these two (EVENT_RUN/STEAL_SPARK) remain here (at - -- least in the ghc6Parsers section) even though both events are deprecated. - -- The reason is that .eventlog files created by the buggy GHC-6.12 - -- mis-declare the size of these two events. So we have to handle them - -- specially here otherwise we'll get the wrong size, leading to us getting - -- out of sync and eventual parse failure. Since we're parsing them anyway, - -- we might as well convert them to the new SparkRun/SparkSteal events. - (FixedSizeParser EVENT_RUN_SPARK sz_old_tid (do -- (thread) - _ <- get :: Get ThreadId - return SparkRun - )), - - (FixedSizeParser EVENT_STEAL_SPARK (sz_old_tid + sz_cap) (do -- (thread, victimCap) - _ <- get :: Get ThreadId - vc <- get :: Get CapNo - return SparkSteal{victimCap=fromIntegral vc} - )), - - (FixedSizeParser EVENT_CREATE_SPARK_THREAD sz_old_tid (do -- (sparkThread) - st <- get :: Get ThreadId - return CreateSparkThread{sparkThread=st} - )), - - (FixedSizeParser EVENT_THREAD_WAKEUP (sz_old_tid + sz_cap) (do -- (thread, other_cap) - t <- get - oc <- get :: Get CapNo - return WakeupThread{thread=t,otherCap=fromIntegral oc} - )) - ] - --- Parsers for parallel events. Parameter is the thread_id size, to create --- ghc6-parsers (using the wrong size) where necessary. -parRTSParsers :: EventTypeSize -> [EventParser EventInfo] -parRTSParsers sz_tid' = [ - (VariableSizeParser EVENT_VERSION (do -- (version) - num <- get :: Get Word16 - string <- getString num - return Version{ version = string } - )), - - (VariableSizeParser EVENT_PROGRAM_INVOCATION (do -- (cmd. line) - num <- get :: Get Word16 - string <- getString num - return ProgramInvocation{ commandline = string } - )), - - (simpleEvent EVENT_EDEN_START_RECEIVE EdenStartReceive), - (simpleEvent EVENT_EDEN_END_RECEIVE EdenEndReceive), - - (FixedSizeParser EVENT_CREATE_PROCESS sz_procid - (do p <- get - return CreateProcess{ process = p }) - ), - - (FixedSizeParser EVENT_KILL_PROCESS sz_procid - (do p <- get - return KillProcess{ process = p }) - ), - - (FixedSizeParser EVENT_ASSIGN_THREAD_TO_PROCESS (sz_tid' + sz_procid) - (do t <- get - p <- get - return AssignThreadToProcess { thread = t, process = p }) - ), - - (FixedSizeParser EVENT_CREATE_MACHINE (sz_mid + sz_realtime) - (do m <- get - t <- get - return CreateMachine { machine = m, realtime = t }) - ), - - (FixedSizeParser EVENT_KILL_MACHINE sz_mid - (do m <- get :: Get MachineId - return KillMachine { machine = m }) - ), - - (FixedSizeParser EVENT_SEND_MESSAGE - (sz_msgtag + 2*sz_procid + 2*sz_tid' + sz_mid) - (do tag <- get :: Get RawMsgTag - sP <- get :: Get ProcessId - sT <- get :: Get ThreadId - rM <- get :: Get MachineId - rP <- get :: Get ProcessId - rIP <- get :: Get PortId - return SendMessage { mesTag = toMsgTag tag, - senderProcess = sP, - senderThread = sT, - receiverMachine = rM, - receiverProcess = rP, - receiverInport = rIP - }) - ), - - (FixedSizeParser EVENT_RECEIVE_MESSAGE - (sz_msgtag + 2*sz_procid + 2*sz_tid' + sz_mid + sz_mes) - (do tag <- get :: Get Word8 - rP <- get :: Get ProcessId - rIP <- get :: Get PortId - sM <- get :: Get MachineId - sP <- get :: Get ProcessId - sT <- get :: Get ThreadId - mS <- get :: Get MessageSize - return ReceiveMessage { mesTag = toMsgTag tag, - receiverProcess = rP, - receiverInport = rIP, - senderMachine = sM, - senderProcess = sP, - senderThread= sT, - messageSize = mS - }) - ), - - (FixedSizeParser EVENT_SEND_RECEIVE_LOCAL_MESSAGE - (sz_msgtag + 2*sz_procid + 2*sz_tid') - (do tag <- get :: Get Word8 - sP <- get :: Get ProcessId - sT <- get :: Get ThreadId - rP <- get :: Get ProcessId - rIP <- get :: Get PortId - return SendReceiveLocalMessage { mesTag = toMsgTag tag, - senderProcess = sP, - senderThread = sT, - receiverProcess = rP, - receiverInport = rIP - }) - )] - -mercuryParsers :: [EventParser EventInfo] -mercuryParsers = [ - (FixedSizeParser EVENT_MER_START_PAR_CONJUNCTION - (sz_par_conj_dyn_id + sz_par_conj_static_id) - (do dyn_id <- get - static_id <- get - return (MerStartParConjunction dyn_id static_id)) - ), - - (FixedSizeParser EVENT_MER_STOP_PAR_CONJUNCTION sz_par_conj_dyn_id - (do dyn_id <- get - return (MerEndParConjunction dyn_id)) - ), - - (FixedSizeParser EVENT_MER_STOP_PAR_CONJUNCT sz_par_conj_dyn_id - (do dyn_id <- get - return (MerEndParConjunct dyn_id)) - ), - - (FixedSizeParser EVENT_MER_CREATE_SPARK (sz_par_conj_dyn_id + sz_spark_id) - (do dyn_id <- get - spark_id <- get - return (MerCreateSpark dyn_id spark_id)) - ), - - (FixedSizeParser EVENT_MER_FUT_CREATE (sz_future_id + sz_string_id) - (do future_id <- get - name_id <- get - return (MerFutureCreate future_id name_id)) - ), - - (FixedSizeParser EVENT_MER_FUT_WAIT_NOSUSPEND (sz_future_id) - (do future_id <- get - return (MerFutureWaitNosuspend future_id)) - ), - - (FixedSizeParser EVENT_MER_FUT_WAIT_SUSPENDED (sz_future_id) - (do future_id <- get - return (MerFutureWaitSuspended future_id)) - ), - - (FixedSizeParser EVENT_MER_FUT_SIGNAL (sz_future_id) - (do future_id <- get - return (MerFutureSignal future_id)) - ), - - (simpleEvent EVENT_MER_LOOKING_FOR_GLOBAL_CONTEXT MerLookingForGlobalThread), - (simpleEvent EVENT_MER_WORK_STEALING MerWorkStealing), - (simpleEvent EVENT_MER_LOOKING_FOR_LOCAL_SPARK MerLookingForLocalSpark), - - (FixedSizeParser EVENT_MER_RELEASE_CONTEXT sz_tid - (do thread_id <- get - return (MerReleaseThread thread_id)) - ), - - (simpleEvent EVENT_MER_ENGINE_SLEEPING MerCapSleeping), - (simpleEvent EVENT_MER_CALLING_MAIN MerCallingMain) - - ] - -perfParsers :: [EventParser EventInfo] -perfParsers = [ - (VariableSizeParser EVENT_PERF_NAME (do -- (perf_num, name) - num <- get :: Get Word16 - perfNum <- get - name <- getString (num - sz_perf_num) - return PerfName{perfNum, name} - )), - - (FixedSizeParser EVENT_PERF_COUNTER (sz_perf_num + sz_kernel_tid + 8) (do -- (perf_num, tid, period) - perfNum <- get - tid <- get - period <- get - return PerfCounter{perfNum, tid, period} - )), - - (FixedSizeParser EVENT_PERF_TRACEPOINT (sz_perf_num + sz_kernel_tid) (do -- (perf_num, tid) - perfNum <- get - tid <- get - return PerfTracepoint{perfNum, tid} - )) - ] - -- ----------------------------------------------------------------------------- -- Utilities @@ -1090,512 +382,3 @@ buildEvent' Event {..} = UnknownEvent{ ref=ref } -> "Unknown Event (ref: " <> BB.word16Dec ref <> ")" _ -> buildEventInfo evSpec - -type PutEvents a = PutM a - -putE :: Binary a => a -> PutEvents () -putE = put - -putType :: EventTypeNum -> PutEvents () -putType = putE - -putCap :: Int -> PutEvents () -putCap c = putE (fromIntegral c :: CapNo) - -putMarker :: Word32 -> PutEvents () -putMarker = putE - -putEStr :: String -> PutEvents () -putEStr = mapM_ putE - -putEventLog :: EventLog -> PutEvents () -putEventLog (EventLog hdr es) = do - putHeader hdr - putData es - -putHeader :: Header -> PutEvents () -putHeader (Header ets) = do - putMarker EVENT_HEADER_BEGIN - putMarker EVENT_HET_BEGIN - mapM_ putEventType ets - putMarker EVENT_HET_END - putMarker EVENT_HEADER_END - where - putEventType (EventType n d msz) = do - putMarker EVENT_ET_BEGIN - putType n - putE $ fromMaybe 0xffff msz - putE (fromIntegral $ length d :: EventTypeDescLen) - mapM_ put d - -- the event type header allows for extra data, which we don't use: - putE (0 :: Word32) - putMarker EVENT_ET_END - -putData :: Data -> PutEvents () -putData (Data es) = do - putMarker EVENT_DATA_BEGIN -- Word32 - mapM_ putEvent es - putType EVENT_DATA_END -- Word16 - -eventTypeNum :: EventInfo -> EventTypeNum -eventTypeNum e = case e of - CreateThread {} -> EVENT_CREATE_THREAD - RunThread {} -> EVENT_RUN_THREAD - StopThread {} -> EVENT_STOP_THREAD - ThreadRunnable {} -> EVENT_THREAD_RUNNABLE - MigrateThread {} -> EVENT_MIGRATE_THREAD - Shutdown {} -> EVENT_SHUTDOWN - WakeupThread {} -> EVENT_THREAD_WAKEUP - ThreadLabel {} -> EVENT_THREAD_LABEL - StartGC {} -> EVENT_GC_START - EndGC {} -> EVENT_GC_END - GlobalSyncGC {} -> EVENT_GC_GLOBAL_SYNC - RequestSeqGC {} -> EVENT_REQUEST_SEQ_GC - RequestParGC {} -> EVENT_REQUEST_PAR_GC - CreateSparkThread {} -> EVENT_CREATE_SPARK_THREAD - SparkCounters {} -> EVENT_SPARK_COUNTERS - SparkCreate {} -> EVENT_SPARK_CREATE - SparkDud {} -> EVENT_SPARK_DUD - SparkOverflow {} -> EVENT_SPARK_OVERFLOW - SparkRun {} -> EVENT_SPARK_RUN - SparkSteal {} -> EVENT_SPARK_STEAL - SparkFizzle {} -> EVENT_SPARK_FIZZLE - SparkGC {} -> EVENT_SPARK_GC - TaskCreate {} -> EVENT_TASK_CREATE - TaskMigrate {} -> EVENT_TASK_MIGRATE - TaskDelete {} -> EVENT_TASK_DELETE - Message {} -> EVENT_LOG_MSG - Startup {} -> EVENT_STARTUP - EventBlock {} -> EVENT_BLOCK_MARKER - UserMessage {} -> EVENT_USER_MSG - UserMarker {} -> EVENT_USER_MARKER - GCIdle {} -> EVENT_GC_IDLE - GCWork {} -> EVENT_GC_WORK - GCDone {} -> EVENT_GC_DONE - GCStatsGHC{} -> EVENT_GC_STATS_GHC - HeapAllocated{} -> EVENT_HEAP_ALLOCATED - HeapSize{} -> EVENT_HEAP_SIZE - HeapLive{} -> EVENT_HEAP_LIVE - HeapInfoGHC{} -> EVENT_HEAP_INFO_GHC - CapCreate{} -> EVENT_CAP_CREATE - CapDelete{} -> EVENT_CAP_DELETE - CapDisable{} -> EVENT_CAP_DISABLE - CapEnable{} -> EVENT_CAP_ENABLE - CapsetCreate {} -> EVENT_CAPSET_CREATE - CapsetDelete {} -> EVENT_CAPSET_DELETE - CapsetAssignCap {} -> EVENT_CAPSET_ASSIGN_CAP - CapsetRemoveCap {} -> EVENT_CAPSET_REMOVE_CAP - RtsIdentifier {} -> EVENT_RTS_IDENTIFIER - ProgramArgs {} -> EVENT_PROGRAM_ARGS - ProgramEnv {} -> EVENT_PROGRAM_ENV - OsProcessPid {} -> EVENT_OSPROCESS_PID - OsProcessParentPid{} -> EVENT_OSPROCESS_PPID - WallClockTime{} -> EVENT_WALL_CLOCK_TIME - UnknownEvent {} -> error "eventTypeNum UnknownEvent" - InternString {} -> EVENT_INTERN_STRING - Version {} -> EVENT_VERSION - ProgramInvocation {} -> EVENT_PROGRAM_INVOCATION - EdenStartReceive {} -> EVENT_EDEN_START_RECEIVE - EdenEndReceive {} -> EVENT_EDEN_END_RECEIVE - CreateProcess {} -> EVENT_CREATE_PROCESS - KillProcess {} -> EVENT_KILL_PROCESS - AssignThreadToProcess {} -> EVENT_ASSIGN_THREAD_TO_PROCESS - CreateMachine {} -> EVENT_CREATE_MACHINE - KillMachine {} -> EVENT_KILL_MACHINE - SendMessage {} -> EVENT_SEND_MESSAGE - ReceiveMessage {} -> EVENT_RECEIVE_MESSAGE - SendReceiveLocalMessage {} -> EVENT_SEND_RECEIVE_LOCAL_MESSAGE - MerStartParConjunction {} -> EVENT_MER_START_PAR_CONJUNCTION - MerEndParConjunction _ -> EVENT_MER_STOP_PAR_CONJUNCTION - MerEndParConjunct _ -> EVENT_MER_STOP_PAR_CONJUNCT - MerCreateSpark {} -> EVENT_MER_CREATE_SPARK - MerFutureCreate {} -> EVENT_MER_FUT_CREATE - MerFutureWaitNosuspend _ -> EVENT_MER_FUT_WAIT_NOSUSPEND - MerFutureWaitSuspended _ -> EVENT_MER_FUT_WAIT_SUSPENDED - MerFutureSignal _ -> EVENT_MER_FUT_SIGNAL - MerLookingForGlobalThread -> EVENT_MER_LOOKING_FOR_GLOBAL_CONTEXT - MerWorkStealing -> EVENT_MER_WORK_STEALING - MerLookingForLocalSpark -> EVENT_MER_LOOKING_FOR_LOCAL_SPARK - MerReleaseThread _ -> EVENT_MER_RELEASE_CONTEXT - MerCapSleeping -> EVENT_MER_ENGINE_SLEEPING - MerCallingMain -> EVENT_MER_CALLING_MAIN - PerfName {} -> nEVENT_PERF_NAME - PerfCounter {} -> nEVENT_PERF_COUNTER - PerfTracepoint {} -> nEVENT_PERF_TRACEPOINT - -nEVENT_PERF_NAME, nEVENT_PERF_COUNTER, nEVENT_PERF_TRACEPOINT :: EventTypeNum -nEVENT_PERF_NAME = EVENT_PERF_NAME -nEVENT_PERF_COUNTER = EVENT_PERF_COUNTER -nEVENT_PERF_TRACEPOINT = EVENT_PERF_TRACEPOINT - -putEvent :: Event -> PutEvents () -putEvent Event {..} = do - putType (eventTypeNum evSpec) - put evTime - putEventSpec evSpec - -putEventSpec :: EventInfo -> PutEvents () -putEventSpec (Startup caps) = do - putCap (fromIntegral caps) - -putEventSpec (EventBlock end cap sz) = do - putE (fromIntegral (sz+24) :: BlockSize) - putE end - putE (fromIntegral cap :: CapNo) - -putEventSpec (CreateThread t) = - putE t - -putEventSpec (RunThread t) = - putE t - --- here we assume that ThreadStopStatus fromEnum matches the definitions in --- EventLogFormat.h --- The standard encoding is used here, which is wrong for eventlogs --- produced by GHC-7.8.2 ([Stop status in GHC-7.8.2] in EventTypes.hs -putEventSpec (StopThread t s) = do - putE t - putE $ case s of - NoStatus -> 0 :: Word16 - HeapOverflow -> 1 - StackOverflow -> 2 - ThreadYielding -> 3 - ThreadBlocked -> 4 - ThreadFinished -> 5 - ForeignCall -> 6 - BlockedOnMVar -> 7 - BlockedOnMVarRead -> 20 -- since GHC-7.8.3 - BlockedOnBlackHole -> 8 - BlockedOnBlackHoleOwnedBy _ -> 8 - BlockedOnRead -> 9 - BlockedOnWrite -> 10 - BlockedOnDelay -> 11 - BlockedOnSTM -> 12 - BlockedOnDoProc -> 13 - BlockedOnCCall -> 14 - BlockedOnCCall_NoUnblockExc -> 15 - BlockedOnMsgThrowTo -> 16 - ThreadMigrating -> 17 - BlockedOnMsgGlobalise -> 18 - putE $ case s of - BlockedOnBlackHoleOwnedBy i -> i - _ -> 0 - -putEventSpec (ThreadRunnable t) = - putE t - -putEventSpec (MigrateThread t c) = do - putE t - putCap c - -putEventSpec (CreateSparkThread t) = - putE t - -putEventSpec (SparkCounters crt dud ovf cnv fiz gcd rem) = do - putE crt - putE dud - putE ovf - putE cnv - -- Warning: order of fiz and gcd reversed! - putE gcd - putE fiz - putE rem - -putEventSpec SparkCreate = - return () - -putEventSpec SparkDud = - return () - -putEventSpec SparkOverflow = - return () - -putEventSpec SparkRun = - return () - -putEventSpec (SparkSteal c) = - putCap c - -putEventSpec SparkFizzle = - return () - -putEventSpec SparkGC = - return () - -putEventSpec (WakeupThread t c) = do - putE t - putCap c - -putEventSpec (ThreadLabel t l) = do - putE (fromIntegral (length l) + sz_tid :: Word16) - putE t - putEStr l - -putEventSpec Shutdown = - return () - -putEventSpec RequestSeqGC = - return () - -putEventSpec RequestParGC = - return () - -putEventSpec StartGC = - return () - -putEventSpec GCWork = - return () - -putEventSpec GCIdle = - return () - -putEventSpec GCDone = - return () - -putEventSpec EndGC = - return () - -putEventSpec GlobalSyncGC = - return () - -putEventSpec (TaskCreate taskId cap tid) = do - putE taskId - putCap cap - putE tid - -putEventSpec (TaskMigrate taskId cap new_cap) = do - putE taskId - putCap cap - putCap new_cap - -putEventSpec (TaskDelete taskId) = - putE taskId - -putEventSpec GCStatsGHC{..} = do - putE heapCapset - putE (fromIntegral gen :: Word16) - putE copied - putE slop - putE frag - putE (fromIntegral parNThreads :: Word32) - putE parMaxCopied - putE parTotCopied - -putEventSpec HeapAllocated{..} = do - putE heapCapset - putE allocBytes - -putEventSpec HeapSize{..} = do - putE heapCapset - putE sizeBytes - -putEventSpec HeapLive{..} = do - putE heapCapset - putE liveBytes - -putEventSpec HeapInfoGHC{..} = do - putE heapCapset - putE (fromIntegral gens :: Word16) - putE maxHeapSize - putE allocAreaSize - putE mblockSize - putE blockSize - -putEventSpec CapCreate{cap} = - putCap cap - -putEventSpec CapDelete{cap} = - putCap cap - -putEventSpec CapDisable{cap} = - putCap cap - -putEventSpec CapEnable{cap} = - putCap cap - -putEventSpec (CapsetCreate cs ct) = do - putE cs - putE $ case ct of - CapsetCustom -> 1 :: Word16 - CapsetOsProcess -> 2 - CapsetClockDomain -> 3 - CapsetUnknown -> 0 - -putEventSpec (CapsetDelete cs) = - putE cs - -putEventSpec (CapsetAssignCap cs cp) = do - putE cs - putCap cp - -putEventSpec (CapsetRemoveCap cs cp) = do - putE cs - putCap cp - -putEventSpec (RtsIdentifier cs rts) = do - putE (fromIntegral (length rts) + sz_capset :: Word16) - putE cs - putEStr rts - -putEventSpec (ProgramArgs cs as) = do - let as' = unsep as - putE (fromIntegral (length as') + sz_capset :: Word16) - putE cs - mapM_ putE as' - -putEventSpec (ProgramEnv cs es) = do - let es' = unsep es - putE (fromIntegral (length es') + sz_capset :: Word16) - putE cs - mapM_ putE es' - -putEventSpec (OsProcessPid cs pid) = do - putE cs - putE pid - -putEventSpec (OsProcessParentPid cs ppid) = do - putE cs - putE ppid - -putEventSpec (WallClockTime cs sec nsec) = do - putE cs - putE sec - putE nsec - -putEventSpec (Message s) = do - putE (fromIntegral (length s) :: Word16) - mapM_ putE s - -putEventSpec (UserMessage s) = do - putE (fromIntegral (length s) :: Word16) - mapM_ putE s - -putEventSpec (UserMarker s) = do - putE (fromIntegral (length s) :: Word16) - mapM_ putE s - -putEventSpec (UnknownEvent {}) = error "putEventSpec UnknownEvent" - -putEventSpec (InternString str id) = do - putE len - mapM_ putE str - putE id - where len = (fromIntegral (length str) :: Word16) + sz_string_id - -putEventSpec (Version s) = do - putE (fromIntegral (length s) :: Word16) - mapM_ putE s - -putEventSpec (ProgramInvocation s) = do - putE (fromIntegral (length s) :: Word16) - mapM_ putE s - -putEventSpec ( EdenStartReceive ) = return () - -putEventSpec ( EdenEndReceive ) = return () - -putEventSpec ( CreateProcess process ) = do - putE process - -putEventSpec ( KillProcess process ) = do - putE process - -putEventSpec ( AssignThreadToProcess thread process ) = do - putE thread - putE process - -putEventSpec ( CreateMachine machine realtime ) = do - putE machine - putE realtime - -putEventSpec ( KillMachine machine ) = do - putE machine - -putEventSpec ( SendMessage mesTag senderProcess senderThread - receiverMachine receiverProcess receiverInport ) = do - putE (fromMsgTag mesTag) - putE senderProcess - putE senderThread - putE receiverMachine - putE receiverProcess - putE receiverInport - -putEventSpec ( ReceiveMessage mesTag receiverProcess receiverInport - senderMachine senderProcess senderThread messageSize ) = do - putE (fromMsgTag mesTag) - putE receiverProcess - putE receiverInport - putE senderMachine - putE senderProcess - putE senderThread - putE messageSize - -putEventSpec ( SendReceiveLocalMessage mesTag senderProcess senderThread - receiverProcess receiverInport ) = do - putE (fromMsgTag mesTag) - putE senderProcess - putE senderThread - putE receiverProcess - putE receiverInport - -putEventSpec (MerStartParConjunction dyn_id static_id) = do - putE dyn_id - putE static_id - -putEventSpec (MerEndParConjunction dyn_id) = - putE dyn_id - -putEventSpec (MerEndParConjunct dyn_id) = - putE dyn_id - -putEventSpec (MerCreateSpark dyn_id spark_id) = do - putE dyn_id - putE spark_id - -putEventSpec (MerFutureCreate future_id name_id) = do - putE future_id - putE name_id - -putEventSpec (MerFutureWaitNosuspend future_id) = - putE future_id - -putEventSpec (MerFutureWaitSuspended future_id) = - putE future_id - -putEventSpec (MerFutureSignal future_id) = - putE future_id - -putEventSpec MerLookingForGlobalThread = return () -putEventSpec MerWorkStealing = return () -putEventSpec MerLookingForLocalSpark = return () - -putEventSpec (MerReleaseThread thread_id) = - putE thread_id - -putEventSpec MerCapSleeping = return () -putEventSpec MerCallingMain = return () - -putEventSpec PerfName{..} = do - putE (fromIntegral (length name) + sz_perf_num :: Word16) - putE perfNum - mapM_ putE name - -putEventSpec PerfCounter{..} = do - putE perfNum - putE tid - putE period - -putEventSpec PerfTracepoint{..} = do - putE perfNum - putE tid - --- [] == [] --- [x] == x\0 --- [x, y, z] == x\0y\0 -unsep :: [String] -> String -unsep = concatMap (++"\0") -- not the most efficient, but should be ok - -splitNull :: String -> [String] -splitNull [] = [] -splitNull xs = case span (/= '\0') xs of - (x, xs') -> x : splitNull (drop 1 xs') diff --git a/src/GHC/RTS/Events/Binary.hs b/src/GHC/RTS/Events/Binary.hs new file mode 100644 index 0000000..e2be5b4 --- /dev/null +++ b/src/GHC/RTS/Events/Binary.hs @@ -0,0 +1,1228 @@ +{-# LANGUAGE CPP #-} +module GHC.RTS.Events.Binary + ( -- * Readers + getHeader + , getEvent + , standardParsers + , ghc6Parsers + , ghc7Parsers + , mercuryParsers + , perfParsers + , pre77StopParsers + , ghc782StopParser + , post782StopParser + , parRTSParsers + + -- * Writers + , putEventLog + , putHeader + , putEvent + + -- * Perf events + , nEVENT_PERF_NAME + , nEVENT_PERF_COUNTER + , nEVENT_PERF_TRACEPOINT + + ) where +import Control.Monad +import Data.Maybe +import Prelude hiding (gcd, rem, id) + +import Data.Array +import Data.Binary +import Data.Binary.Put +import qualified Data.Binary.Get as G + +import GHC.RTS.EventTypes +import GHC.RTS.EventParserUtils + +#define EVENTLOG_CONSTANTS_ONLY +#include "EventLogFormat.h" + +getEventType :: Get EventType +getEventType = do + etNum <- get + size <- get :: Get EventTypeSize + let etSize = if size == 0xffff then Nothing else Just size + -- 0xffff indicates variable-sized event + etDescLen <- get :: Get EventTypeDescLen + etDesc <- getEtDesc (fromIntegral etDescLen) + etExtraLen <- get :: Get Word32 + G.skip (fromIntegral etExtraLen) + ete <- get :: Get Marker + when (ete /= EVENT_ET_END) $ + fail "Event Type end marker not found." + return (EventType etNum etDesc etSize) + where + getEtDesc :: Int -> Get [Char] + getEtDesc s = replicateM s (get :: Get Char) + +getHeader :: Get Header +getHeader = do + hdrb <- get :: Get Marker + when (hdrb /= EVENT_HEADER_BEGIN) $ + fail "Header begin marker not found" + hetm <- get :: Get Marker + when (hetm /= EVENT_HET_BEGIN) $ + fail "Header Event Type begin marker not found" + ets <- getEventTypes + emark <- get :: Get Marker + when (emark /= EVENT_HEADER_END) $ + fail "Header end marker not found" + db <- get :: Get Marker + when (db /= EVENT_DATA_BEGIN) $ + fail "My Data begin marker not found" + return $ Header ets + where + getEventTypes :: Get [EventType] + getEventTypes = do + m <- get :: Get Marker + case m of + EVENT_ET_BEGIN -> do + et <- getEventType + nextET <- getEventTypes + return (et : nextET) + EVENT_HET_END -> + return [] + _ -> + fail "Malformed list of Event Types in header" + +getEvent :: EventParsers -> Get (Maybe Event) +getEvent (EventParsers parsers) = do + etRef <- get :: Get EventTypeNum + if etRef == EVENT_DATA_END + then return Nothing + else do !evTime <- get + evSpec <- parsers ! fromIntegral etRef + return $ Just Event { evCap = undefined, .. } + +-- +-- standardEventParsers. +-- +standardParsers :: [EventParser EventInfo] +standardParsers = [ + (FixedSizeParser EVENT_STARTUP sz_cap (do -- (n_caps) + c <- get :: Get CapNo + return Startup{ n_caps = fromIntegral c } + )), + + (FixedSizeParser EVENT_BLOCK_MARKER (sz_block_size + sz_time + sz_cap) (do -- (size, end_time, cap) + block_size <- get :: Get BlockSize + end_time <- get :: Get Timestamp + c <- get :: Get CapNo + return EventBlock { end_time = end_time, + cap = fromIntegral c, + block_size = ((fromIntegral block_size) - + (fromIntegral sz_block_event)) + } + )), + + -- EVENT_SHUTDOWN is replaced by EVENT_CAP_DELETE and GHC 7.6+ + -- no longer generate the event; should be removed at some point + (simpleEvent EVENT_SHUTDOWN Shutdown), + + (simpleEvent EVENT_REQUEST_SEQ_GC RequestSeqGC), + + (simpleEvent EVENT_REQUEST_PAR_GC RequestParGC), + + (simpleEvent EVENT_GC_START StartGC), + + (simpleEvent EVENT_GC_WORK GCWork), + + (simpleEvent EVENT_GC_IDLE GCIdle), + + (simpleEvent EVENT_GC_DONE GCDone), + + (simpleEvent EVENT_GC_END EndGC), + + (simpleEvent EVENT_GC_GLOBAL_SYNC GlobalSyncGC), + + (FixedSizeParser EVENT_GC_STATS_GHC (sz_capset + 2 + 5*8 + 4) (do -- (heap_capset, generation, copied_bytes, slop_bytes, frag_bytes, par_n_threads, par_max_copied, par_tot_copied) + heapCapset <- get + gen <- get :: Get Word16 + copied <- get :: Get Word64 + slop <- get :: Get Word64 + frag <- get :: Get Word64 + parNThreads <- get :: Get Word32 + parMaxCopied <- get :: Get Word64 + parTotCopied <- get :: Get Word64 + return GCStatsGHC{ gen = fromIntegral gen + , parNThreads = fromIntegral parNThreads + , ..} + )), + + (FixedSizeParser EVENT_HEAP_ALLOCATED (sz_capset + 8) (do -- (heap_capset, alloc_bytes) + heapCapset <- get + allocBytes <- get + return HeapAllocated{..} + )), + + (FixedSizeParser EVENT_HEAP_SIZE (sz_capset + 8) (do -- (heap_capset, size_bytes) + heapCapset <- get + sizeBytes <- get + return HeapSize{..} + )), + + (FixedSizeParser EVENT_HEAP_LIVE (sz_capset + 8) (do -- (heap_capset, live_bytes) + heapCapset <- get + liveBytes <- get + return HeapLive{..} + )), + + (FixedSizeParser EVENT_HEAP_INFO_GHC (sz_capset + 2 + 4*8) (do -- (heap_capset, n_generations, max_heap_size, alloc_area_size, mblock_size, block_size) + heapCapset <- get + gens <- get :: Get Word16 + maxHeapSize <- get :: Get Word64 + allocAreaSize <- get :: Get Word64 + mblockSize <- get :: Get Word64 + blockSize <- get :: Get Word64 + return HeapInfoGHC{gens = fromIntegral gens, ..} + )), + + (FixedSizeParser EVENT_CAP_CREATE (sz_cap) (do -- (cap) + cap <- get :: Get CapNo + return CapCreate{cap = fromIntegral cap} + )), + + (FixedSizeParser EVENT_CAP_DELETE (sz_cap) (do -- (cap) + cap <- get :: Get CapNo + return CapDelete{cap = fromIntegral cap} + )), + + (FixedSizeParser EVENT_CAP_DISABLE (sz_cap) (do -- (cap) + cap <- get :: Get CapNo + return CapDisable{cap = fromIntegral cap} + )), + + (FixedSizeParser EVENT_CAP_ENABLE (sz_cap) (do -- (cap) + cap <- get :: Get CapNo + return CapEnable{cap = fromIntegral cap} + )), + + (FixedSizeParser EVENT_CAPSET_CREATE (sz_capset + sz_capset_type) (do -- (capset, capset_type) + cs <- get + ct <- fmap mkCapsetType get + return CapsetCreate{capset=cs,capsetType=ct} + )), + + (FixedSizeParser EVENT_CAPSET_DELETE sz_capset (do -- (capset) + cs <- get + return CapsetDelete{capset=cs} + )), + + (FixedSizeParser EVENT_CAPSET_ASSIGN_CAP (sz_capset + sz_cap) (do -- (capset, cap) + cs <- get + cp <- get :: Get CapNo + return CapsetAssignCap{capset=cs,cap=fromIntegral cp} + )), + + (FixedSizeParser EVENT_CAPSET_REMOVE_CAP (sz_capset + sz_cap) (do -- (capset, cap) + cs <- get + cp <- get :: Get CapNo + return CapsetRemoveCap{capset=cs,cap=fromIntegral cp} + )), + + (FixedSizeParser EVENT_OSPROCESS_PID (sz_capset + sz_pid) (do -- (capset, pid) + cs <- get + pd <- get + return OsProcessPid{capset=cs,pid=pd} + )), + + (FixedSizeParser EVENT_OSPROCESS_PPID (sz_capset + sz_pid) (do -- (capset, ppid) + cs <- get + pd <- get + return OsProcessParentPid{capset=cs,ppid=pd} + )), + + (FixedSizeParser EVENT_WALL_CLOCK_TIME (sz_capset + 8 + 4) (do -- (capset, unix_epoch_seconds, nanoseconds) + cs <- get + s <- get + ns <- get + return WallClockTime{capset=cs,sec=s,nsec=ns} + )), + + (VariableSizeParser EVENT_LOG_MSG (do -- (msg) + num <- get :: Get Word16 + string <- getString num + return Message{ msg = string } + )), + (VariableSizeParser EVENT_USER_MSG (do -- (msg) + num <- get :: Get Word16 + string <- getString num + return UserMessage{ msg = string } + )), + (VariableSizeParser EVENT_USER_MARKER (do -- (markername) + num <- get :: Get Word16 + string <- getString num + return UserMarker{ markername = string } + )), + (VariableSizeParser EVENT_PROGRAM_ARGS (do -- (capset, [arg]) + num <- get :: Get Word16 + cs <- get + string <- getString (num - sz_capset) + return ProgramArgs{ capset = cs + , args = splitNull string } + )), + (VariableSizeParser EVENT_PROGRAM_ENV (do -- (capset, [arg]) + num <- get :: Get Word16 + cs <- get + string <- getString (num - sz_capset) + return ProgramEnv{ capset = cs + , env = splitNull string } + )), + (VariableSizeParser EVENT_RTS_IDENTIFIER (do -- (capset, str) + num <- get :: Get Word16 + cs <- get + string <- getString (num - sz_capset) + return RtsIdentifier{ capset = cs + , rtsident = string } + )), + + (VariableSizeParser EVENT_INTERN_STRING (do -- (str, id) + num <- get :: Get Word16 + string <- getString (num - sz_string_id) + sId <- get :: Get StringId + return (InternString string sId) + )), + + (VariableSizeParser EVENT_THREAD_LABEL (do -- (thread, str) + num <- get :: Get Word16 + tid <- get + str <- getString (num - sz_tid) + return ThreadLabel{ thread = tid + , threadlabel = str } + )) + ] + +-- Parsers valid for GHC7 but not GHC6. +ghc7Parsers :: [EventParser EventInfo] +ghc7Parsers = [ + (FixedSizeParser EVENT_CREATE_THREAD sz_tid (do -- (thread) + t <- get + return CreateThread{thread=t} + )), + + (FixedSizeParser EVENT_RUN_THREAD sz_tid (do -- (thread) + t <- get + return RunThread{thread=t} + )), + + (FixedSizeParser EVENT_THREAD_RUNNABLE sz_tid (do -- (thread) + t <- get + return ThreadRunnable{thread=t} + )), + + (FixedSizeParser EVENT_MIGRATE_THREAD (sz_tid + sz_cap) (do -- (thread, newCap) + t <- get + nc <- get :: Get CapNo + return MigrateThread{thread=t,newCap=fromIntegral nc} + )), + + -- Yes, EVENT_RUN/STEAL_SPARK are deprecated, but see the explanation in the + -- 'ghc6Parsers' section below. Since we're parsing them anyway, we might + -- as well convert them to the new SparkRun/SparkSteal events. + (FixedSizeParser EVENT_RUN_SPARK sz_tid (do -- (thread) + _ <- get :: Get ThreadId + return SparkRun + )), + + (FixedSizeParser EVENT_STEAL_SPARK (sz_tid + sz_cap) (do -- (thread, victimCap) + _ <- get :: Get ThreadId + vc <- get :: Get CapNo + return SparkSteal{victimCap=fromIntegral vc} + )), + + (FixedSizeParser EVENT_CREATE_SPARK_THREAD sz_tid (do -- (sparkThread) + st <- get :: Get ThreadId + return CreateSparkThread{sparkThread=st} + )), + + (FixedSizeParser EVENT_SPARK_COUNTERS (7*8) (do -- (crt,dud,ovf,cnv,gcd,fiz,rem) + crt <- get :: Get Word64 + dud <- get :: Get Word64 + ovf <- get :: Get Word64 + cnv <- get :: Get Word64 + gcd <- get :: Get Word64 + fiz <- get :: Get Word64 + rem <- get :: Get Word64 + return SparkCounters{sparksCreated = crt, sparksDud = dud, + sparksOverflowed = ovf, sparksConverted = cnv, + -- Warning: order of fiz and gcd reversed! + sparksFizzled = fiz, sparksGCd = gcd, + sparksRemaining = rem} + )), + + (simpleEvent EVENT_SPARK_CREATE SparkCreate), + (simpleEvent EVENT_SPARK_DUD SparkDud), + (simpleEvent EVENT_SPARK_OVERFLOW SparkOverflow), + (simpleEvent EVENT_SPARK_RUN SparkRun), + (FixedSizeParser EVENT_SPARK_STEAL sz_cap (do -- (victimCap) + vc <- get :: Get CapNo + return SparkSteal{victimCap=fromIntegral vc} + )), + (simpleEvent EVENT_SPARK_FIZZLE SparkFizzle), + (simpleEvent EVENT_SPARK_GC SparkGC), + + (FixedSizeParser EVENT_TASK_CREATE (sz_taskid + sz_cap + sz_kernel_tid) (do -- (taskID, cap, tid) + taskId <- get :: Get TaskId + cap <- get :: Get CapNo + tid <- get :: Get KernelThreadId + return TaskCreate{ taskId, cap = fromIntegral cap, tid } + )), + (FixedSizeParser EVENT_TASK_MIGRATE (sz_taskid + sz_cap*2) (do -- (taskID, cap, new_cap) + taskId <- get :: Get TaskId + cap <- get :: Get CapNo + new_cap <- get :: Get CapNo + return TaskMigrate{ taskId, cap = fromIntegral cap + , new_cap = fromIntegral new_cap + } + )), + (FixedSizeParser EVENT_TASK_DELETE (sz_taskid) (do -- (taskID) + taskId <- get :: Get TaskId + return TaskDelete{ taskId } + )), + + (FixedSizeParser EVENT_THREAD_WAKEUP (sz_tid + sz_cap) (do -- (thread, other_cap) + t <- get + oc <- get :: Get CapNo + return WakeupThread{thread=t,otherCap=fromIntegral oc} + )) + ] + +-- special thread stop event parsers for GHC version 7.8.2 +-- see [Stop status in GHC-7.8.2] in EventTypes.hs +ghc782StopParser :: EventParser EventInfo +ghc782StopParser = + (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) (do + -- (thread, status, info) + t <- get + s <- get :: Get RawThreadStopStatus + i <- get :: Get ThreadId + return StopThread{thread = t, + status = case () of + _ | s > maxThreadStopStatus782 + -> NoStatus + | s == 9 {- XXX yeuch -} + -- GHC-7.8.2: 9 == BlockedOnBlackHole + -> BlockedOnBlackHoleOwnedBy i + | otherwise + -> mkStopStatus782 s} + )) + +-- parsers for GHC < 7.8.2. Older versions do not use block info +-- (different length). See [Stop status in GHC-7.8.2] in +-- EventTypes.hs +pre77StopParsers :: [EventParser EventInfo] +pre77StopParsers = [ + (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status) (do + -- (thread, status) + t <- get + s <- get :: Get RawThreadStopStatus + return StopThread{thread=t, status = if s > maxThreadStopStatusPre77 + then NoStatus + else mkStopStatus s} + -- older version of the event, no block info + )), + + (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) + (do + -- (thread, status, info) + t <- get + s <- get :: Get RawThreadStopStatus + i <- get :: Get ThreadId + return StopThread{thread = t, + status = case () of + _ | s > maxThreadStopStatusPre77 + -> NoStatus + | s == 8 {- XXX yeuch -} + -- pre-7.7: 8==BlockedOnBlackhole + -> BlockedOnBlackHoleOwnedBy i + | otherwise + -> mkStopStatus s} + )) + ] + +-- parsers for GHC >= 7.8.3, always using block info field parser. +-- See [Stop status in GHC-7.8.2] in EventTypes.hs +post782StopParser :: EventParser EventInfo +post782StopParser = + (FixedSizeParser EVENT_STOP_THREAD (sz_tid + sz_th_stop_status + sz_tid) + (do + -- (thread, status, info) + t <- get + s <- get :: Get RawThreadStopStatus + i <- get :: Get ThreadId + return StopThread{thread = t, + status = case () of + _ | s > maxThreadStopStatus + -> NoStatus + | s == 8 {- XXX yeuch -} + -- post-7.8.2: 8==BlockedOnBlackhole + -> BlockedOnBlackHoleOwnedBy i + | otherwise + -> mkStopStatus s} + )) + + ----------------------- + -- GHC 6.12 compat: GHC 6.12 reported the wrong sizes for some events, + -- so we have to recognise those wrong sizes here for backwards + -- compatibility. +ghc6Parsers :: [EventParser EventInfo] +ghc6Parsers = [ + (FixedSizeParser EVENT_STARTUP 0 (do + -- BUG in GHC 6.12: the startup event was incorrectly + -- declared as size 0, so we accept it here. + c <- get :: Get CapNo + return Startup{ n_caps = fromIntegral c } + )), + + (FixedSizeParser EVENT_CREATE_THREAD sz_old_tid (do -- (thread) + t <- get + return CreateThread{thread=t} + )), + + (FixedSizeParser EVENT_RUN_THREAD sz_old_tid (do -- (thread) + t <- get + return RunThread{thread=t} + )), + + (FixedSizeParser EVENT_STOP_THREAD (sz_old_tid + 2) (do -- (thread, status) + t <- get + s <- get :: Get RawThreadStopStatus + return StopThread{thread=t, status = if s > maxThreadStopStatusPre77 + then NoStatus + else mkStopStatus s} + -- older version of the event uses pre-77 encoding + -- (actually, it only uses encodings 0 to 5) + -- see [Stop status in GHC-7.8.2] in EventTypes.hs + )), + + (FixedSizeParser EVENT_THREAD_RUNNABLE sz_old_tid (do -- (thread) + t <- get + return ThreadRunnable{thread=t} + )), + + (FixedSizeParser EVENT_MIGRATE_THREAD (sz_old_tid + sz_cap) (do -- (thread, newCap) + t <- get + nc <- get :: Get CapNo + return MigrateThread{thread=t,newCap=fromIntegral nc} + )), + + -- Note: it is vital that these two (EVENT_RUN/STEAL_SPARK) remain here (at + -- least in the ghc6Parsers section) even though both events are deprecated. + -- The reason is that .eventlog files created by the buggy GHC-6.12 + -- mis-declare the size of these two events. So we have to handle them + -- specially here otherwise we'll get the wrong size, leading to us getting + -- out of sync and eventual parse failure. Since we're parsing them anyway, + -- we might as well convert them to the new SparkRun/SparkSteal events. + (FixedSizeParser EVENT_RUN_SPARK sz_old_tid (do -- (thread) + _ <- get :: Get ThreadId + return SparkRun + )), + + (FixedSizeParser EVENT_STEAL_SPARK (sz_old_tid + sz_cap) (do -- (thread, victimCap) + _ <- get :: Get ThreadId + vc <- get :: Get CapNo + return SparkSteal{victimCap=fromIntegral vc} + )), + + (FixedSizeParser EVENT_CREATE_SPARK_THREAD sz_old_tid (do -- (sparkThread) + st <- get :: Get ThreadId + return CreateSparkThread{sparkThread=st} + )), + + (FixedSizeParser EVENT_THREAD_WAKEUP (sz_old_tid + sz_cap) (do -- (thread, other_cap) + t <- get + oc <- get :: Get CapNo + return WakeupThread{thread=t,otherCap=fromIntegral oc} + )) + ] + +-- Parsers for parallel events. Parameter is the thread_id size, to create +-- ghc6-parsers (using the wrong size) where necessary. +parRTSParsers :: EventTypeSize -> [EventParser EventInfo] +parRTSParsers sz_tid' = [ + (VariableSizeParser EVENT_VERSION (do -- (version) + num <- get :: Get Word16 + string <- getString num + return Version{ version = string } + )), + + (VariableSizeParser EVENT_PROGRAM_INVOCATION (do -- (cmd. line) + num <- get :: Get Word16 + string <- getString num + return ProgramInvocation{ commandline = string } + )), + + (simpleEvent EVENT_EDEN_START_RECEIVE EdenStartReceive), + (simpleEvent EVENT_EDEN_END_RECEIVE EdenEndReceive), + + (FixedSizeParser EVENT_CREATE_PROCESS sz_procid + (do p <- get + return CreateProcess{ process = p }) + ), + + (FixedSizeParser EVENT_KILL_PROCESS sz_procid + (do p <- get + return KillProcess{ process = p }) + ), + + (FixedSizeParser EVENT_ASSIGN_THREAD_TO_PROCESS (sz_tid' + sz_procid) + (do t <- get + p <- get + return AssignThreadToProcess { thread = t, process = p }) + ), + + (FixedSizeParser EVENT_CREATE_MACHINE (sz_mid + sz_realtime) + (do m <- get + t <- get + return CreateMachine { machine = m, realtime = t }) + ), + + (FixedSizeParser EVENT_KILL_MACHINE sz_mid + (do m <- get :: Get MachineId + return KillMachine { machine = m }) + ), + + (FixedSizeParser EVENT_SEND_MESSAGE + (sz_msgtag + 2*sz_procid + 2*sz_tid' + sz_mid) + (do tag <- get :: Get RawMsgTag + sP <- get :: Get ProcessId + sT <- get :: Get ThreadId + rM <- get :: Get MachineId + rP <- get :: Get ProcessId + rIP <- get :: Get PortId + return SendMessage { mesTag = toMsgTag tag, + senderProcess = sP, + senderThread = sT, + receiverMachine = rM, + receiverProcess = rP, + receiverInport = rIP + }) + ), + + (FixedSizeParser EVENT_RECEIVE_MESSAGE + (sz_msgtag + 2*sz_procid + 2*sz_tid' + sz_mid + sz_mes) + (do tag <- get :: Get Word8 + rP <- get :: Get ProcessId + rIP <- get :: Get PortId + sM <- get :: Get MachineId + sP <- get :: Get ProcessId + sT <- get :: Get ThreadId + mS <- get :: Get MessageSize + return ReceiveMessage { mesTag = toMsgTag tag, + receiverProcess = rP, + receiverInport = rIP, + senderMachine = sM, + senderProcess = sP, + senderThread= sT, + messageSize = mS + }) + ), + + (FixedSizeParser EVENT_SEND_RECEIVE_LOCAL_MESSAGE + (sz_msgtag + 2*sz_procid + 2*sz_tid') + (do tag <- get :: Get Word8 + sP <- get :: Get ProcessId + sT <- get :: Get ThreadId + rP <- get :: Get ProcessId + rIP <- get :: Get PortId + return SendReceiveLocalMessage { mesTag = toMsgTag tag, + senderProcess = sP, + senderThread = sT, + receiverProcess = rP, + receiverInport = rIP + }) + )] + +mercuryParsers :: [EventParser EventInfo] +mercuryParsers = [ + (FixedSizeParser EVENT_MER_START_PAR_CONJUNCTION + (sz_par_conj_dyn_id + sz_par_conj_static_id) + (do dyn_id <- get + static_id <- get + return (MerStartParConjunction dyn_id static_id)) + ), + + (FixedSizeParser EVENT_MER_STOP_PAR_CONJUNCTION sz_par_conj_dyn_id + (do dyn_id <- get + return (MerEndParConjunction dyn_id)) + ), + + (FixedSizeParser EVENT_MER_STOP_PAR_CONJUNCT sz_par_conj_dyn_id + (do dyn_id <- get + return (MerEndParConjunct dyn_id)) + ), + + (FixedSizeParser EVENT_MER_CREATE_SPARK (sz_par_conj_dyn_id + sz_spark_id) + (do dyn_id <- get + spark_id <- get + return (MerCreateSpark dyn_id spark_id)) + ), + + (FixedSizeParser EVENT_MER_FUT_CREATE (sz_future_id + sz_string_id) + (do future_id <- get + name_id <- get + return (MerFutureCreate future_id name_id)) + ), + + (FixedSizeParser EVENT_MER_FUT_WAIT_NOSUSPEND (sz_future_id) + (do future_id <- get + return (MerFutureWaitNosuspend future_id)) + ), + + (FixedSizeParser EVENT_MER_FUT_WAIT_SUSPENDED (sz_future_id) + (do future_id <- get + return (MerFutureWaitSuspended future_id)) + ), + + (FixedSizeParser EVENT_MER_FUT_SIGNAL (sz_future_id) + (do future_id <- get + return (MerFutureSignal future_id)) + ), + + (simpleEvent EVENT_MER_LOOKING_FOR_GLOBAL_CONTEXT MerLookingForGlobalThread), + (simpleEvent EVENT_MER_WORK_STEALING MerWorkStealing), + (simpleEvent EVENT_MER_LOOKING_FOR_LOCAL_SPARK MerLookingForLocalSpark), + + (FixedSizeParser EVENT_MER_RELEASE_CONTEXT sz_tid + (do thread_id <- get + return (MerReleaseThread thread_id)) + ), + + (simpleEvent EVENT_MER_ENGINE_SLEEPING MerCapSleeping), + (simpleEvent EVENT_MER_CALLING_MAIN MerCallingMain) + + ] + +perfParsers :: [EventParser EventInfo] +perfParsers = [ + (VariableSizeParser EVENT_PERF_NAME (do -- (perf_num, name) + num <- get :: Get Word16 + perfNum <- get + name <- getString (num - sz_perf_num) + return PerfName{perfNum, name} + )), + + (FixedSizeParser EVENT_PERF_COUNTER (sz_perf_num + sz_kernel_tid + 8) (do -- (perf_num, tid, period) + perfNum <- get + tid <- get + period <- get + return PerfCounter{perfNum, tid, period} + )), + + (FixedSizeParser EVENT_PERF_TRACEPOINT (sz_perf_num + sz_kernel_tid) (do -- (perf_num, tid) + perfNum <- get + tid <- get + return PerfTracepoint{perfNum, tid} + )) + ] + +----------------------------------------------------------- + +putE :: Binary a => a -> PutM () +putE = put + +putType :: EventTypeNum -> PutM () +putType = putE + +putCap :: Int -> PutM () +putCap c = putE (fromIntegral c :: CapNo) + +putMarker :: Word32 -> PutM () +putMarker = putE + +putEStr :: String -> PutM () +putEStr = mapM_ putE + +putEventLog :: EventLog -> PutM () +putEventLog (EventLog hdr es) = do + putHeader hdr + putData es + +putHeader :: Header -> PutM () +putHeader (Header ets) = do + putMarker EVENT_HEADER_BEGIN + putMarker EVENT_HET_BEGIN + mapM_ putEventType ets + putMarker EVENT_HET_END + putMarker EVENT_HEADER_END + where + putEventType (EventType n d msz) = do + putMarker EVENT_ET_BEGIN + putType n + putE $ fromMaybe 0xffff msz + putE (fromIntegral $ length d :: EventTypeDescLen) + mapM_ put d + -- the event type header allows for extra data, which we don't use: + putE (0 :: Word32) + putMarker EVENT_ET_END + +putData :: Data -> PutM () +putData (Data es) = do + putMarker EVENT_DATA_BEGIN -- Word32 + mapM_ putEvent es + putType EVENT_DATA_END -- Word16 + +eventTypeNum :: EventInfo -> EventTypeNum +eventTypeNum e = case e of + CreateThread {} -> EVENT_CREATE_THREAD + RunThread {} -> EVENT_RUN_THREAD + StopThread {} -> EVENT_STOP_THREAD + ThreadRunnable {} -> EVENT_THREAD_RUNNABLE + MigrateThread {} -> EVENT_MIGRATE_THREAD + Shutdown {} -> EVENT_SHUTDOWN + WakeupThread {} -> EVENT_THREAD_WAKEUP + ThreadLabel {} -> EVENT_THREAD_LABEL + StartGC {} -> EVENT_GC_START + EndGC {} -> EVENT_GC_END + GlobalSyncGC {} -> EVENT_GC_GLOBAL_SYNC + RequestSeqGC {} -> EVENT_REQUEST_SEQ_GC + RequestParGC {} -> EVENT_REQUEST_PAR_GC + CreateSparkThread {} -> EVENT_CREATE_SPARK_THREAD + SparkCounters {} -> EVENT_SPARK_COUNTERS + SparkCreate {} -> EVENT_SPARK_CREATE + SparkDud {} -> EVENT_SPARK_DUD + SparkOverflow {} -> EVENT_SPARK_OVERFLOW + SparkRun {} -> EVENT_SPARK_RUN + SparkSteal {} -> EVENT_SPARK_STEAL + SparkFizzle {} -> EVENT_SPARK_FIZZLE + SparkGC {} -> EVENT_SPARK_GC + TaskCreate {} -> EVENT_TASK_CREATE + TaskMigrate {} -> EVENT_TASK_MIGRATE + TaskDelete {} -> EVENT_TASK_DELETE + Message {} -> EVENT_LOG_MSG + Startup {} -> EVENT_STARTUP + EventBlock {} -> EVENT_BLOCK_MARKER + UserMessage {} -> EVENT_USER_MSG + UserMarker {} -> EVENT_USER_MARKER + GCIdle {} -> EVENT_GC_IDLE + GCWork {} -> EVENT_GC_WORK + GCDone {} -> EVENT_GC_DONE + GCStatsGHC{} -> EVENT_GC_STATS_GHC + HeapAllocated{} -> EVENT_HEAP_ALLOCATED + HeapSize{} -> EVENT_HEAP_SIZE + HeapLive{} -> EVENT_HEAP_LIVE + HeapInfoGHC{} -> EVENT_HEAP_INFO_GHC + CapCreate{} -> EVENT_CAP_CREATE + CapDelete{} -> EVENT_CAP_DELETE + CapDisable{} -> EVENT_CAP_DISABLE + CapEnable{} -> EVENT_CAP_ENABLE + CapsetCreate {} -> EVENT_CAPSET_CREATE + CapsetDelete {} -> EVENT_CAPSET_DELETE + CapsetAssignCap {} -> EVENT_CAPSET_ASSIGN_CAP + CapsetRemoveCap {} -> EVENT_CAPSET_REMOVE_CAP + RtsIdentifier {} -> EVENT_RTS_IDENTIFIER + ProgramArgs {} -> EVENT_PROGRAM_ARGS + ProgramEnv {} -> EVENT_PROGRAM_ENV + OsProcessPid {} -> EVENT_OSPROCESS_PID + OsProcessParentPid{} -> EVENT_OSPROCESS_PPID + WallClockTime{} -> EVENT_WALL_CLOCK_TIME + UnknownEvent {} -> error "eventTypeNum UnknownEvent" + InternString {} -> EVENT_INTERN_STRING + Version {} -> EVENT_VERSION + ProgramInvocation {} -> EVENT_PROGRAM_INVOCATION + EdenStartReceive {} -> EVENT_EDEN_START_RECEIVE + EdenEndReceive {} -> EVENT_EDEN_END_RECEIVE + CreateProcess {} -> EVENT_CREATE_PROCESS + KillProcess {} -> EVENT_KILL_PROCESS + AssignThreadToProcess {} -> EVENT_ASSIGN_THREAD_TO_PROCESS + CreateMachine {} -> EVENT_CREATE_MACHINE + KillMachine {} -> EVENT_KILL_MACHINE + SendMessage {} -> EVENT_SEND_MESSAGE + ReceiveMessage {} -> EVENT_RECEIVE_MESSAGE + SendReceiveLocalMessage {} -> EVENT_SEND_RECEIVE_LOCAL_MESSAGE + MerStartParConjunction {} -> EVENT_MER_START_PAR_CONJUNCTION + MerEndParConjunction _ -> EVENT_MER_STOP_PAR_CONJUNCTION + MerEndParConjunct _ -> EVENT_MER_STOP_PAR_CONJUNCT + MerCreateSpark {} -> EVENT_MER_CREATE_SPARK + MerFutureCreate {} -> EVENT_MER_FUT_CREATE + MerFutureWaitNosuspend _ -> EVENT_MER_FUT_WAIT_NOSUSPEND + MerFutureWaitSuspended _ -> EVENT_MER_FUT_WAIT_SUSPENDED + MerFutureSignal _ -> EVENT_MER_FUT_SIGNAL + MerLookingForGlobalThread -> EVENT_MER_LOOKING_FOR_GLOBAL_CONTEXT + MerWorkStealing -> EVENT_MER_WORK_STEALING + MerLookingForLocalSpark -> EVENT_MER_LOOKING_FOR_LOCAL_SPARK + MerReleaseThread _ -> EVENT_MER_RELEASE_CONTEXT + MerCapSleeping -> EVENT_MER_ENGINE_SLEEPING + MerCallingMain -> EVENT_MER_CALLING_MAIN + PerfName {} -> nEVENT_PERF_NAME + PerfCounter {} -> nEVENT_PERF_COUNTER + PerfTracepoint {} -> nEVENT_PERF_TRACEPOINT + +nEVENT_PERF_NAME, nEVENT_PERF_COUNTER, nEVENT_PERF_TRACEPOINT :: EventTypeNum +nEVENT_PERF_NAME = EVENT_PERF_NAME +nEVENT_PERF_COUNTER = EVENT_PERF_COUNTER +nEVENT_PERF_TRACEPOINT = EVENT_PERF_TRACEPOINT + +putEvent :: Event -> PutM () +putEvent Event {..} = do + putType (eventTypeNum evSpec) + put evTime + putEventSpec evSpec + +putEventSpec :: EventInfo -> PutM () +putEventSpec (Startup caps) = do + putCap (fromIntegral caps) + +putEventSpec (EventBlock end cap sz) = do + putE (fromIntegral (sz+24) :: BlockSize) + putE end + putE (fromIntegral cap :: CapNo) + +putEventSpec (CreateThread t) = + putE t + +putEventSpec (RunThread t) = + putE t + +-- here we assume that ThreadStopStatus fromEnum matches the definitions in +-- EventLogFormat.h +-- The standard encoding is used here, which is wrong for eventlogs +-- produced by GHC-7.8.2 ([Stop status in GHC-7.8.2] in EventTypes.hs +putEventSpec (StopThread t s) = do + putE t + putE $ case s of + NoStatus -> 0 :: Word16 + HeapOverflow -> 1 + StackOverflow -> 2 + ThreadYielding -> 3 + ThreadBlocked -> 4 + ThreadFinished -> 5 + ForeignCall -> 6 + BlockedOnMVar -> 7 + BlockedOnMVarRead -> 20 -- since GHC-7.8.3 + BlockedOnBlackHole -> 8 + BlockedOnBlackHoleOwnedBy _ -> 8 + BlockedOnRead -> 9 + BlockedOnWrite -> 10 + BlockedOnDelay -> 11 + BlockedOnSTM -> 12 + BlockedOnDoProc -> 13 + BlockedOnCCall -> 14 + BlockedOnCCall_NoUnblockExc -> 15 + BlockedOnMsgThrowTo -> 16 + ThreadMigrating -> 17 + BlockedOnMsgGlobalise -> 18 + putE $ case s of + BlockedOnBlackHoleOwnedBy i -> i + _ -> 0 + +putEventSpec (ThreadRunnable t) = + putE t + +putEventSpec (MigrateThread t c) = do + putE t + putCap c + +putEventSpec (CreateSparkThread t) = + putE t + +putEventSpec (SparkCounters crt dud ovf cnv fiz gcd rem) = do + putE crt + putE dud + putE ovf + putE cnv + -- Warning: order of fiz and gcd reversed! + putE gcd + putE fiz + putE rem + +putEventSpec SparkCreate = + return () + +putEventSpec SparkDud = + return () + +putEventSpec SparkOverflow = + return () + +putEventSpec SparkRun = + return () + +putEventSpec (SparkSteal c) = + putCap c + +putEventSpec SparkFizzle = + return () + +putEventSpec SparkGC = + return () + +putEventSpec (WakeupThread t c) = do + putE t + putCap c + +putEventSpec (ThreadLabel t l) = do + putE (fromIntegral (length l) + sz_tid :: Word16) + putE t + putEStr l + +putEventSpec Shutdown = + return () + +putEventSpec RequestSeqGC = + return () + +putEventSpec RequestParGC = + return () + +putEventSpec StartGC = + return () + +putEventSpec GCWork = + return () + +putEventSpec GCIdle = + return () + +putEventSpec GCDone = + return () + +putEventSpec EndGC = + return () + +putEventSpec GlobalSyncGC = + return () + +putEventSpec (TaskCreate taskId cap tid) = do + putE taskId + putCap cap + putE tid + +putEventSpec (TaskMigrate taskId cap new_cap) = do + putE taskId + putCap cap + putCap new_cap + +putEventSpec (TaskDelete taskId) = + putE taskId + +putEventSpec GCStatsGHC{..} = do + putE heapCapset + putE (fromIntegral gen :: Word16) + putE copied + putE slop + putE frag + putE (fromIntegral parNThreads :: Word32) + putE parMaxCopied + putE parTotCopied + +putEventSpec HeapAllocated{..} = do + putE heapCapset + putE allocBytes + +putEventSpec HeapSize{..} = do + putE heapCapset + putE sizeBytes + +putEventSpec HeapLive{..} = do + putE heapCapset + putE liveBytes + +putEventSpec HeapInfoGHC{..} = do + putE heapCapset + putE (fromIntegral gens :: Word16) + putE maxHeapSize + putE allocAreaSize + putE mblockSize + putE blockSize + +putEventSpec CapCreate{cap} = + putCap cap + +putEventSpec CapDelete{cap} = + putCap cap + +putEventSpec CapDisable{cap} = + putCap cap + +putEventSpec CapEnable{cap} = + putCap cap + +putEventSpec (CapsetCreate cs ct) = do + putE cs + putE $ case ct of + CapsetCustom -> 1 :: Word16 + CapsetOsProcess -> 2 + CapsetClockDomain -> 3 + CapsetUnknown -> 0 + +putEventSpec (CapsetDelete cs) = + putE cs + +putEventSpec (CapsetAssignCap cs cp) = do + putE cs + putCap cp + +putEventSpec (CapsetRemoveCap cs cp) = do + putE cs + putCap cp + +putEventSpec (RtsIdentifier cs rts) = do + putE (fromIntegral (length rts) + sz_capset :: Word16) + putE cs + putEStr rts + +putEventSpec (ProgramArgs cs as) = do + let as' = unsep as + putE (fromIntegral (length as') + sz_capset :: Word16) + putE cs + mapM_ putE as' + +putEventSpec (ProgramEnv cs es) = do + let es' = unsep es + putE (fromIntegral (length es') + sz_capset :: Word16) + putE cs + mapM_ putE es' + +putEventSpec (OsProcessPid cs pid) = do + putE cs + putE pid + +putEventSpec (OsProcessParentPid cs ppid) = do + putE cs + putE ppid + +putEventSpec (WallClockTime cs sec nsec) = do + putE cs + putE sec + putE nsec + +putEventSpec (Message s) = do + putE (fromIntegral (length s) :: Word16) + mapM_ putE s + +putEventSpec (UserMessage s) = do + putE (fromIntegral (length s) :: Word16) + mapM_ putE s + +putEventSpec (UserMarker s) = do + putE (fromIntegral (length s) :: Word16) + mapM_ putE s + +putEventSpec (UnknownEvent {}) = error "putEventSpec UnknownEvent" + +putEventSpec (InternString str id) = do + putE len + mapM_ putE str + putE id + where len = (fromIntegral (length str) :: Word16) + sz_string_id + +putEventSpec (Version s) = do + putE (fromIntegral (length s) :: Word16) + mapM_ putE s + +putEventSpec (ProgramInvocation s) = do + putE (fromIntegral (length s) :: Word16) + mapM_ putE s + +putEventSpec ( EdenStartReceive ) = return () + +putEventSpec ( EdenEndReceive ) = return () + +putEventSpec ( CreateProcess process ) = do + putE process + +putEventSpec ( KillProcess process ) = do + putE process + +putEventSpec ( AssignThreadToProcess thread process ) = do + putE thread + putE process + +putEventSpec ( CreateMachine machine realtime ) = do + putE machine + putE realtime + +putEventSpec ( KillMachine machine ) = do + putE machine + +putEventSpec ( SendMessage mesTag senderProcess senderThread + receiverMachine receiverProcess receiverInport ) = do + putE (fromMsgTag mesTag) + putE senderProcess + putE senderThread + putE receiverMachine + putE receiverProcess + putE receiverInport + +putEventSpec ( ReceiveMessage mesTag receiverProcess receiverInport + senderMachine senderProcess senderThread messageSize ) = do + putE (fromMsgTag mesTag) + putE receiverProcess + putE receiverInport + putE senderMachine + putE senderProcess + putE senderThread + putE messageSize + +putEventSpec ( SendReceiveLocalMessage mesTag senderProcess senderThread + receiverProcess receiverInport ) = do + putE (fromMsgTag mesTag) + putE senderProcess + putE senderThread + putE receiverProcess + putE receiverInport + +putEventSpec (MerStartParConjunction dyn_id static_id) = do + putE dyn_id + putE static_id + +putEventSpec (MerEndParConjunction dyn_id) = + putE dyn_id + +putEventSpec (MerEndParConjunct dyn_id) = + putE dyn_id + +putEventSpec (MerCreateSpark dyn_id spark_id) = do + putE dyn_id + putE spark_id + +putEventSpec (MerFutureCreate future_id name_id) = do + putE future_id + putE name_id + +putEventSpec (MerFutureWaitNosuspend future_id) = + putE future_id + +putEventSpec (MerFutureWaitSuspended future_id) = + putE future_id + +putEventSpec (MerFutureSignal future_id) = + putE future_id + +putEventSpec MerLookingForGlobalThread = return () +putEventSpec MerWorkStealing = return () +putEventSpec MerLookingForLocalSpark = return () + +putEventSpec (MerReleaseThread thread_id) = + putE thread_id + +putEventSpec MerCapSleeping = return () +putEventSpec MerCallingMain = return () + +putEventSpec PerfName{..} = do + putE (fromIntegral (length name) + sz_perf_num :: Word16) + putE perfNum + mapM_ putE name + +putEventSpec PerfCounter{..} = do + putE perfNum + putE tid + putE period + +putEventSpec PerfTracepoint{..} = do + putE perfNum + putE tid + +-- [] == [] +-- [x] == x\0 +-- [x, y, z] == x\0y\0 +unsep :: [String] -> String +unsep = concatMap (++"\0") -- not the most efficient, but should be ok + +splitNull :: String -> [String] +splitNull [] = [] +splitNull xs = case span (/= '\0') xs of + (x, xs') -> x : splitNull (drop 1 xs') diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs index 6cc944a..c4fb557 100644 --- a/src/GHC/RTS/Events/Incremental.hs +++ b/src/GHC/RTS/Events/Incremental.hs @@ -43,6 +43,7 @@ import qualified Data.IntMap.Strict as IM import GHC.RTS.EventParserUtils import GHC.RTS.EventTypes import GHC.RTS.Events +import GHC.RTS.Events.Binary #define EVENTLOG_CONSTANTS_ONLY #include "EventLogFormat.h" From bcb45953bc8a04bf57ee2bfb6d21729590a5998f Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Sun, 12 Mar 2017 07:23:32 +0900 Subject: [PATCH 14/17] Move I/O interface in Incremental to Events --- src/GHC/RTS/EventTypes.hs | 8 +++ src/GHC/RTS/Events.hs | 107 +++++++++++++++++++++++++++-- src/GHC/RTS/Events/Incremental.hs | 108 ------------------------------ 3 files changed, 110 insertions(+), 113 deletions(-) diff --git a/src/GHC/RTS/EventTypes.hs b/src/GHC/RTS/EventTypes.hs index b42e476..7a906b5 100644 --- a/src/GHC/RTS/EventTypes.hs +++ b/src/GHC/RTS/EventTypes.hs @@ -1,6 +1,7 @@ {-# OPTIONS_GHC -fwarn-incomplete-patterns #-} module GHC.RTS.EventTypes where +import Control.Monad import Data.Binary @@ -520,3 +521,10 @@ toMsgTag = toEnum . fromIntegral . (\n -> n - offset) fromMsgTag :: MessageTag -> RawMsgTag fromMsgTag = (+ offset) . fromIntegral . fromEnum + +-- Checks if the capability is not -1 (which indicates a global eventblock), so +-- has no associated capability +mkCap :: Int -> Maybe Int +mkCap cap = do + guard $ fromIntegral cap /= (-1 :: Word16) + return cap diff --git a/src/GHC/RTS/Events.hs b/src/GHC/RTS/Events.hs index c727143..509fc6c 100644 --- a/src/GHC/RTS/Events.hs +++ b/src/GHC/RTS/Events.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP,BangPatterns #-} {-# LANGUAGE OverloadedStrings #-} -{-# OPTIONS_GHC -funbox-strict-fields -fwarn-incomplete-patterns #-} +{-# LANGUAGE MultiWayIf #-} {- - Parser functions for GHC RTS EventLog framework. -} @@ -26,11 +26,16 @@ module GHC.RTS.Events ( MessageSize, MessageTag(..), + -- * Reading and writing event logs + readEventLogFromFile, + writeEventLogToFile, + -- * Utilities CapEvent(..), sortEvents, buildEventTypeMap, -- * Printing + printEventsIncremental, showEventInfo, buildEventInfo, showThreadStopStatus, ppEventLog, ppEventType, @@ -47,28 +52,120 @@ module GHC.RTS.Events ( ) where {- Libraries. -} +import Control.Applicative +import Control.Concurrent hiding (ThreadId) +import qualified Data.Binary.Put as P +import qualified Data.ByteString as B import qualified Data.ByteString.Builder as BB +import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy.Char8 as BL8 import Data.IntMap (IntMap) -import qualified Data.IntMap as M +import qualified Data.IntMap as IM import Data.Foldable (foldMap) import Data.Function hiding (id) import Data.List import Data.Monoid ((<>)) +import System.IO import Prelude hiding (gcd, rem, id) import GHC.RTS.EventTypes import GHC.RTS.Events.Binary +import GHC.RTS.Events.Incremental + +-- | Read an entire eventlog file. It returns an error message if it +-- encouters an error while decoding. +-- +-- Note that it doesn't fail if it consumes all input in the middle of decoding +-- of an event. +readEventLogFromFile :: FilePath -> IO (Either String EventLog) +readEventLogFromFile path = fmap fst . readEventLog <$> BL.readFile path + +-- | Read an eventlog file and pretty print it to stdout +printEventsIncremental + :: Bool -- ^ Follow the file or not + -> FilePath + -> IO () +printEventsIncremental follow path = + withFile path ReadMode (hPrintEventsIncremental follow) + +-- | Read an eventlog from the Handle and pretty print it to stdout +hPrintEventsIncremental + :: Bool -- ^ Follow the handle or not + -> Handle + -> IO () +hPrintEventsIncremental follow hdl = go decodeEventLog + where + go decoder = case decoder of + Produce event decoder' -> do + BB.hPutBuilder stdout $ buildEvent' event <> "\n" + go decoder' + Consume k -> do + chunk <- B.hGetSome hdl 4096 + if + | not (B.null chunk) -> go $ k chunk + | follow -> threadDelay 1000000 >> go decoder + | otherwise -> return () + Done {} -> return () + Error _ err -> fail err + +-- | Writes the 'EventLog' to file. The log is expected to __NOT__ have 'EventBlock' +-- markers/events - the parsers no longer emit them and they are handled behind +-- the scenes. +writeEventLogToFile :: FilePath -> EventLog -> IO () +writeEventLogToFile fp = BL.writeFile fp . serialiseEventLog + + +-- | Serialises an 'EventLog' back to a 'ByteString', usually for writing it +-- back to a file. +serialiseEventLog :: EventLog -> BL.ByteString +serialiseEventLog el@(EventLog _ (Data events)) = + P.runPut $ putEventLog blockedEl + where + eventsMap = capSplitEvents events + blockedEventsMap = IM.mapWithKey addBlockMarker eventsMap + blockedEl = el{dat = Data blockedEvents} + blockedEvents = IM.foldr (++) [] blockedEventsMap + +-- Gets the Capability of an event in numeric form +getIntCap :: Event -> Int +getIntCap Event{evCap = cap} = + case cap of + Just capNo -> capNo + Nothing -> -1 + +-- Creates an IntMap of the events with capability number as the key. +-- Key -1 indicates global (capless) event +capSplitEvents :: [Event] -> IM.IntMap [Event] +capSplitEvents evts = capSplitEvents' evts IM.empty + +capSplitEvents' :: [Event] -> IM.IntMap [Event] -> IM.IntMap [Event] +capSplitEvents' evts imap = + case evts of + (x:xs) -> capSplitEvents' xs (IM.insertWith (++) (getIntCap x) [x] imap) + [] -> imap + +-- Adds a block marker to the beginnng of a list of events, annotated with +-- its capability. All events are expected to belong to the same cap. +addBlockMarker :: Int -> [Event] -> [Event] +addBlockMarker cap evts = + (Event startTime (EventBlock endTime cap sz) (mkCap cap)) : sortedEvts + where + sz = fromIntegral . BL.length $ P.runPut $ mapM_ putEvent evts + startTime = case sortedEvts of + (x:_) -> evTime x + [] -> error "Cannot add block marker to an empty list of events" + sortedEvts = sortEvents evts + endTime = evTime $ last sortedEvts -- ----------------------------------------------------------------------------- -- Utilities - sortEvents :: [Event] -> [Event] sortEvents = sortBy (compare `on` evTime) buildEventTypeMap :: [EventType] -> IntMap EventType -buildEventTypeMap etypes = M.fromList [ (fromIntegral (num t),t) | t <- etypes ] +buildEventTypeMap etypes = + IM.fromList [ (fromIntegral (num t),t) | t <- etypes ] ----------------------------------------------------------------------------- -- Some pretty-printing support @@ -370,7 +467,7 @@ buildEvent imap Event {..} = <> maybe "" (\c -> "cap " <> BB.intDec c <> ": ") evCap <> case evSpec of UnknownEvent{ ref=ref } -> - maybe "" (BB.stringUtf8 . desc) $ M.lookup (fromIntegral ref) imap + maybe "" (BB.stringUtf8 . desc) $ IM.lookup (fromIntegral ref) imap _ -> buildEventInfo evSpec buildEvent' :: Event -> BB.Builder diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs index c4fb557..e855d79 100644 --- a/src/GHC/RTS/Events/Incremental.hs +++ b/src/GHC/RTS/Events/Incremental.hs @@ -12,37 +12,20 @@ module GHC.RTS.Events.Incremental , readHeader , readEvents , readEventLog - - -- * IO interface - , readEventLogFromFile - , printEventsIncremental - , hPrintEventsIncremental - - -- * Serialisation - , writeEventLogToFile - , serialiseEventLog ) where -import Control.Applicative -import Control.Concurrent import Control.Monad import Data.Either import Data.Maybe -import Data.Monoid -import Data.Word -import System.IO import Prelude import qualified Data.Binary.Get as G -import qualified Data.Binary.Put as P import qualified Data.ByteString as B -import qualified Data.ByteString.Builder as BB import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy.Internal as BL import qualified Data.IntMap.Strict as IM import GHC.RTS.EventParserUtils import GHC.RTS.EventTypes -import GHC.RTS.Events import GHC.RTS.Events.Binary #define EVENTLOG_CONSTANTS_ONLY @@ -168,42 +151,6 @@ readEventLog bytes = do case readEvents header bytes' of (events, err) -> return (EventLog header (Data events), err) --- | Read an entire eventlog file. It returns an error message if it --- encouters an error while decoding. --- --- Note that it doesn't fail if it consumes all input in the middle of decoding --- of an event. -readEventLogFromFile :: FilePath -> IO (Either String EventLog) -readEventLogFromFile path = fmap fst . readEventLog <$> BL.readFile path - --- | Read an eventlog file and pretty print it to stdout -printEventsIncremental - :: Bool -- ^ Follow the file or not - -> FilePath - -> IO () -printEventsIncremental follow path = - withFile path ReadMode (hPrintEventsIncremental follow) - --- | Read an eventlog from the Handle and pretty print it to stdout -hPrintEventsIncremental - :: Bool -- ^ Follow the handle or not - -> Handle - -> IO () -hPrintEventsIncremental follow hdl = go decodeEventLog - where - go decoder = case decoder of - Produce event decoder' -> do - BB.hPutBuilder stdout $ buildEvent' event <> "\n" - go decoder' - Consume k -> do - chunk <- B.hGetSome hdl 4096 - if - | not (B.null chunk) -> go $ k chunk - | follow -> threadDelay 1000000 >> go decoder - | otherwise -> return () - Done {} -> return () - Error _ err -> fail err - -- | Makes a decoder with all the required parsers when given a Header mkEventDecoder :: Header -> G.Decoder (Maybe Event) mkEventDecoder header = G.runGetIncremental $ getEvent parsers @@ -253,58 +200,3 @@ mkEventDecoder header = G.runGetIncremental $ getEvent parsers , perfParsers ] parsers = EventParsers $ mkEventTypeParsers imap event_parsers - --- | Writes the 'EventLog' to file. The log is expected to __NOT__ have 'EventBlock' --- markers/events - the parsers no longer emit them and they are handled behind --- the scenes. -writeEventLogToFile :: FilePath -> EventLog -> IO () -writeEventLogToFile fp = BL.writeFile fp . serialiseEventLog - --- | Serialises an 'EventLog' back to a 'ByteString', usually for writing it --- back to a file. -serialiseEventLog :: EventLog -> BL.ByteString -serialiseEventLog el@(EventLog _ (Data events)) = - P.runPut $ putEventLog blockedEl - where - eventsMap = capSplitEvents events - blockedEventsMap = IM.mapWithKey addBlockMarker eventsMap - blockedEl = el{dat = Data blockedEvents} - blockedEvents = IM.foldr (++) [] blockedEventsMap - --- Gets the Capability of an event in numeric form -getIntCap :: Event -> Int -getIntCap Event{evCap = cap} = - case cap of - Just capNo -> capNo - Nothing -> -1 - --- Creates an IntMap of the events with capability number as the key. --- Key -1 indicates global (capless) event -capSplitEvents :: [Event] -> IM.IntMap [Event] -capSplitEvents evts = capSplitEvents' evts IM.empty - -capSplitEvents' :: [Event] -> IM.IntMap [Event] -> IM.IntMap [Event] -capSplitEvents' evts imap = - case evts of - (x:xs) -> capSplitEvents' xs (IM.insertWith (++) (getIntCap x) [x] imap) - [] -> imap - --- Adds a block marker to the beginnng of a list of events, annotated with --- its capability. All events are expected to belong to the same cap. -addBlockMarker :: Int -> [Event] -> [Event] -addBlockMarker cap evts = - (Event startTime (EventBlock endTime cap sz) (mkCap cap)) : sortedEvts - where - sz = fromIntegral . BL.length $ P.runPut $ mapM_ putEvent evts - startTime = case sortedEvts of - (x:_) -> evTime x - [] -> error "Cannot add block marker to an empty list of events" - sortedEvts = sortEvents evts - endTime = evTime $ last sortedEvts - --- Checks if the capability is not -1 (which indicates a global eventblock), so --- has no associated capability -mkCap :: Int -> Maybe Int -mkCap cap = do - guard $ fromIntegral cap /= (-1 :: Word16) - return cap From 61ffacf1a2f792e360c0bc6e1e42d07e7d3178ec Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Sun, 12 Mar 2017 07:31:35 +0900 Subject: [PATCH 15/17] Remove unnecessary GHC_OPTIONS and add -fsimpl-tick-factor=150 to Events --- src/GHC/RTS/EventParserUtils.hs | 2 -- src/GHC/RTS/EventTypes.hs | 2 -- src/GHC/RTS/Events.hs | 1 + src/GHC/RTS/Events/Merge.hs | 2 -- 4 files changed, 1 insertion(+), 6 deletions(-) diff --git a/src/GHC/RTS/EventParserUtils.hs b/src/GHC/RTS/EventParserUtils.hs index 564981a..f860993 100644 --- a/src/GHC/RTS/EventParserUtils.hs +++ b/src/GHC/RTS/EventParserUtils.hs @@ -1,7 +1,5 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} -{-# OPTIONS_GHC -fwarn-incomplete-patterns #-} - module GHC.RTS.EventParserUtils ( EventParser(..), EventParsers(..), diff --git a/src/GHC/RTS/EventTypes.hs b/src/GHC/RTS/EventTypes.hs index 7a906b5..1551cac 100644 --- a/src/GHC/RTS/EventTypes.hs +++ b/src/GHC/RTS/EventTypes.hs @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -fwarn-incomplete-patterns #-} - module GHC.RTS.EventTypes where import Control.Monad diff --git a/src/GHC/RTS/Events.hs b/src/GHC/RTS/Events.hs index 509fc6c..d765afc 100644 --- a/src/GHC/RTS/Events.hs +++ b/src/GHC/RTS/Events.hs @@ -1,6 +1,7 @@ {-# LANGUAGE CPP,BangPatterns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE MultiWayIf #-} +{-# OPTIONS_GHC -fsimpl-tick-factor=150 #-} {- - Parser functions for GHC RTS EventLog framework. -} diff --git a/src/GHC/RTS/Events/Merge.hs b/src/GHC/RTS/Events/Merge.hs index 3a14c81..37e6e2f 100644 --- a/src/GHC/RTS/Events/Merge.hs +++ b/src/GHC/RTS/Events/Merge.hs @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -funbox-strict-fields #-} - module GHC.RTS.Events.Merge (mergeEventLogs) where import GHC.RTS.Events From d3a2789dbb091ef78a985d36b43da90aa8421a17 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Sun, 12 Mar 2017 17:16:42 +0900 Subject: [PATCH 16/17] Improve Haddock --- src/GHC/RTS/EventParserUtils.hs | 2 +- src/GHC/RTS/Events.hs | 11 +++++++++++ 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/src/GHC/RTS/EventParserUtils.hs b/src/GHC/RTS/EventParserUtils.hs index f860993..7f64903 100644 --- a/src/GHC/RTS/EventParserUtils.hs +++ b/src/GHC/RTS/EventParserUtils.hs @@ -44,7 +44,7 @@ skip n = G.skip (fromIntegral n) -- -- --- Event parser data. Parsers are either fixed or vairable size. +-- | Event parser data. Parsers are either fixed or vairable size. -- data EventParser a = FixedSizeParser { diff --git a/src/GHC/RTS/Events.hs b/src/GHC/RTS/Events.hs index d765afc..3bf3d08 100644 --- a/src/GHC/RTS/Events.hs +++ b/src/GHC/RTS/Events.hs @@ -20,12 +20,23 @@ module GHC.RTS.Events ( ThreadId, TaskId, KernelThreadId(..), + EventTypeNum, + EventTypeDesc, + EventTypeSize, + BlockSize, + Capset, + StringId, -- some types for the parallel RTS ProcessId, MachineId, PortId, MessageSize, MessageTag(..), + ParConjDynId, + ParConjStaticId, + SparkId, + FutureId, + PerfEventTypeNum, -- * Reading and writing event logs readEventLogFromFile, From 53f2872aba90442ed92cbbf72439711129058b16 Mon Sep 17 00:00:00 2001 From: Mitsutoshi Aoe Date: Sun, 9 Apr 2017 06:43:38 +0900 Subject: [PATCH 17/17] Add note about non-incremental parsing of readHeader --- src/GHC/RTS/Events/Incremental.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/GHC/RTS/Events/Incremental.hs b/src/GHC/RTS/Events/Incremental.hs index e855d79..2b483a3 100644 --- a/src/GHC/RTS/Events/Incremental.hs +++ b/src/GHC/RTS/Events/Incremental.hs @@ -100,6 +100,9 @@ decodeEventLog = withHeader $ \header leftover -> -- | Read a header from a lazy bytestring and return the header and the -- leftover input for subsequent decoding. +-- +-- Note that the input must contain a whole header in one go. If incremental +-- parsing of a header is necessary, use 'decodeHeader' instead. readHeader :: BL.ByteString -> Either String (Header, BL.ByteString) readHeader = go $ Left decodeHeader where