Skip to content

Commit e9b859d

Browse files
committed
studio: Show transaction history table. #307
1 parent 4f0a09e commit e9b859d

File tree

3 files changed

+50
-10
lines changed

3 files changed

+50
-10
lines changed

studio/dist/index.html

+1
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@
1717
<link rel="stylesheet" href="auths.css">
1818
<link rel="stylesheet" href="kdmoncat-bricks.css">
1919
<link rel="stylesheet" href="../../halogen-grid-kit/src/GridKit/KeyHandler.css" />
20+
<link rel="stylesheet" href="studio.css">
2021

2122
<style>
2223
svg {

studio/dist/studio.css

+6
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
tr.css-tx-execution {
2+
background: orange;
3+
}
4+
tr.css-tx-current {
5+
background: pink;
6+
}

studio/src/View/Transaction.purs

+43-10
Original file line numberDiff line numberDiff line change
@@ -3,34 +3,39 @@ module View.Transaction where
33
import Prelude hiding (div)
44
import Affjax (URL) -- TODO eliminate
55
import Data.Array (mapMaybe)
6-
import Data.Lens (over, preview, _Just, second)
6+
import Data.String.CodePoints (take)
7+
import Data.Lens (over, preview, _Just, second, view)
78
import Data.Maybe (Maybe, maybe)
9+
import Data.Newtype (un)
10+
import Data.Either (either)
811
import Data.Either.Nested (type (\/))
12+
import Data.Tuple.Nested ((/\))
913
import Effect.Aff.Class (class MonadAff)
1014
import Halogen (ComponentHTML)
11-
import Halogen.HTML (HTML, slot, div, table, tr, td, a, text, p, br, pre)
12-
import Halogen.HTML.Properties (href)
15+
import Halogen.HTML (HTML, slot, div, table, tr, th, td, a, text, p, br, pre)
16+
import Halogen.HTML.Core (ClassName(..))
17+
import Halogen.HTML.Properties (classes, href)
1318

1419
import View.Studio.Model (Action(..))
1520
import View.Studio.Model.Route (WiringFiringInfo, ExecutionTrace)
1621
import Statebox.Client (txUrl)
17-
import Statebox.Core.Lenses (_firingTx, _firing, _firingPath)
18-
import Statebox.Core.Transaction (HashStr, TxSum, FiringTx, WiringTx, isExecution)
22+
import Statebox.Core.Lenses (_firingTx, _firing, _firingPath, _GluedTransitionId)
23+
import Statebox.Core.Transaction (HashStr, TxSum, FiringTx, TxId, WiringTx, evalTxSum, isExecution)
1924
import Statebox.Core.Types (TID, GluedTransitionId(..))
2025

2126

2227
firingTxView :: s m. MonadAff m => WiringFiringInfo -> FiringTx -> String \/ ExecutionTrace -> ComponentHTML Action s m
23-
firingTxView wfi tx executionTrace =
28+
firingTxView wfi tx executionTraceE =
2429
div []
2530
[ p [] [ text $ if isExecution tx.firing then "Execution" else "Firing" ]
2631
, table [] $ txWrapperRows wfi tx <>
2732
firingTxBodyRows wfi tx <>
28-
[ row "trace" $ text $ show $ firedTransitions ] <>
29-
[ row "trace raw" $ text (show executionTrace) ]
33+
[ row "trace" $ text $ either (const "no") (show <<< map (un GluedTransitionId)) firedTransitionsE ] <>
34+
[ row "history" $ either (const $ text "no execution trace") (firingTxHistoryTable wfi.hash) executionTraceE ]
3035
]
3136
where
32-
firedTransitions :: String \/ Array GluedTransitionId
33-
firedTransitions = map (mapMaybe (preview (second <<< _Just <<< _firingTx <<< _firing <<< _firingPath))) executionTrace
37+
firedTransitionsE :: String \/ Array GluedTransitionId
38+
firedTransitionsE = map (mapMaybe (preview (second <<< _Just <<< _firingTx <<< _firing <<< _firingPath))) executionTraceE
3439

3540
wiringTxView :: s m. MonadAff m => WiringFiringInfo -> WiringTx -> ComponentHTML Action s m
3641
wiringTxView wfi tx =
@@ -57,6 +62,30 @@ txWrapperRows wfi tx =
5762

5863
--------------------------------------------------------------------------------
5964

65+
firingTxHistoryTable :: s m. MonadAff m => TxId -> ExecutionTrace -> ComponentHTML Action s m
66+
firingTxHistoryTable currentHash et =
67+
div [] (headerRows <> (historyRow <$> et))
68+
where
69+
headerRows = [ tr [] [ th [] [ text "hash" ], th [] [ text "transition" ], th [] [ text "message" ] ] ]
70+
71+
historyRow (hash /\ txMaybe) =
72+
tr [ classes $ if hash == currentHash then [ ClassName "css-tx-current" ] else [] ] $
73+
maybe [ td [] [ text $ shortHash hash ], td [] [], td [] [ text $ "transaction not loaded." ] ]
74+
(evalTxSum (\x -> [ td [] [ text $ shortHash hash ], td [] [], td [] [ text $ "unexpected non-firing transaction" ] ])
75+
(\x -> [ td [] [ text $ shortHash hash ], td [] [], td [] [ text $ "unexpected non-firing transaction" ] ])
76+
(\x -> [ td [] [ text $ shortHash hash ], td [] [], td [] [ text $ "unexpected non-firing transaction" ] ])
77+
(\firingTx -> [ td [] [ text $ shortHash hash ]
78+
, td [] [ text $ show $ view (_GluedTransitionId >>> _firingPath >>> _firing) firingTx ]
79+
, td [] [ maybe (text "no message")
80+
(\msg -> pre [] [ text $ "\"" <> msg <> "\"" ])
81+
firingTx.firing.message
82+
]
83+
])
84+
)
85+
txMaybe
86+
87+
--------------------------------------------------------------------------------
88+
6089
wiringTxBodyRows :: s m. MonadAff m => WiringFiringInfo -> WiringTx -> Array (ComponentHTML Action s m)
6190
wiringTxBodyRows wfi tx =
6291
[ row "diagrams" $ text $ show (tx.wiring.diagrams <#> _.name)
@@ -78,3 +107,7 @@ row caption content =
78107
tr [] [ td [] [ text caption ]
79108
, td [] [ content ]
80109
]
110+
111+
-- TODO dedupe
112+
shortHash :: HashStr -> String
113+
shortHash = take 8

0 commit comments

Comments
 (0)