Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data CtrlType
- data CtrlSetCtxt af = CSC {}
- newtype CtrlSet af = CS {
- unCS :: Set (CtrlSetCtxt af)
- fromCSCtxts :: (Foldable f, Ord af) => f (CtrlSetCtxt af) -> CtrlSet af
- toCtxtList :: CtrlSet af -> [CtrlSetCtxt af]
- respectsCC :: Ord af => MultiSet af -> CtrlSetCtxt af -> Bool
- msRespectsCS :: Ord af => MultiSet af -> CtrlSet af -> Bool
- newtype RList eb cs = RL {
- unRL :: [(eb, cs)]
- justCS :: Monoid eb => cs -> RList eb cs
- extend :: Semigroup eb => eb -> RList eb cs -> RList eb cs
- respectsRList :: Semigroup eb => (eb -> cs -> Bool) -> eb -> RList eb cs -> Bool
Documentation
data CtrlSetCtxt af Source #
Instances
Eq af => Eq (CtrlSetCtxt af) Source # | |
Defined in Zsyntax.ReactionList (==) :: CtrlSetCtxt af -> CtrlSetCtxt af -> Bool # (/=) :: CtrlSetCtxt af -> CtrlSetCtxt af -> Bool # | |
Ord af => Ord (CtrlSetCtxt af) Source # | |
Defined in Zsyntax.ReactionList compare :: CtrlSetCtxt af -> CtrlSetCtxt af -> Ordering # (<) :: CtrlSetCtxt af -> CtrlSetCtxt af -> Bool # (<=) :: CtrlSetCtxt af -> CtrlSetCtxt af -> Bool # (>) :: CtrlSetCtxt af -> CtrlSetCtxt af -> Bool # (>=) :: CtrlSetCtxt af -> CtrlSetCtxt af -> Bool # max :: CtrlSetCtxt af -> CtrlSetCtxt af -> CtrlSetCtxt af # min :: CtrlSetCtxt af -> CtrlSetCtxt af -> CtrlSetCtxt af # | |
Show af => Show (CtrlSetCtxt af) Source # | |
Defined in Zsyntax.ReactionList showsPrec :: Int -> CtrlSetCtxt af -> ShowS # show :: CtrlSetCtxt af -> String # showList :: [CtrlSetCtxt af] -> ShowS # |
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.
CS | |
|
Instances
Eq af => Eq (CtrlSet af) Source # | |
Ord af => Ord (CtrlSet af) Source # | |
Show af => Show (CtrlSet af) Source # | |
Ord af => Semigroup (CtrlSet af) Source # | |
Ord af => Monoid (CtrlSet af) Source # | |
fromCSCtxts :: (Foldable f, Ord af) => f (CtrlSetCtxt af) -> CtrlSet af Source #
toCtxtList :: CtrlSet af -> [CtrlSetCtxt 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.
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.
Instances
(Eq eb, Eq cs) => Eq (RList eb cs) Source # | |
(Ord eb, Ord cs) => Ord (RList eb cs) Source # | |
Defined in Zsyntax.ReactionList | |
(Show eb, Show cs) => Show (RList eb cs) Source # | |
Semigroup (RList eb cs) Source # | |
Monoid (RList eb cs) Source # | |