modelling-tasks-0.0.0.1
Safe HaskellSafe-Inferred
LanguageHaskell2010

Modelling.PetriNet.Types

Description

This module provides types to represent Petri nets.

A Petri net is a mathematical modelling language. It is used to describe distributed systems. Another name for Petri net is place / transition (PT) net.

The Types module defines basic type class instances and functions to work on and transform Petri net representations.

Synopsis

Documentation

data AdvConfig Source #

Instances

Instances details
Generic AdvConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep AdvConfig :: Type -> Type #

Read AdvConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show AdvConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep AdvConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep AdvConfig = D1 ('MetaData "AdvConfig" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "AdvConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "presenceOfSelfLoops") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "presenceOfSinkTransitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "presenceOfSourceTransitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

data AlloyConfig Source #

Constructors

AlloyConfig 

Instances

Instances details
Generic AlloyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep AlloyConfig :: Type -> Type #

Read AlloyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show AlloyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep AlloyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep AlloyConfig = D1 ('MetaData "AlloyConfig" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "AlloyConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "maxInstances") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: S1 ('MetaSel ('Just "timeout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

data BasicConfig Source #

Constructors

BasicConfig 

Fields

Instances

Instances details
Generic BasicConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep BasicConfig :: Type -> Type #

Read BasicConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show BasicConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep BasicConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep BasicConfig = D1 ('MetaData "BasicConfig" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "BasicConfig" 'PrefixI 'True) (((S1 ('MetaSel ('Just "places") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "transitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "atLeastActive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "flowOverall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)))) :*: ((S1 ('MetaSel ('Just "maxTokensPerPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "maxFlowPerEdge") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "tokensOverall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)) :*: S1 ('MetaSel ('Just "isConnected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

type Change = PetriChange String Source #

A PetriChange where nodes are labelled by strings.

data ChangeConfig Source #

Instances

Instances details
Generic ChangeConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep ChangeConfig :: Type -> Type #

Read ChangeConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show ChangeConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep ChangeConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep ChangeConfig = D1 ('MetaData "ChangeConfig" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "ChangeConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tokenChangeOverall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "maxTokenChangePerPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "flowChangeOverall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "maxFlowChangePerEdge") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

newtype Concurrent a Source #

Constructors

Concurrent (a, a) 

Instances

Instances details
Foldable Concurrent Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

fold :: Monoid m => Concurrent m -> m #

foldMap :: Monoid m => (a -> m) -> Concurrent a -> m #

foldMap' :: Monoid m => (a -> m) -> Concurrent a -> m #

foldr :: (a -> b -> b) -> b -> Concurrent a -> b #

foldr' :: (a -> b -> b) -> b -> Concurrent a -> b #

foldl :: (b -> a -> b) -> b -> Concurrent a -> b #

foldl' :: (b -> a -> b) -> b -> Concurrent a -> b #

foldr1 :: (a -> a -> a) -> Concurrent a -> a #

foldl1 :: (a -> a -> a) -> Concurrent a -> a #

toList :: Concurrent a -> [a] #

null :: Concurrent a -> Bool #

length :: Concurrent a -> Int #

elem :: Eq a => a -> Concurrent a -> Bool #

maximum :: Ord a => Concurrent a -> a #

minimum :: Ord a => Concurrent a -> a #

sum :: Num a => Concurrent a -> a #

product :: Num a => Concurrent a -> a #

Traversable Concurrent Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

traverse :: Applicative f => (a -> f b) -> Concurrent a -> f (Concurrent b) #

sequenceA :: Applicative f => Concurrent (f a) -> f (Concurrent a) #

mapM :: Monad m => (a -> m b) -> Concurrent a -> m (Concurrent b) #

sequence :: Monad m => Concurrent (m a) -> m (Concurrent a) #

Functor Concurrent Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

fmap :: (a -> b) -> Concurrent a -> Concurrent b #

(<$) :: a -> Concurrent b -> Concurrent a #

Generic (Concurrent a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep (Concurrent a) :: Type -> Type #

Methods

from :: Concurrent a -> Rep (Concurrent a) x #

to :: Rep (Concurrent a) x -> Concurrent a #

Read a => Read (Concurrent a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show a => Show (Concurrent a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (Concurrent a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (Concurrent a) = D1 ('MetaData "Concurrent" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'True) (C1 ('MetaCons "Concurrent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a, a))))

type Conflict = PetriConflict Place Transition Source #

A PetriConflict where nodes are labelled by strings.

data ConflictConfig Source #

Constructors

ConflictConfig 

Fields

Instances

Instances details
Generic ConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep ConflictConfig :: Type -> Type #

Read ConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show ConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep ConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep ConflictConfig = D1 ('MetaData "ConflictConfig" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "ConflictConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "addConflictCommonPreconditions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "withConflictDistractors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "conflictDistractorAddExtraPreconditions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "conflictDistractorOnlyConflictLike") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "conflictDistractorOnlyConcurrentLike") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))

data DrawSettings Source #

Instances

Instances details
Data DrawSettings Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DrawSettings -> c DrawSettings #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DrawSettings #

toConstr :: DrawSettings -> Constr #

dataTypeOf :: DrawSettings -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DrawSettings) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DrawSettings) #

gmapT :: (forall b. Data b => b -> b) -> DrawSettings -> DrawSettings #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DrawSettings -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DrawSettings -> r #

gmapQ :: (forall d. Data d => d -> u) -> DrawSettings -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DrawSettings -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DrawSettings -> m DrawSettings #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DrawSettings -> m DrawSettings #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DrawSettings -> m DrawSettings #

Generic DrawSettings Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep DrawSettings :: Type -> Type #

Read DrawSettings Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show DrawSettings Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep DrawSettings Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep DrawSettings = D1 ('MetaData "DrawSettings" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "DrawSettings" 'PrefixI 'True) ((S1 ('MetaSel ('Just "withPlaceNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "withSvgHighlighting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "withTransitionNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "with1Weights") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "withGraphvizCommand") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GraphvizCommand)))))

data FindConcurrencyConfig Source #

Instances

Instances details
Generic FindConcurrencyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep FindConcurrencyConfig :: Type -> Type #

Read FindConcurrencyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show FindConcurrencyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep FindConcurrencyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep FindConcurrencyConfig = D1 ('MetaData "FindConcurrencyConfig" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "FindConcurrencyConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "basicConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BasicConfig) :*: (S1 ('MetaSel ('Just "advConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AdvConfig) :*: S1 ('MetaSel ('Just "changeConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChangeConfig))) :*: ((S1 ('MetaSel ('Just "graphConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GraphConfig) :*: S1 ('MetaSel ('Just "printSolution") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "alloyConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AlloyConfig) :*: S1 ('MetaSel ('Just "extraText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Language String)))))))

data FindConflictConfig Source #

Instances

Instances details
Generic FindConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep FindConflictConfig :: Type -> Type #

Read FindConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show FindConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep FindConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

data GraphConfig Source #

Constructors

GraphConfig 

Fields

Instances

Instances details
Generic GraphConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep GraphConfig :: Type -> Type #

Read GraphConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show GraphConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep GraphConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep GraphConfig = D1 ('MetaData "GraphConfig" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "GraphConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "graphLayouts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GraphvizCommand]) :*: S1 ('MetaSel ('Just "hidePlaceNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "hideTransitionNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "hideWeight1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

class (PetriNode n, Show (p n String)) => Net p n where Source #

Methods

emptyNet :: p n a Source #

alterFlow Source #

Arguments

:: Ord a 
=> a

source

-> Int

the flow

-> a

target

-> p n a 
-> p n a 

Inserts flow into the Net by connecting the provided source and target by the given flow. If no PetriNode for the given source or target exists within the Net no flow is added to the Net If flow between source and target exists already it is replaced.

alterNode Source #

Arguments

:: Ord a 
=> a

node key

-> Maybe Int

initial tokens

-> p n a 
-> p n a 

Inserts a PetriNode into the Net given the desired key,

  • a place node with the desired initial tokes if Just such are provided,
  • a transition node otherwise.

If the desired key already exists, the targeted PetriNode is replaced without affecting preexisting flow. (use deleteNode first if you desire to clear related flow)

deleteFlow :: Ord a => a -> a -> p n a -> p n a Source #

Removes the flow going from the first given key to the second one..

deleteNode :: Ord a => a -> p n a -> p n a Source #

Removes the PetriNode associated with the key and all connections going from or to the removed node.

flow :: Ord a => a -> a -> p n a -> Maybe Int Source #

nodes :: Ord a => p n a -> Map a (n a) Source #

outFlow :: Ord a => a -> p n a -> Map a Int Source #

mapNet :: Ord b => (a -> b) -> p n a -> p n b Source #

traverseNet :: (Applicative f, Ord b) => (a -> f b) -> p n a -> f (p n b) Source #

Instances

Instances details
Net PetriLike Node Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

emptyNet :: PetriLike Node a Source #

alterFlow :: Ord a => a -> Int -> a -> PetriLike Node a -> PetriLike Node a Source #

alterNode :: Ord a => a -> Maybe Int -> PetriLike Node a -> PetriLike Node a Source #

deleteFlow :: Ord a => a -> a -> PetriLike Node a -> PetriLike Node a Source #

deleteNode :: Ord a => a -> PetriLike Node a -> PetriLike Node a Source #

flow :: Ord a => a -> a -> PetriLike Node a -> Maybe Int Source #

nodes :: Ord a => PetriLike Node a -> Map a (Node a) Source #

outFlow :: Ord a => a -> PetriLike Node a -> Map a Int Source #

mapNet :: Ord b => (a -> b) -> PetriLike Node a -> PetriLike Node b Source #

traverseNet :: (Applicative f, Ord b) => (a -> f b) -> PetriLike Node a -> f (PetriLike Node b) Source #

Net PetriLike SimpleNode Source # 
Instance details

Defined in Modelling.PetriNet.Types

data Node a Source #

A node is part of a Petri like graph (see PetriLike). Each node stores its predecessor and successor nodes together with their weight in the fields $sel:flowIn:PlaceNode and Node respectively. Additionally PlaceNodes have a value of initial tokens.

Constructors

PlaceNode 

Fields

TransitionNode 

Fields

Instances

Instances details
PetriNode Node Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

initialTokens :: Node a -> Int Source #

isPlaceNode :: Node a -> Bool Source #

isTransitionNode :: Node a -> Bool Source #

mapNode :: Ord b => (a -> b) -> Node a -> Node b Source #

traverseNode :: (Applicative f, Ord b) => (a -> f b) -> Node a -> f (Node b) Source #

Net PetriLike Node Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

emptyNet :: PetriLike Node a Source #

alterFlow :: Ord a => a -> Int -> a -> PetriLike Node a -> PetriLike Node a Source #

alterNode :: Ord a => a -> Maybe Int -> PetriLike Node a -> PetriLike Node a Source #

deleteFlow :: Ord a => a -> a -> PetriLike Node a -> PetriLike Node a Source #

deleteNode :: Ord a => a -> PetriLike Node a -> PetriLike Node a Source #

flow :: Ord a => a -> a -> PetriLike Node a -> Maybe Int Source #

nodes :: Ord a => PetriLike Node a -> Map a (Node a) Source #

outFlow :: Ord a => a -> PetriLike Node a -> Map a Int Source #

mapNet :: Ord b => (a -> b) -> PetriLike Node a -> PetriLike Node b Source #

traverseNet :: (Applicative f, Ord b) => (a -> f b) -> PetriLike Node a -> f (PetriLike Node b) Source #

(Data a, Ord a) => Data (Node a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Node a -> c (Node a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Node a) #

toConstr :: Node a -> Constr #

dataTypeOf :: Node a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Node a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Node a)) #

gmapT :: (forall b. Data b => b -> b) -> Node a -> Node a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Node a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Node a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Node a -> m (Node a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Node a -> m (Node a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Node a -> m (Node a) #

Generic (Node a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep (Node a) :: Type -> Type #

Methods

from :: Node a -> Rep (Node a) x #

to :: Rep (Node a) x -> Node a #

(Ord a, Read a) => Read (Node a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show a => Show (Node a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

showsPrec :: Int -> Node a -> ShowS #

show :: Node a -> String #

showList :: [Node a] -> ShowS #

Eq a => Eq (Node a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

(==) :: Node a -> Node a -> Bool #

(/=) :: Node a -> Node a -> Bool #

type Rep (Node a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (Node a) = D1 ('MetaData "Node" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "PlaceNode" 'PrefixI 'True) (S1 ('MetaSel ('Just "initial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "flowIn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a Int)) :*: S1 ('MetaSel ('Just "flowOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a Int)))) :+: C1 ('MetaCons "TransitionNode" 'PrefixI 'True) (S1 ('MetaSel ('Just "flowIn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a Int)) :*: S1 ('MetaSel ('Just "flowOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a Int))))

data Petri Source #

Constructors

Petri 

Fields

Instances

Instances details
Generic Petri Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep Petri :: Type -> Type #

Methods

from :: Petri -> Rep Petri x #

to :: Rep Petri x -> Petri #

Read Petri Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show Petri Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

showsPrec :: Int -> Petri -> ShowS #

show :: Petri -> String #

showList :: [Petri] -> ShowS #

Eq Petri Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

(==) :: Petri -> Petri -> Bool #

(/=) :: Petri -> Petri -> Bool #

type Rep Petri Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep Petri

data PetriChange a Source #

A PetriChange describes the changes on a PetriLike graph by mapping PlaceNodes to token changes and origins of an edge to a mapping from their targets to flow changes.

Constructors

Change 

Fields

  • tokenChange :: Map a Int

    The token change Map: Mapping places to changes of their tokens.

  • flowChange :: Map a (Map a Int)

    The flow change Map: Mapping source nodes to a mapping from target nodes to the flow change (if any) at the edge between source and target.

Instances

Instances details
Generic (PetriChange a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep (PetriChange a) :: Type -> Type #

Methods

from :: PetriChange a -> Rep (PetriChange a) x #

to :: Rep (PetriChange a) x -> PetriChange a #

Show a => Show (PetriChange a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Eq a => Eq (PetriChange a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriChange a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriChange a) = D1 ('MetaData "PetriChange" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "Change" 'PrefixI 'True) (S1 ('MetaSel ('Just "tokenChange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a Int)) :*: S1 ('MetaSel ('Just "flowChange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a (Map a Int)))))

data PetriConflict p t Source #

A PetriConflict describes a conflict between two transitions. It occurs when the number of tokens at the source place are not enough to fire both transitions (both are having the same source place).

Constructors

Conflict 

Fields

  • conflictTrans :: (t, t)

    The pair of transitions in conflict.

  • conflictPlaces :: [p]

    The set of source nodes having not enough tokens to fire both transitions.

Instances

Instances details
Bifoldable PetriConflict Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

bifold :: Monoid m => PetriConflict m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> PetriConflict a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> PetriConflict a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> PetriConflict a b -> c #

Bifunctor PetriConflict Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

bimap :: (a -> b) -> (c -> d) -> PetriConflict a c -> PetriConflict b d #

first :: (a -> b) -> PetriConflict a c -> PetriConflict b c #

second :: (b -> c) -> PetriConflict a b -> PetriConflict a c #

Bitraversable PetriConflict Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> PetriConflict a b -> f (PetriConflict c d) #

Functor (PetriConflict p) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

fmap :: (a -> b) -> PetriConflict p a -> PetriConflict p b #

(<$) :: a -> PetriConflict p b -> PetriConflict p a #

Generic (PetriConflict p t) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep (PetriConflict p t) :: Type -> Type #

Methods

from :: PetriConflict p t -> Rep (PetriConflict p t) x #

to :: Rep (PetriConflict p t) x -> PetriConflict p t #

(Read t, Read p) => Read (PetriConflict p t) Source # 
Instance details

Defined in Modelling.PetriNet.Types

(Show t, Show p) => Show (PetriConflict p t) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriConflict p t) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriConflict p t) = D1 ('MetaData "PetriConflict" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "Conflict" 'PrefixI 'True) (S1 ('MetaSel ('Just "conflictTrans") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (t, t)) :*: S1 ('MetaSel ('Just "conflictPlaces") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [p])))

newtype PetriConflict' x Source #

Constructors

PetriConflict' 

Instances

Instances details
Foldable PetriConflict' Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

fold :: Monoid m => PetriConflict' m -> m #

foldMap :: Monoid m => (a -> m) -> PetriConflict' a -> m #

foldMap' :: Monoid m => (a -> m) -> PetriConflict' a -> m #

foldr :: (a -> b -> b) -> b -> PetriConflict' a -> b #

foldr' :: (a -> b -> b) -> b -> PetriConflict' a -> b #

foldl :: (b -> a -> b) -> b -> PetriConflict' a -> b #

foldl' :: (b -> a -> b) -> b -> PetriConflict' a -> b #

foldr1 :: (a -> a -> a) -> PetriConflict' a -> a #

foldl1 :: (a -> a -> a) -> PetriConflict' a -> a #

toList :: PetriConflict' a -> [a] #

null :: PetriConflict' a -> Bool #

length :: PetriConflict' a -> Int #

elem :: Eq a => a -> PetriConflict' a -> Bool #

maximum :: Ord a => PetriConflict' a -> a #

minimum :: Ord a => PetriConflict' a -> a #

sum :: Num a => PetriConflict' a -> a #

product :: Num a => PetriConflict' a -> a #

Traversable PetriConflict' Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

traverse :: Applicative f => (a -> f b) -> PetriConflict' a -> f (PetriConflict' b) #

sequenceA :: Applicative f => PetriConflict' (f a) -> f (PetriConflict' a) #

mapM :: Monad m => (a -> m b) -> PetriConflict' a -> m (PetriConflict' b) #

sequence :: Monad m => PetriConflict' (m a) -> m (PetriConflict' a) #

Functor PetriConflict' Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

fmap :: (a -> b) -> PetriConflict' a -> PetriConflict' b #

(<$) :: a -> PetriConflict' b -> PetriConflict' a #

Generic (PetriConflict' x) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep (PetriConflict' x) :: Type -> Type #

Read x => Read (PetriConflict' x) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show x => Show (PetriConflict' x) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriConflict' x) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriConflict' x) = D1 ('MetaData "PetriConflict'" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'True) (C1 ('MetaCons "PetriConflict'" 'PrefixI 'True) (S1 ('MetaSel ('Just "toPetriConflict") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PetriConflict x x))))

newtype PetriLike n a Source #

A Petri like graph consists of nodes which might have connections between each other.

The PetriLike graph is a valid Petri net only if

Constructors

PetriLike 

Fields

  • allNodes :: Map a (n a)

    the Map of all nodes the Petri net like graph is made of

Instances

Instances details
Net PetriLike Node Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

emptyNet :: PetriLike Node a Source #

alterFlow :: Ord a => a -> Int -> a -> PetriLike Node a -> PetriLike Node a Source #

alterNode :: Ord a => a -> Maybe Int -> PetriLike Node a -> PetriLike Node a Source #

deleteFlow :: Ord a => a -> a -> PetriLike Node a -> PetriLike Node a Source #

deleteNode :: Ord a => a -> PetriLike Node a -> PetriLike Node a Source #

flow :: Ord a => a -> a -> PetriLike Node a -> Maybe Int Source #

nodes :: Ord a => PetriLike Node a -> Map a (Node a) Source #

outFlow :: Ord a => a -> PetriLike Node a -> Map a Int Source #

mapNet :: Ord b => (a -> b) -> PetriLike Node a -> PetriLike Node b Source #

traverseNet :: (Applicative f, Ord b) => (a -> f b) -> PetriLike Node a -> f (PetriLike Node b) Source #

Net PetriLike SimpleNode Source # 
Instance details

Defined in Modelling.PetriNet.Types

(Typeable n, Data a, Data (n a), Ord a) => Data (PetriLike n a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PetriLike n a -> c (PetriLike n a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PetriLike n a) #

toConstr :: PetriLike n a -> Constr #

dataTypeOf :: PetriLike n a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PetriLike n a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PetriLike n a)) #

gmapT :: (forall b. Data b => b -> b) -> PetriLike n a -> PetriLike n a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PetriLike n a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PetriLike n a -> r #

gmapQ :: (forall d. Data d => d -> u) -> PetriLike n a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PetriLike n a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PetriLike n a -> m (PetriLike n a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PetriLike n a -> m (PetriLike n a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PetriLike n a -> m (PetriLike n a) #

Generic (PetriLike n a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep (PetriLike n a) :: Type -> Type #

Methods

from :: PetriLike n a -> Rep (PetriLike n a) x #

to :: Rep (PetriLike n a) x -> PetriLike n a #

(Ord a, Read a, Read (n a)) => Read (PetriLike n a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

(Show a, Show (n a)) => Show (PetriLike n a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

showsPrec :: Int -> PetriLike n a -> ShowS #

show :: PetriLike n a -> String #

showList :: [PetriLike n a] -> ShowS #

(Eq a, Eq (n a)) => Eq (PetriLike n a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

(==) :: PetriLike n a -> PetriLike n a -> Bool #

(/=) :: PetriLike n a -> PetriLike n a -> Bool #

type Rep (PetriLike n a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriLike n a) = D1 ('MetaData "PetriLike" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'True) (C1 ('MetaCons "PetriLike" 'PrefixI 'True) (S1 ('MetaSel ('Just "allNodes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a (n a)))))

data PetriMath a Source #

Stores a mathematical representation of a Petri net based on a five tuple.

Constructors

PetriMath 

Fields

Instances

Instances details
Foldable PetriMath Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

fold :: Monoid m => PetriMath m -> m #

foldMap :: Monoid m => (a -> m) -> PetriMath a -> m #

foldMap' :: Monoid m => (a -> m) -> PetriMath a -> m #

foldr :: (a -> b -> b) -> b -> PetriMath a -> b #

foldr' :: (a -> b -> b) -> b -> PetriMath a -> b #

foldl :: (b -> a -> b) -> b -> PetriMath a -> b #

foldl' :: (b -> a -> b) -> b -> PetriMath a -> b #

foldr1 :: (a -> a -> a) -> PetriMath a -> a #

foldl1 :: (a -> a -> a) -> PetriMath a -> a #

toList :: PetriMath a -> [a] #

null :: PetriMath a -> Bool #

length :: PetriMath a -> Int #

elem :: Eq a => a -> PetriMath a -> Bool #

maximum :: Ord a => PetriMath a -> a #

minimum :: Ord a => PetriMath a -> a #

sum :: Num a => PetriMath a -> a #

product :: Num a => PetriMath a -> a #

Traversable PetriMath Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

traverse :: Applicative f => (a -> f b) -> PetriMath a -> f (PetriMath b) #

sequenceA :: Applicative f => PetriMath (f a) -> f (PetriMath a) #

mapM :: Monad m => (a -> m b) -> PetriMath a -> m (PetriMath b) #

sequence :: Monad m => PetriMath (m a) -> m (PetriMath a) #

Functor PetriMath Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

fmap :: (a -> b) -> PetriMath a -> PetriMath b #

(<$) :: a -> PetriMath b -> PetriMath a #

Data a => Data (PetriMath a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PetriMath a -> c (PetriMath a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PetriMath a) #

toConstr :: PetriMath a -> Constr #

dataTypeOf :: PetriMath a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PetriMath a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PetriMath a)) #

gmapT :: (forall b. Data b => b -> b) -> PetriMath a -> PetriMath a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PetriMath a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PetriMath a -> r #

gmapQ :: (forall d. Data d => d -> u) -> PetriMath a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PetriMath a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PetriMath a -> m (PetriMath a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PetriMath a -> m (PetriMath a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PetriMath a -> m (PetriMath a) #

Generic (PetriMath a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep (PetriMath a) :: Type -> Type #

Methods

from :: PetriMath a -> Rep (PetriMath a) x #

to :: Rep (PetriMath a) x -> PetriMath a #

Read a => Read (PetriMath a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show a => Show (PetriMath a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriMath a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (PetriMath a) = D1 ('MetaData "PetriMath" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "PetriMath" 'PrefixI 'True) ((S1 ('MetaSel ('Just "netMath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "placesMath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "transitionsMath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) :*: (S1 ('MetaSel ('Just "tokenChangeMath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(a, a)]) :*: (S1 ('MetaSel ('Just "initialMarkingMath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "placeOrderMath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))))

class Show (n String) => PetriNode n where Source #

Methods

initialTokens :: n a -> Int Source #

isPlaceNode :: n a -> Bool Source #

Whether the Node is a PlaceNode.

isTransitionNode :: n a -> Bool Source #

Whether the PetriNode is a TransitionNode.

mapNode :: Ord b => (a -> b) -> n a -> n b Source #

This function acts like fmap on other Functors.

Note that PetriNode is not necessarily a true Functor and thus mapNode is not a true fmap because an Ord instance is required for Nodes first type parameter for mapNode to work, furthermore (and that is the original reason), mapNode usually uses mapKeys internally in order to apply the mapping. Thus, the user of mapNode is responsible to ensure that the transformation preserves uniqueness on all used keys.

traverseNode :: (Applicative f, Ord b) => (a -> f b) -> n a -> f (n b) Source #

This function acts like traverse on Traversable.

Not that PetriNode is not necessarily Traversable itself as it requires an Ord instance for the result type within the Applicative of its first argument, the applicative lifting transformation function. This behaviour occurs, because the traversal changes the keys of the underlying Map. Transformations on this map require a specific traversal traverseKeyMap.

The user is responsible to ensure uniqueness of the keys after the traversal. Note, that the order of values could also change if the transformation is not order-preserving.

Instances

Instances details
PetriNode Node Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

initialTokens :: Node a -> Int Source #

isPlaceNode :: Node a -> Bool Source #

isTransitionNode :: Node a -> Bool Source #

mapNode :: Ord b => (a -> b) -> Node a -> Node b Source #

traverseNode :: (Applicative f, Ord b) => (a -> f b) -> Node a -> f (Node b) Source #

PetriNode SimpleNode Source # 
Instance details

Defined in Modelling.PetriNet.Types

data PickConcurrencyConfig Source #

Instances

Instances details
Generic PickConcurrencyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep PickConcurrencyConfig :: Type -> Type #

Read PickConcurrencyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show PickConcurrencyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep PickConcurrencyConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep PickConcurrencyConfig = D1 ('MetaData "PickConcurrencyConfig" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "PickConcurrencyConfig" 'PrefixI 'True) (((S1 ('MetaSel ('Just "basicConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BasicConfig) :*: S1 ('MetaSel ('Just "changeConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChangeConfig)) :*: (S1 ('MetaSel ('Just "graphConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GraphConfig) :*: S1 ('MetaSel ('Just "printSolution") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "prohibitSourceTransitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "useDifferentGraphLayouts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "alloyConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AlloyConfig) :*: S1 ('MetaSel ('Just "extraText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Language String)))))))

data PickConflictConfig Source #

Instances

Instances details
Generic PickConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep PickConflictConfig :: Type -> Type #

Read PickConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show PickConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep PickConflictConfig Source # 
Instance details

Defined in Modelling.PetriNet.Types

data SimpleNode a Source #

Constructors

SimplePlace 

Fields

SimpleTransition 

Fields

Instances

Instances details
PetriNode SimpleNode Source # 
Instance details

Defined in Modelling.PetriNet.Types

Net PetriLike SimpleNode Source # 
Instance details

Defined in Modelling.PetriNet.Types

(Data a, Ord a) => Data (SimpleNode a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SimpleNode a -> c (SimpleNode a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SimpleNode a) #

toConstr :: SimpleNode a -> Constr #

dataTypeOf :: SimpleNode a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SimpleNode a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SimpleNode a)) #

gmapT :: (forall b. Data b => b -> b) -> SimpleNode a -> SimpleNode a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SimpleNode a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SimpleNode a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SimpleNode a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SimpleNode a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SimpleNode a -> m (SimpleNode a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleNode a -> m (SimpleNode a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleNode a -> m (SimpleNode a) #

Generic (SimpleNode a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Associated Types

type Rep (SimpleNode a) :: Type -> Type #

Methods

from :: SimpleNode a -> Rep (SimpleNode a) x #

to :: Rep (SimpleNode a) x -> SimpleNode a #

(Ord a, Read a) => Read (SimpleNode a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Show a => Show (SimpleNode a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Eq a => Eq (SimpleNode a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

Methods

(==) :: SimpleNode a -> SimpleNode a -> Bool #

(/=) :: SimpleNode a -> SimpleNode a -> Bool #

type Rep (SimpleNode a) Source # 
Instance details

Defined in Modelling.PetriNet.Types

type Rep (SimpleNode a) = D1 ('MetaData "SimpleNode" "Modelling.PetriNet.Types" "modelling-tasks-0.0.0.1-5lkaY76HE6k79qLVIy6Ku2" 'False) (C1 ('MetaCons "SimplePlace" 'PrefixI 'True) (S1 ('MetaSel ('Just "initial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "flowOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a Int))) :+: C1 ('MetaCons "SimpleTransition" 'PrefixI 'True) (S1 ('MetaSel ('Just "flowOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a Int))))

allDrawSettings :: GraphConfig -> [DrawSettings] Source #

Provides a list of all DrawSetting that can be obtained by using drawSettingsWithCommand and all possible graphLayouts of the given config.

checkPetriNodeCount :: (Net p n, Ord a) => (Int, Maybe Int) -> p n a -> Bool Source #

Check if the count of nodes in a Petri net falls within the given bounds

drawSettingsWithCommand :: GraphConfig -> GraphvizCommand -> DrawSettings Source #

Converts a GraphConfig into DrawSettings by choosing the provided GraphvizCommand.

Raises a runtime error if the provided GraphvizCommand is not in the $sel:graphLayouts:GraphConfig list of the GraphConfig.

lConflictPlaces :: forall p t p. Lens (PetriConflict p t) (PetriConflict p t) [p] [p] Source #

lConflictTrans :: forall p t t. Lens (PetriConflict p t) (PetriConflict p t) (t, t) (t, t) Source #

lGraphLayouts :: Lens' GraphConfig [GraphvizCommand] Source #

mapChange :: Ord b => (a -> b) -> PetriChange a -> PetriChange b Source #

This function acts like fmap on other Functors.

Note that Change is not a true Functor and thus mapChange is not a true fmap because an Ord instance is required for Changes first type parameter for mapChange to work, furthermore (and that is the original reason), mapChange uses mapKeys internally in order to apply the mapping. Thus, the user of mapChange is responsible to ensure that the transformation preserves uniqueness on all used keys.

maybeInitial :: PetriNode n => n a -> Maybe Int Source #

Returns Just the Node tokens of the given node, if it is a place PetriNode, otherwise it returns Nothing.

petriLikeToPetri :: (MonadThrow m, Ord a) => PetriLike Node a -> m Petri Source #

Transform a PetriLike graph into a Petri net. It first checks if the given Petri net like graph is indeed a valid Petri net (see also PetriLike),

  • if it is, the Petri net like graph is transformed into a Petri net by eliminating references to names of places and transitions at all. Instead $sel:initialMarking:Petri is given by a list (where each position represents different places) and transitions ($sel:trans:Petri) are given by a lists of token change (where, again, each position represents a different place, but the same index within $sel:initialMarking:Petri and $sel:trans:Petri represents the same place).
  • if it is not, an exception is thrown indicating the reason why the given Petri net like graph is not a valid Petri net.

placeNames :: (Net p n, Ord k) => p n k -> [k] Source #

shuffleNames :: (MonadThrow m, Net p n, Ord a, RandomGen g) => p n a -> RandT g m (p n a, Bimap a a) Source #

transformNet :: (Net p n, Net p' n', Ord a) => p n a -> p' n' a Source #

transitionNames :: (Net p n, Ord k) => p n k -> [k] Source #

Orphan instances

Data GraphvizCommand Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GraphvizCommand -> c GraphvizCommand #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GraphvizCommand #

toConstr :: GraphvizCommand -> Constr #

dataTypeOf :: GraphvizCommand -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GraphvizCommand) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GraphvizCommand) #

gmapT :: (forall b. Data b => b -> b) -> GraphvizCommand -> GraphvizCommand #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GraphvizCommand -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GraphvizCommand -> r #

gmapQ :: (forall d. Data d => d -> u) -> GraphvizCommand -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GraphvizCommand -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GraphvizCommand -> m GraphvizCommand #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GraphvizCommand -> m GraphvizCommand #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GraphvizCommand -> m GraphvizCommand #