11module Statebox.Core.WiringTree where
22
33import Prelude
4- import Data.Array (head )
4+ import Control.Apply (lift3 )
5+ import Data.Array (head , length , partition , range )
6+ import Data.Either (Either (..), either )
57import Data.Maybe (Maybe )
8+ import Data.Tuple.Nested ((/\))
69
7- import Statebox.Core.Types (Diagram , Net , Wiring )
10+ import Data.Petrinet.Representation.NLL (ErrNetEncoding , TransitionF' , fromNLL )
11+ import Statebox.Core.Execution (Path )
12+ import Statebox.Core.Types (Diagram , Net , PID , TID , Wiring )
813
914data WiringTree
1015 = Net Net
@@ -14,3 +19,60 @@ data WiringTree
1419-- | For the moment, we forget about diagrams and gluings and we consider only simple nets
1520wiringToWiringTree :: Wiring -> Maybe WiringTree
1621wiringToWiringTree wiring = Net <$> head wiring.nets
22+
23+ type Transition =
24+ { path :: Path
25+ , transition :: TID
26+ , name :: String
27+ }
28+
29+ data Glued a
30+ = Untouched a
31+ | Initial a
32+ | Final a
33+ | Glued a a
34+
35+ isInitial :: forall a . Glued a -> Boolean
36+ isInitial = case _ of
37+ Initial a -> true
38+ _ -> false
39+
40+ isFinal :: forall a . Glued a -> Boolean
41+ isFinal = case _ of
42+ Final a -> true
43+ _ -> false
44+
45+ data LinerisationError
46+ = DiagramNotYetAllowed
47+ | NLLDecodingFailed ErrNetEncoding
48+
49+ linearise :: WiringTree -> Either LinerisationError (Array (Glued Transition ))
50+ linearise (Net net) = lineariseNet net
51+ linearise (Diagram diagram branches) = Left DiagramNotYetAllowed
52+
53+ lineariseNet :: Net -> Either LinerisationError (Array (Glued Transition ))
54+ lineariseNet net = linearisePartitionsAndNames net.partition net.names
55+
56+ linearisePartitionsAndNames :: Array PID -> Array String -> Either LinerisationError (Array (Glued Transition ))
57+ linearisePartitionsAndNames partition names =
58+ either (NLLDecodingFailed >>> Left ) (Right <<< flip lineriseTransitionsAndNames names) $ fromNLL 0 partition
59+
60+ -- the use of `lift3` does not consider the fact that the arrays could in principle have different lenghts
61+ lineriseTransitionsAndNames :: Array (TransitionF' PID ) -> Array String -> Array (Glued Transition )
62+ lineriseTransitionsAndNames transitions names =
63+ sortInitialFinal $ lift3 buildGluedTransition (range 0 (length transitions - 1 )) transitions names
64+
65+ buildGluedTransition :: TID -> TransitionF' PID -> String -> Glued Transition
66+ buildGluedTransition tId (inputs /\ outputs) name =
67+ case (inputs /\ outputs) of
68+ ([] /\ _ ) -> Initial { name: name, path: [0 , 0 , 0 ], transition: tId } -- the path is [0, 0, 0] because we consider a trivial diagram to be there
69+ (_ /\ [] ) -> Final { name: name, path: [0 , 0 , 0 ], transition: tId }
70+ (inp /\ out) -> Untouched { name: name, path: [0 , 0 , 0 ], transition: tId }
71+
72+ -- | we are using this custom function instead of `sortBy` because that does not guarantee
73+ -- | the order of equal things to be preserved
74+ sortInitialFinal :: forall a . Array (Glued a ) -> Array (Glued a )
75+ sortInitialFinal gluedItems =
76+ let { no: notInitial , yes: initial } = partition isInitial gluedItems
77+ { no: notInitialAndFinal, yes: final } = partition isFinal notInitial
78+ in initial <> notInitialAndFinal <> final
0 commit comments