ADPfusion-0.6.0.0: Efficient, high-level dynamic programming.

Safe HaskellNone
LanguageHaskell2010

ADP.Fusion.Core.Term.Switch

Description

Switches allow enabling and disabling individual rules on a global level.

TODO Consider moving the switch status to the type level. TODO Consider using patterns for the switch status and encode using Ints.

Synopsis

Documentation

data Switch where Source #

Terminal for the switch. The switch status is not given to any function, since processing of the rule already indicates that the switch is enabled -- if all other symbols parse successfully. Due to consistency, the type of result is ().

Constructors

Switch :: !SwitchStatus -> Switch 
Instances
Build Switch Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Switch

Associated Types

type Stack Switch :: Type Source #

(TermStream m (Z :. pos) (TermSymbol M Switch) (Elm (Term1 (Elm ls (PointL i))) (Z :. PointL i)) (Z :. PointL i), posLeft ~ LeftPosTy pos Switch (PointL i), TermStaticVar pos Switch (PointL i), MkStream m posLeft ls (PointL i)) => MkStream m (pos :: Type) (ls :!: Switch) (PointL i) Source # 
Instance details

Defined in ADP.Fusion.PointL.Term.Switch

Methods

mkStream :: Proxy pos -> (ls :!: Switch) -> Int# -> LimitType (PointL i) -> PointL i -> Stream m (Elm (ls :!: Switch) (PointL i)) Source #

TermStreamContext m ps ts s x0 i0 is (PointL O) => TermStream m (ps :. OStatic d :: Type) (TermSymbol ts Switch) s (is :. PointL O) Source # 
Instance details

Defined in ADP.Fusion.PointL.Term.Switch

Methods

termStream :: Proxy (ps :. OStatic d) -> TermSymbol ts Switch -> LimitType (is :. PointL O) -> (is :. PointL O) -> Stream m (TermState s Z Z) -> Stream m (TermState s (is :. PointL O) (TermArg (TermSymbol ts Switch))) Source #

TermStreamContext m ps ts s x0 i0 is (PointL I) => TermStream m (ps :. IStatic d :: Type) (TermSymbol ts Switch) s (is :. PointL I) Source # 
Instance details

Defined in ADP.Fusion.PointL.Term.Switch

Methods

termStream :: Proxy (ps :. IStatic d) -> TermSymbol ts Switch -> LimitType (is :. PointL I) -> (is :. PointL I) -> Stream m (TermState s Z Z) -> Stream m (TermState s (is :. PointL I) (TermArg (TermSymbol ts Switch))) Source #

TermStaticVar (IStatic d :: Type) Switch (PointL I) Source # 
Instance details

Defined in ADP.Fusion.PointL.Term.Switch

TermStaticVar (OStatic d :: Type) Switch (PointL O) Source # 
Instance details

Defined in ADP.Fusion.PointL.Term.Switch

(Show i, Show (RunningIndex i), Show (Elm ls i)) => Show (Elm (ls :!: Switch) i) Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Switch

Methods

showsPrec :: Int -> Elm (ls :!: Switch) i -> ShowS #

show :: Elm (ls :!: Switch) i -> String #

showList :: [Elm (ls :!: Switch) i] -> ShowS #

Element ls i => Element (ls :!: Switch) i Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Switch

Associated Types

data Elm (ls :!: Switch) i :: Type Source #

type RecElm (ls :!: Switch) i :: Type Source #

type Arg (ls :!: Switch) :: Type Source #

Methods

getArg :: Elm (ls :!: Switch) i -> Arg (ls :!: Switch) Source #

getIdx :: Elm (ls :!: Switch) i -> RunningIndex i Source #

getElm :: Elm (ls :!: Switch) i -> RecElm (ls :!: Switch) i Source #

type Stack Switch Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Switch

type TermArg Switch Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Switch

type TermArg Switch = ()
data Elm (ls :!: Switch) i Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Switch

data Elm (ls :!: Switch) i = ElmSwitch !(RunningIndex i) !(Elm ls i)
type Arg (ls :!: Switch) Source # 
Instance details

Defined in ADP.Fusion.Core.Term.Switch

type Arg (ls :!: Switch) = Arg ls :. ()
type LeftPosTy (IVariable d) Switch (PointL I) Source # 
Instance details

Defined in ADP.Fusion.PointL.Term.Switch

type LeftPosTy (IStatic d) Switch (PointL I) Source # 
Instance details

Defined in ADP.Fusion.PointL.Term.Switch

type LeftPosTy (OStatic d) Switch (PointL O) Source # 
Instance details

Defined in ADP.Fusion.PointL.Term.Switch