-- | Offers an 'activePair' pattern for convenient implementation of interaction nets. module GraphRewriting.Pattern.InteractionNet where import Prelude.Unicode import Data.View import GraphRewriting.Graph.Types import GraphRewriting.Graph.Read import GraphRewriting.Pattern -- | Index that identifies the principal port within the list of ports class INet v where principalPort ∷ v → Int -- | Instead of @(,)@ to save parentheses data Pair x = x :-: x pair ∷ Pair a → (a,a) pair (x :-: y) = (x,y) activePair ∷ (View [Port] n, View v n, INet v) ⇒ Pattern n (Pair v) activePair = do v1 ← node n1 ← previous ports1 ← liftReader (inspectNode n1) let pp1 = ports1 !! principalPort v1 v2 ← adverse pp1 n1 n2 ← previous ports2 ← liftReader (inspectNode n2) let pp2 = ports2 !! principalPort v2 require (pp1 ≡ pp2) return (v1 :-: v2)