Skip to content

Commit

Permalink
feat(new-debugger): Display running version
Browse files Browse the repository at this point in the history
  • Loading branch information
symbiont-daniel-gustafsson committed Mar 24, 2022
1 parent 75aa484 commit dcea4ec
Show file tree
Hide file tree
Showing 3 changed files with 9 additions and 0 deletions.
4 changes: 4 additions & 0 deletions src/new-debugger/src/Debugger/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
module Debugger.State where

import Data.Aeson
import Data.Int
import GHC.Generics (Generic)

import Data.Vector (Vector)
Expand All @@ -21,6 +22,7 @@ instance ToJSON DebEvent
data InstanceState = InstanceState
{ isState :: String -- Should probably be per reactor
, isCurrentEvent :: DebEvent
, isRunningVersion :: Int64
, isSeqDia :: String
, isLogs :: [String]
, isSent :: [DebEvent]
Expand All @@ -29,6 +31,7 @@ data InstanceState = InstanceState
data InstanceStateRepr = InstanceStateRepr
{ state :: String
, currentEvent :: DebEvent
, runningVersion :: Int64
, logs :: [String]
, sent :: [DebEvent]
} deriving Generic
Expand All @@ -45,6 +48,7 @@ fromRepr = fmap repr
repr i = InstanceState
{ isState = state i
, isCurrentEvent = currentEvent i
, isRunningVersion = runningVersion i
, isSeqDia = "Sequence Diagram not supported yet!" -- should actually be built here
, isLogs = logs i
, isSent = sent i
Expand Down
4 changes: 4 additions & 0 deletions src/new-debugger/src/Debugger/UI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ drawUI as = [ui]
]
, vBox
[ borderWithLabel (str "Input") $ renderMessage as
, vLimit 3 $ borderWithLabel (str "Version") $ renderVersion as
, borderWithLabel (str "Output") $ renderSentMessage as
]
]
Expand Down Expand Up @@ -71,6 +72,9 @@ renderSeqDia as = renderToString as isSeqDia
renderMessage :: AppState -> Widget ()
renderMessage as = renderToString as (message . isCurrentEvent)

renderVersion :: AppState -> Widget ()
renderVersion as = renderToString as (show . isRunningVersion)

renderSentMessage :: AppState -> Widget ()
renderSentMessage as = renderToString as (addEmpty . unlines . map (renderEvent True) . isSent)
where
Expand Down
1 change: 1 addition & 0 deletions src/sut/dumblog/src/Dumblog/Journal/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,7 @@ replayDebug originCommands originState = do
is = InstanceStateRepr
{ state = show (ppEditExpr ansiWlPretty (ediff s s'))
, currentEvent = ce
, runningVersion = v
, logs = logLines
, sent = [ DebEvent
{ from = "dumblog"
Expand Down

0 comments on commit dcea4ec

Please sign in to comment.