modelling-tasks-0.0.0.1
Safe HaskellNone
LanguageHaskell2010

Modelling.PetriNet.Reach.Type

Description

originally from Autotool (https:/gitlab.imn.htwk-leipzig.deautotool/all0) based on revision: ad25a990816a162fdd13941ff889653f22d6ea0a based on file: collectionsrcPetri/Type.hs

Synopsis

Documentation

type Connection s t = ([s], t, [s]) Source #

newtype State s Source #

Constructors

State 

Fields

Instances

Instances details
(Ord s, Reader s) => Reader (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

ToDoc s => ToDoc (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

toDocPrec :: Int -> State s -> Doc

toDocList :: [State s] -> Doc

(Data s, Ord s) => Data (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

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

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

toConstr :: State s -> Constr #

dataTypeOf :: State s -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Associated Types

type Rep (State s) 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep (State s) = D1 ('MetaData "State" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'True) (C1 ('MetaCons "State" 'PrefixI 'True) (S1 ('MetaSel ('Just "unState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map s Int))))

Methods

from :: State s -> Rep (State s) x #

to :: Rep (State s) x -> State s #

(Ord s, Read s) => Read (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Show s => Show (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

showsPrec :: Int -> State s -> ShowS #

show :: State s -> String #

showList :: [State s] -> ShowS #

Ord s => Eq (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

(==) :: State s -> State s -> Bool #

(/=) :: State s -> State s -> Bool #

Ord s => Ord (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

compare :: State s -> State s -> Ordering #

(<) :: State s -> State s -> Bool #

(<=) :: State s -> State s -> Bool #

(>) :: State s -> State s -> Bool #

(>=) :: State s -> State s -> Bool #

max :: State s -> State s -> State s #

min :: State s -> State s -> State s #

(Ord s, Hashable s) => Hashable (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

hashWithSalt :: Int -> State s -> Int

hash :: State s -> Int

type Rep (State s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep (State s) = D1 ('MetaData "State" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'True) (C1 ('MetaCons "State" 'PrefixI 'True) (S1 ('MetaSel ('Just "unState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map s Int))))

mapState :: Ord b => (a -> b) -> State a -> State b Source #

mark :: Ord s => State s -> s -> Int Source #

data Capacity s Source #

Constructors

Unbounded 
AllBounded Int 
Bounded (Map s Int) 

Instances

Instances details
(Ord s, Reader s) => Reader (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

ToDoc s => ToDoc (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

toDocPrec :: Int -> Capacity s -> Doc

toDocList :: [Capacity s] -> Doc

(Data s, Ord s) => Data (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

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

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

toConstr :: Capacity s -> Constr #

dataTypeOf :: Capacity s -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Associated Types

type Rep (Capacity s) 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep (Capacity s) = D1 ('MetaData "Capacity" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'False) (C1 ('MetaCons "Unbounded" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AllBounded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "Bounded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map s Int)))))

Methods

from :: Capacity s -> Rep (Capacity s) x #

to :: Rep (Capacity s) x -> Capacity s #

(Ord s, Read s) => Read (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Show s => Show (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

showsPrec :: Int -> Capacity s -> ShowS #

show :: Capacity s -> String #

showList :: [Capacity s] -> ShowS #

Eq s => Eq (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

(==) :: Capacity s -> Capacity s -> Bool #

(/=) :: Capacity s -> Capacity s -> Bool #

Ord s => Ord (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

compare :: Capacity s -> Capacity s -> Ordering #

(<) :: Capacity s -> Capacity s -> Bool #

(<=) :: Capacity s -> Capacity s -> Bool #

(>) :: Capacity s -> Capacity s -> Bool #

(>=) :: Capacity s -> Capacity s -> Bool #

max :: Capacity s -> Capacity s -> Capacity s #

min :: Capacity s -> Capacity s -> Capacity s #

Hashable s => Hashable (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

hashWithSalt :: Int -> Capacity s -> Int

hash :: Capacity s -> Int

type Rep (Capacity s) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep (Capacity s) = D1 ('MetaData "Capacity" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'False) (C1 ('MetaCons "Unbounded" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AllBounded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "Bounded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map s Int)))))

mapCapacity :: Ord a => (s -> a) -> Capacity s -> Capacity a Source #

data TransitionBehaviorConstraints Source #

Constraints on transition token behavior in the net

Constructors

TransitionBehaviorConstraints 

Fields

  • allowedTokenChanges :: Maybe Ordering

    Specify which token-changing transitions to allow. Just LT: allow only token-decreasing transitions (forbid increasing) Just GT: allow only token-increasing transitions (forbid decreasing) Nothing: allow both increasing and decreasing transitions Note: Just EQ is rejected during config validation as meaningless (would only allow preserving transitions, conflicting with areNonPreserving)

  • areNonPreserving :: Maybe Int

    Require exactly this many transitions to not be token-preserving. If Nothing, no restriction on number of non-preserving transitions.

Instances

Instances details
Reader TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

ToDoc TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Data TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

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

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

toConstr :: TransitionBehaviorConstraints -> Constr #

dataTypeOf :: TransitionBehaviorConstraints -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Associated Types

type Rep TransitionBehaviorConstraints 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep TransitionBehaviorConstraints = D1 ('MetaData "TransitionBehaviorConstraints" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'False) (C1 ('MetaCons "TransitionBehaviorConstraints" 'PrefixI 'True) (S1 ('MetaSel ('Just "allowedTokenChanges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ordering)) :*: S1 ('MetaSel ('Just "areNonPreserving") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))
Read TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Show TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Eq TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Ord TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Hashable TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep TransitionBehaviorConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep TransitionBehaviorConstraints = D1 ('MetaData "TransitionBehaviorConstraints" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'False) (C1 ('MetaCons "TransitionBehaviorConstraints" 'PrefixI 'True) (S1 ('MetaSel ('Just "allowedTokenChanges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ordering)) :*: S1 ('MetaSel ('Just "areNonPreserving") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

data ArrowDensityConstraints Source #

Arrow density constraints for net generation

Constructors

ArrowDensityConstraints 

Fields

Instances

Instances details
Reader ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

ToDoc ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Data ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

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

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

toConstr :: ArrowDensityConstraints -> Constr #

dataTypeOf :: ArrowDensityConstraints -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Associated Types

type Rep ArrowDensityConstraints 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep ArrowDensityConstraints = D1 ('MetaData "ArrowDensityConstraints" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'False) (C1 ('MetaCons "ArrowDensityConstraints" 'PrefixI 'True) ((S1 ('MetaSel ('Just "incomingArrowsPerTransition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)) :*: (S1 ('MetaSel ('Just "outgoingArrowsPerTransition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)) :*: S1 ('MetaSel ('Just "incomingArrowsPerPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)))) :*: (S1 ('MetaSel ('Just "outgoingArrowsPerPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)) :*: (S1 ('MetaSel ('Just "totalArrowsFromPlacesToTransitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)) :*: S1 ('MetaSel ('Just "totalArrowsFromTransitionsToPlaces") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int))))))
Read ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Show ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Eq ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Ord ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Hashable ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep ArrowDensityConstraints Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep ArrowDensityConstraints = D1 ('MetaData "ArrowDensityConstraints" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'False) (C1 ('MetaCons "ArrowDensityConstraints" 'PrefixI 'True) ((S1 ('MetaSel ('Just "incomingArrowsPerTransition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)) :*: (S1 ('MetaSel ('Just "outgoingArrowsPerTransition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)) :*: S1 ('MetaSel ('Just "incomingArrowsPerPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)))) :*: (S1 ('MetaSel ('Just "outgoingArrowsPerPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)) :*: (S1 ('MetaSel ('Just "totalArrowsFromPlacesToTransitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int)) :*: S1 ('MetaSel ('Just "totalArrowsFromTransitionsToPlaces") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Maybe Int))))))

noArrowDensityConstraints :: ArrowDensityConstraints Source #

Default arrow density constraints (no restrictions)

data Net s t Source #

Constructors

Net 

Fields

Instances

Instances details
(Ord s, Ord t, Reader s, Reader t) => Reader (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

(ToDoc s, ToDoc t) => ToDoc (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

toDocPrec :: Int -> Net s t -> Doc

toDocList :: [Net s t] -> Doc

(Data s, Data t, Ord s, Ord t) => Data (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Net s t -> c (Net s t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Net s t) #

toConstr :: Net s t -> Constr #

dataTypeOf :: Net s t -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Net s t -> Net s t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Net s t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Net s t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Net s t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Net s t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Net s t -> m (Net s t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Net s t -> m (Net s t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Net s t -> m (Net s t) #

Generic (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Associated Types

type Rep (Net s t) 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep (Net s t) = D1 ('MetaData "Net" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'False) (C1 ('MetaCons "Net" 'PrefixI 'True) ((S1 ('MetaSel ('Just "places") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set s)) :*: S1 ('MetaSel ('Just "transitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set t))) :*: (S1 ('MetaSel ('Just "connections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Connection s t]) :*: (S1 ('MetaSel ('Just "capacity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Capacity s)) :*: S1 ('MetaSel ('Just "start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (State s))))))

Methods

from :: Net s t -> Rep (Net s t) x #

to :: Rep (Net s t) x -> Net s t #

(Read s, Read t, Ord s, Ord t) => Read (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

readsPrec :: Int -> ReadS (Net s t) #

readList :: ReadS [Net s t] #

readPrec :: ReadPrec (Net s t) #

readListPrec :: ReadPrec [Net s t] #

(Show s, Show t) => Show (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

showsPrec :: Int -> Net s t -> ShowS #

show :: Net s t -> String #

showList :: [Net s t] -> ShowS #

(Eq t, Ord s) => Eq (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

(==) :: Net s t -> Net s t -> Bool #

(/=) :: Net s t -> Net s t -> Bool #

(Ord s, Ord t) => Ord (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

compare :: Net s t -> Net s t -> Ordering #

(<) :: Net s t -> Net s t -> Bool #

(<=) :: Net s t -> Net s t -> Bool #

(>) :: Net s t -> Net s t -> Bool #

(>=) :: Net s t -> Net s t -> Bool #

max :: Net s t -> Net s t -> Net s t #

min :: Net s t -> Net s t -> Net s t #

(Ord s, Hashable s, Hashable t) => Hashable (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

hashWithSalt :: Int -> Net s t -> Int

hash :: Net s t -> Int

type Rep (Net s t) Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep (Net s t) = D1 ('MetaData "Net" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'False) (C1 ('MetaCons "Net" 'PrefixI 'True) ((S1 ('MetaSel ('Just "places") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set s)) :*: S1 ('MetaSel ('Just "transitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set t))) :*: (S1 ('MetaSel ('Just "connections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Connection s t]) :*: (S1 ('MetaSel ('Just "capacity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Capacity s)) :*: S1 ('MetaSel ('Just "start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (State s))))))

bimapNet :: (Ord a, Ord b) => (s -> a) -> (t -> b) -> Net s t -> Net a b Source #

conforms :: Ord k => Capacity k -> State k -> Bool Source #

newtype Place Source #

Constructors

Place Int 

Instances

Instances details
Reader Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

ToDoc Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

toDocPrec :: Int -> Place -> Doc

toDocList :: [Place] -> Doc

Data Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

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

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

toConstr :: Place -> Constr #

dataTypeOf :: Place -> DataType #

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

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

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

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

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

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

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

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

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

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

Enum Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Generic Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Associated Types

type Rep Place 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep Place = D1 ('MetaData "Place" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'True) (C1 ('MetaCons "Place" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Methods

from :: Place -> Rep Place x #

to :: Rep Place x -> Place #

Read Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Show Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

showsPrec :: Int -> Place -> ShowS #

show :: Place -> String #

showList :: [Place] -> ShowS #

Eq Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

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

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

Ord Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

compare :: Place -> Place -> Ordering #

(<) :: Place -> Place -> Bool #

(<=) :: Place -> Place -> Bool #

(>) :: Place -> Place -> Bool #

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

max :: Place -> Place -> Place #

min :: Place -> Place -> Place #

Hashable Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

hashWithSalt :: Int -> Place -> Int

hash :: Place -> Int

type Rep Place Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep Place = D1 ('MetaData "Place" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'True) (C1 ('MetaCons "Place" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype Transition Source #

Constructors

Transition Int 

Instances

Instances details
Reader Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

ToDoc Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

toDocPrec :: Int -> Transition -> Doc

toDocList :: [Transition] -> Doc

Data Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

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

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

toConstr :: Transition -> Constr #

dataTypeOf :: Transition -> DataType #

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

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

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

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

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

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

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

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

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

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

Enum Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Generic Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Associated Types

type Rep Transition 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep Transition = D1 ('MetaData "Transition" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'True) (C1 ('MetaCons "Transition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
Read Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Show Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Eq Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Ord Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Hashable Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep Transition Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep Transition = D1 ('MetaData "Transition" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'True) (C1 ('MetaCons "Transition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype TransitionsList Source #

Constructors

TransitionsList 

Instances

Instances details
Reader TransitionsList Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

ToDoc TransitionsList Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Methods

toDocPrec :: Int -> TransitionsList -> Doc

toDocList :: [TransitionsList] -> Doc

Generic TransitionsList Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

Associated Types

type Rep TransitionsList 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep TransitionsList = D1 ('MetaData "TransitionsList" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'True) (C1 ('MetaCons "TransitionsList" 'PrefixI 'True) (S1 ('MetaSel ('Just "transitionsList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Transition])))
Show TransitionsList Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep TransitionsList Source # 
Instance details

Defined in Modelling.PetriNet.Reach.Type

type Rep TransitionsList = D1 ('MetaData "TransitionsList" "Modelling.PetriNet.Reach.Type" "modelling-tasks-0.0.0.1-2KiclaEArwR4yz1IHg8eKf" 'True) (C1 ('MetaCons "TransitionsList" 'PrefixI 'True) (S1 ('MetaSel ('Just "transitionsList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Transition])))

hasIsolatedNodes :: (Ord s, Ord t) => Net s t -> Bool Source #

Check if a net has any isolated nodes (nodes with no connections)

connectionTokenBehavior :: Connection s t -> (Int, Int) Source #

Determine the token behavior of a connection Returns: (consumed, produced)

satisfiesTransitionBehaviorConstraints :: Net s t -> TransitionBehaviorConstraints -> Bool Source #

Check if a net satisfies the given transition behavior constraints

countFusableTransitionsConsuming :: Ord s => [([s], t, [s])] -> Int Source #

Count transitions with exactly one input place which moreover is exclusively consumed from by that transition. More specifically, a "fusable transition consuming" is a transition t where: - t consumes (truly) from exactly one input place s, AND - t is the only transition that consumes from s (except for trivial back-and-forth looping transitions)

countFusableTransitionsProducing :: Ord s => [([s], t, [s])] -> Int Source #

Count transitions with exactly one output place which moreover is exclusively produced to by that transition. More specifically, a "fusable transition producing" is a transition t where: - t produces (truly) to exactly one place s, AND - t is the only transition that produces to s (except for trivial back-and-forth looping transitions)