Skip to content

Commit 5923590

Browse files
committed
io-sim: added pretty printers
Pretty print 'Trace' and list of events (as returned by 'traceEvents').
1 parent 997c174 commit 5923590

File tree

3 files changed

+63
-1
lines changed

3 files changed

+63
-1
lines changed

io-sim/src/Control/Monad/IOSim.hs

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE ExplicitNamespaces #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
23
{-# LANGUAGE RankNTypes #-}
34
{-# LANGUAGE ScopedTypeVariables #-}
45

@@ -22,6 +23,9 @@ module Control.Monad.IOSim (
2223
-- * Simulation trace
2324
type SimTrace,
2425
Trace (Cons, Nil, Trace, SimTrace, TraceMainReturn, TraceMainException, TraceDeadlock),
26+
ppTrace,
27+
ppTrace_,
28+
ppEvents,
2529
SimResult(..),
2630
SimEvent(..),
2731
SimEventType(..),
@@ -57,7 +61,7 @@ import Data.List (intercalate)
5761
import Data.Bifoldable
5862
import Data.Typeable (Typeable)
5963

60-
import Data.List.Trace
64+
import Data.List.Trace (Trace (..))
6165

6266
import Control.Exception (throw)
6367

@@ -243,6 +247,19 @@ traceEvents (SimTrace time tid tlbl event t) = (time, tid, tlbl, event)
243247
: traceEvents t
244248
traceEvents _ = []
245249

250+
ppEvents :: [(Time, ThreadId, Maybe ThreadLabel, SimEventType)]
251+
-> String
252+
ppEvents events =
253+
intercalate "\n"
254+
[ ppSimEvent width
255+
SimEvent {seTime, seThreadId, seThreadLabel, seType }
256+
| (seTime, seThreadId, seThreadLabel, seType) <- events
257+
]
258+
where
259+
width = maximum
260+
[ maybe 0 length threadLabel
261+
| (_, _, threadLabel, _) <- events
262+
]
246263

247264

248265
-- | See 'runSimTraceST' below.

io-sim/src/Control/Monad/IOSim/Internal.hs

Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,25 +44,32 @@ module Control.Monad.IOSim.Internal (
4444
SimResult (..),
4545
SimEventType (..),
4646
TraceEvent,
47+
ppTrace,
48+
ppTrace_,
49+
ppSimEvent,
4750
liftST,
4851
execReadTVar
4952

5053
) where
5154

5255
import Prelude hiding (read)
5356

57+
import Data.Bifoldable
58+
import Data.Bifunctor
5459
import Data.Dynamic (Dynamic, toDyn)
5560
import Data.Foldable (traverse_)
5661
import qualified Data.List as List
5762
import qualified Data.List.Trace as Trace
5863
import Data.Map.Strict (Map)
5964
import qualified Data.Map.Strict as Map
65+
import Data.Maybe (fromMaybe)
6066
import Data.OrdPSQ (OrdPSQ)
6167
import qualified Data.OrdPSQ as PSQ
6268
import Data.Set (Set)
6369
import qualified Data.Set as Set
6470
import Data.Time (UTCTime (..), fromGregorian)
6571
import Data.Typeable (Typeable)
72+
import Text.Printf
6673
import Quiet (Quiet (..))
6774
import GHC.Generics (Generic)
6875

@@ -600,6 +607,21 @@ data SimEvent = SimEvent {
600607
seThreadLabel :: !(Maybe ThreadLabel),
601608
seType :: !SimEventType
602609
}
610+
deriving Generic
611+
deriving Show via Quiet SimEvent
612+
613+
ppSimEvent :: Int -- ^ width of thread label
614+
-> SimEvent
615+
-> String
616+
ppSimEvent d SimEvent {seTime, seThreadId, seThreadLabel, seType} =
617+
printf "%-24s - %-13s %-*s - %s"
618+
(show seTime)
619+
(show seThreadId)
620+
d
621+
threadLabel
622+
(show seType)
623+
where
624+
threadLabel = fromMaybe "" seThreadLabel
603625

604626
data SimResult a
605627
= MainReturn !Time a ![Labelled ThreadId]
@@ -610,6 +632,22 @@ data SimResult a
610632

611633
type SimTrace a = Trace.Trace (SimResult a) SimEvent
612634

635+
-- | Pretty print simulation trace.
636+
--
637+
ppTrace :: Show a => SimTrace a -> String
638+
ppTrace tr = Trace.ppTrace
639+
show
640+
(ppSimEvent (bimaximum (bimap (const 0) (maybe 0 length . seThreadLabel) tr)))
641+
tr
642+
643+
-- | Like 'ppTrace' but does not show the result value.
644+
--
645+
ppTrace_ :: SimTrace a -> String
646+
ppTrace_ tr = Trace.ppTrace
647+
(const "")
648+
(ppSimEvent (bimaximum (bimap (const 0) (maybe 0 length . seThreadLabel) tr)))
649+
tr
650+
613651
pattern Trace :: Time -> ThreadId -> Maybe ThreadLabel -> SimEventType -> SimTrace a
614652
-> SimTrace a
615653
pattern Trace time threadId threadLabel traceEvent trace =

io-sim/src/Data/List/Trace.hs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22

33
module Data.List.Trace
44
( Trace (..)
5+
, ppTrace
56
, toList
67
, fromList
78
, head
@@ -57,6 +58,12 @@ toList = bifoldr (\_ bs -> bs) (:) []
5758
fromList :: a -> [b] -> Trace a b
5859
fromList a = foldr Cons (Nil a)
5960

61+
-- | Pretty print an 'Trace'.
62+
--
63+
ppTrace :: (a -> String) -> (b -> String) -> Trace a b -> String
64+
ppTrace sa sb (Cons b bs) = sb b ++ "\n" ++ ppTrace sa sb bs
65+
ppTrace sa _sb (Nil a) = sa a
66+
6067
instance Bifunctor Trace where
6168
bimap f g (Cons b bs) = Cons (g b) (bimap f g bs)
6269
bimap f _ (Nil a) = Nil (f a)

0 commit comments

Comments
 (0)