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

Safe HaskellNone
LanguageHaskell2010

ADP.Fusion.Term.Strng.Type

Synopsis

Documentation

data Strng v x where Source #

Strng terminals return "strings", i.e. vectors of Chrs. They allow the user to specify [ 0 .. ] atoms to be parsed at once. It is possible to both, limit the minimal and maximal number.

NOTE gadt comments are not parsed by haddock?

Constructors

Strng :: Vector v x => (Int -> Int -> v x -> v x) -> Int -> Int -> v x -> Strng v x 

Instances

(Show i, Show (RunningIndex i), Show (v x), Show (Elm ls i)) => Show (Elm ((:!:) ls (Strng v x)) i) Source # 

Methods

showsPrec :: Int -> Elm (ls :!: Strng v x) i -> ShowS #

show :: Elm (ls :!: Strng v x) i -> String #

showList :: [Elm (ls :!: Strng v x) i] -> ShowS #

Build (Strng v x) Source # 

Associated Types

type Stack (Strng v x) :: * Source #

Methods

build :: Strng v x -> Stack (Strng v x) Source #

Element ls i => Element ((:!:) ls (Strng v x)) i Source # 

Associated Types

data Elm ((:!:) ls (Strng v x)) i :: * Source #

type RecElm ((:!:) ls (Strng v x)) i :: * Source #

type Arg ((:!:) ls (Strng v x)) :: * Source #

Methods

getArg :: Elm (ls :!: Strng v x) i -> Arg (ls :!: Strng v x) Source #

getIdx :: Elm (ls :!: Strng v x) i -> RunningIndex i Source #

getElm :: Elm (ls :!: Strng v x) i -> RecElm (ls :!: Strng v x) i Source #

type Stack (Strng v x) Source # 
type Stack (Strng v x) = (:!:) S (Strng v x)
data Elm ((:!:) ls (Strng v x)) Source # 
data Elm ((:!:) ls (Strng v x)) = ElmStrng !(v x) !(RunningIndex i) !(Elm ls i)
type Arg ((:!:) ls (Strng v x)) Source # 
type Arg ((:!:) ls (Strng v x)) = (:.) (Arg ls) (v x)
type TermArg (Strng v x) Source # 
type TermArg (Strng v x) = v x

manyS :: Vector v x => v x -> Strng v x Source #

someS :: Vector v x => v x -> Strng v x Source #

strng :: Vector v x => Int -> Int -> v x -> Strng v x Source #