zsyntax-0.2.0.0: Automated theorem prover for the Zsyntax biochemical calculus

Safe HaskellNone
LanguageHaskell2010

Zsyntax.ReactionList

Synopsis

Documentation

data CtrlType Source #

Constructors

Regular 
SupersetClosed 
Instances
Eq CtrlType Source # 
Instance details

Defined in Zsyntax.ReactionList

Ord CtrlType Source # 
Instance details

Defined in Zsyntax.ReactionList

Show CtrlType Source # 
Instance details

Defined in Zsyntax.ReactionList

data CtrlSetCtxt af Source #

Constructors

CSC 
Instances
Eq af => Eq (CtrlSetCtxt af) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

(==) :: CtrlSetCtxt af -> CtrlSetCtxt af -> Bool #

(/=) :: CtrlSetCtxt af -> CtrlSetCtxt af -> Bool #

Ord af => Ord (CtrlSetCtxt af) Source # 
Instance details

Defined in Zsyntax.ReactionList

Show af => Show (CtrlSetCtxt af) Source # 
Instance details

Defined in Zsyntax.ReactionList

newtype CtrlSet af Source #

A control set is a set of linear contexts made up of atomic formulas, that is, multisets of formulas of the bonding language.

For a context C in a control set S we may want to consider its superset closure, that is, have that C' is in S for all superset C' of C. We therefore distinguish between superset-closed contexts and normal contexts in a control set. Actually, superset-closed contexts are the only way to specify infinite control sets.

Constructors

CS 

Fields

Instances
Eq af => Eq (CtrlSet af) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

(==) :: CtrlSet af -> CtrlSet af -> Bool #

(/=) :: CtrlSet af -> CtrlSet af -> Bool #

Ord af => Ord (CtrlSet af) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

compare :: CtrlSet af -> CtrlSet af -> Ordering #

(<) :: CtrlSet af -> CtrlSet af -> Bool #

(<=) :: CtrlSet af -> CtrlSet af -> Bool #

(>) :: CtrlSet af -> CtrlSet af -> Bool #

(>=) :: CtrlSet af -> CtrlSet af -> Bool #

max :: CtrlSet af -> CtrlSet af -> CtrlSet af #

min :: CtrlSet af -> CtrlSet af -> CtrlSet af #

Show af => Show (CtrlSet af) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

showsPrec :: Int -> CtrlSet af -> ShowS #

show :: CtrlSet af -> String #

showList :: [CtrlSet af] -> ShowS #

Ord af => Semigroup (CtrlSet af) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

(<>) :: CtrlSet af -> CtrlSet af -> CtrlSet af #

sconcat :: NonEmpty (CtrlSet af) -> CtrlSet af #

stimes :: Integral b => b -> CtrlSet af -> CtrlSet af #

Ord af => Monoid (CtrlSet af) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

mempty :: CtrlSet af #

mappend :: CtrlSet af -> CtrlSet af -> CtrlSet af #

mconcat :: [CtrlSet af] -> CtrlSet af #

fromCSCtxts :: (Foldable f, Ord af) => f (CtrlSetCtxt af) -> CtrlSet af Source #

respectsCC :: Ord af => MultiSet af -> CtrlSetCtxt af -> Bool Source #

Checks whether a linear context "respects" a control set context.

msRespectsCS :: Ord af => MultiSet af -> CtrlSet af -> Bool Source #

Checks whether a linear context "respects" a control set, that is, if it respects all the control set contexts.

newtype RList eb cs Source #

A reaction list is a list of pairs, where in each pair the first component is an elementary base, and the second component is a control set.

Constructors

RL 

Fields

  • unRL :: [(eb, cs)]
     
Instances
(Eq eb, Eq cs) => Eq (RList eb cs) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

(==) :: RList eb cs -> RList eb cs -> Bool #

(/=) :: RList eb cs -> RList eb cs -> Bool #

(Ord eb, Ord cs) => Ord (RList eb cs) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

compare :: RList eb cs -> RList eb cs -> Ordering #

(<) :: RList eb cs -> RList eb cs -> Bool #

(<=) :: RList eb cs -> RList eb cs -> Bool #

(>) :: RList eb cs -> RList eb cs -> Bool #

(>=) :: RList eb cs -> RList eb cs -> Bool #

max :: RList eb cs -> RList eb cs -> RList eb cs #

min :: RList eb cs -> RList eb cs -> RList eb cs #

(Show eb, Show cs) => Show (RList eb cs) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

showsPrec :: Int -> RList eb cs -> ShowS #

show :: RList eb cs -> String #

showList :: [RList eb cs] -> ShowS #

Semigroup (RList eb cs) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

(<>) :: RList eb cs -> RList eb cs -> RList eb cs #

sconcat :: NonEmpty (RList eb cs) -> RList eb cs #

stimes :: Integral b => b -> RList eb cs -> RList eb cs #

Monoid (RList eb cs) Source # 
Instance details

Defined in Zsyntax.ReactionList

Methods

mempty :: RList eb cs #

mappend :: RList eb cs -> RList eb cs -> RList eb cs #

mconcat :: [RList eb cs] -> RList eb cs #

justCS :: Monoid eb => cs -> RList eb cs Source #

extend :: Semigroup eb => eb -> RList eb cs -> RList eb cs Source #

Extends a reaction list with an elementary base.

respectsRList :: Semigroup eb => (eb -> cs -> Bool) -> eb -> RList eb cs -> Bool Source #

Checks whether an elementary base "respects" a reaction list, given a function to check whether the base "respects" the list's control sets.