Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Once you defined a StateMachineT
, you can render its topology as a
directed graph using a Mermaid state diagram
Synopsis
- newtype Mermaid = Mermaid {}
- newtype MachineLabel = MachineLabel {}
- renderStateDiagram :: (RenderableVertices a, Show a) => Graph a -> Mermaid
- labelVertex :: Show a => MachineLabel -> a -> Text
- renderLabelledVertices :: forall a. (Show a, RenderableVertices a) => MachineLabel -> Graph a -> Mermaid
- renderVertices :: forall a. (Show a, RenderableVertices a) => Graph a -> Mermaid
- renderLabelledEdges :: Show a => MachineLabel -> Graph a -> Mermaid
- renderEdges :: Show a => Graph a -> Mermaid
- renderLabelledGraph :: (RenderableVertices a, Show a) => MachineLabel -> Graph a -> Mermaid
- renderGraph :: (RenderableVertices a, Show a) => Graph a -> Mermaid
- topologyAsGraph :: Topology v -> Graph v
- baseMachineAsGraph :: forall vertex topology input output m. (Demote vertex ~ vertex, SingKind vertex, SingI topology) => BaseMachineT m (topology :: Topology vertex) input output -> Graph vertex
- renderUntypedStateDiagram :: UntypedGraph -> Mermaid
- renderUntypedGraph :: UntypedGraph -> Mermaid
- machineAsGraph :: StateMachineT m input output -> UntypedGraph
Documentation
Mermaid
is just a newtype
around Text
to specialize it to Mermaid
diagrams
newtype MachineLabel Source #
A MachineLabel
is just a newtype around Text
to represents label which
will be attached to every leaf of the tree defined by the constructors of
StateMachineT
Instances
IsString MachineLabel Source # | |
Defined in Crem.Render.Render fromString :: String -> MachineLabel # | |
Show MachineLabel Source # | |
Defined in Crem.Render.Render showsPrec :: Int -> MachineLabel -> ShowS # show :: MachineLabel -> String # showList :: [MachineLabel] -> ShowS # | |
Eq MachineLabel Source # | |
Defined in Crem.Render.Render (==) :: MachineLabel -> MachineLabel -> Bool # (/=) :: MachineLabel -> MachineLabel -> Bool # |
renderStateDiagram :: (RenderableVertices a, Show a) => Graph a -> Mermaid Source #
We can render a Graph
as a Mermaid state diagram
labelVertex :: Show a => MachineLabel -> a -> Text Source #
Prepends a MachineLabel
to the Show
output, as a Text
renderLabelledVertices :: forall a. (Show a, RenderableVertices a) => MachineLabel -> Graph a -> Mermaid Source #
Render all the vertices of a graph after labelling all of them
renderVertices :: forall a. (Show a, RenderableVertices a) => Graph a -> Mermaid Source #
Render all vertices with no label
renderLabelledEdges :: Show a => MachineLabel -> Graph a -> Mermaid Source #
Render all the edges of a graph after labelling all of them
renderLabelledGraph :: (RenderableVertices a, Show a) => MachineLabel -> Graph a -> Mermaid Source #
Join the outputs of renderLabelledVertices
and renderLabelledEdges
to
render an entire Graph
renderGraph :: (RenderableVertices a, Show a) => Graph a -> Mermaid Source #
Render a Graph
with no labels
baseMachineAsGraph :: forall vertex topology input output m. (Demote vertex ~ vertex, SingKind vertex, SingI topology) => BaseMachineT m (topology :: Topology vertex) input output -> Graph vertex Source #
Interpret a BaseMachine
as a Graph
using the information contained in
its topology.
This is the point where we make usage of the machinery provided by the
singletons library, which
require us to impose the constraints we have on vertex
and topology
renderUntypedStateDiagram :: UntypedGraph -> Mermaid Source #
Render an UntypedGraph
to the Mermaid format
renderUntypedGraph :: UntypedGraph -> Mermaid Source #
Render an UntypedGraph
machineAsGraph :: StateMachineT m input output -> UntypedGraph Source #
Interpret a StateMachine
as an UntypedGraph
using the information
contained in its structure and in the topology of its basic components