lasercutter-0.1.0.0: A high-powered, single-pass tree parser.
Safe HaskellNone
LanguageHaskell2010

Lasercutter.Types

Synopsis

Documentation

class IsTree t where Source #

Lasercutter supports any inductive tree types, as witnessed by getChildren.

Since: 0.1.0.0

Methods

getChildren :: t -> [t] Source #

Get all children of the current node.

Since: 0.1.0.0

data Parser bc t a where Source #

A tree parser which runs all queries in a single pass. This is accomplished via a free encoding of the applicative structure, which can be arbitrarily reassociated for better performance.

Since: 0.1.0.0

Constructors

Pure :: a -> Parser bc t a

The free pure constructor.

Since: 0.1.0.0

LiftA2 :: (b -> c -> a) -> Parser bc t b -> Parser bc t c -> Parser bc t a

The free liftA2 constructor. This is an inlining of Day convolution.

Since: 0.1.0.0

GetCrumbs :: Parser bc t bc

Get the breadcrumbs at the current part of the tree.

Since: 0.1.0.0

Target :: (t -> Bool) -> Parser bc t a -> Parser bc t [a]

Run the given parser at every subtree which matches the given predicate. This is not recursive --- that is, a given subtree only runs the given parser once, not in all further matching subtrees.

Since: 0.1.0.0

OnChildren :: Parser bc t a -> Parser bc t [a]

Run the given parser on each child of the current node.

Since: 0.1.0.0

Current :: Parser bc t t

Get the current node.

Since: 0.1.0.0

Expect :: Parser bc t (Maybe a) -> Parser bc t a

Swallow a parsed Maybe, failing the parser if it was Nothing. Don't use this constructor explicitly; prefer expect which maintains some invariants.

optional is the inverse to this parser.

Since: 0.1.0.0

Fail :: Parser bc t a

Immediately fail a parse. Equivalent to Expect (pure Nothing).

Since: 0.1.0.0

Instances

Instances details
Profunctor (Parser bc) Source # 
Instance details

Defined in Lasercutter.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Parser bc b c -> Parser bc a d #

lmap :: (a -> b) -> Parser bc b c -> Parser bc a c #

rmap :: (b -> c) -> Parser bc a b -> Parser bc a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Parser bc a b -> Parser bc a c #

(.#) :: forall a b c q. Coercible b a => Parser bc b c -> q a b -> Parser bc a c #

Functor (Parser bc t) Source # 
Instance details

Defined in Lasercutter.Types

Methods

fmap :: (a -> b) -> Parser bc t a -> Parser bc t b #

(<$) :: a -> Parser bc t b -> Parser bc t a #

Applicative (Parser bc t) Source # 
Instance details

Defined in Lasercutter.Types

Methods

pure :: a -> Parser bc t a #

(<*>) :: Parser bc t (a -> b) -> Parser bc t a -> Parser bc t b #

liftA2 :: (a -> b -> c) -> Parser bc t a -> Parser bc t b -> Parser bc t c #

(*>) :: Parser bc t a -> Parser bc t b -> Parser bc t b #

(<*) :: Parser bc t a -> Parser bc t b -> Parser bc t a #

Alternative (Parser bc t) Source # 
Instance details

Defined in Lasercutter.Types

Methods

empty :: Parser bc t a #

(<|>) :: Parser bc t a -> Parser bc t a -> Parser bc t a #

some :: Parser bc t a -> Parser bc t [a] #

many :: Parser bc t a -> Parser bc t [a] #

Selective (Parser bc t) Source # 
Instance details

Defined in Lasercutter.Types

Methods

select :: Parser bc t (Either a b) -> Parser bc t (a -> b) -> Parser bc t b #

Filterable (Parser bc t) Source # 
Instance details

Defined in Lasercutter.Types

Methods

mapMaybe :: (a -> Maybe b) -> Parser bc t a -> Parser bc t b #

catMaybes :: Parser bc t (Maybe a) -> Parser bc t a #

filter :: (a -> Bool) -> Parser bc t a -> Parser bc t a #

Show (Parser bc t a) Source # 
Instance details

Defined in Lasercutter.Types

Methods

showsPrec :: Int -> Parser bc t a -> ShowS #

show :: Parser bc t a -> String #

showList :: [Parser bc t a] -> ShowS #

Semigroup a => Semigroup (Parser bc t a) Source # 
Instance details

Defined in Lasercutter.Types

Methods

(<>) :: Parser bc t a -> Parser bc t a -> Parser bc t a #

sconcat :: NonEmpty (Parser bc t a) -> Parser bc t a #

stimes :: Integral b => b -> Parser bc t a -> Parser bc t a #

Monoid a => Monoid (Parser bc t a) Source # 
Instance details

Defined in Lasercutter.Types

Methods

mempty :: Parser bc t a #

mappend :: Parser bc t a -> Parser bc t a -> Parser bc t a #

mconcat :: [Parser bc t a] -> Parser bc t a #

mapTree :: (t -> t') -> Parser bc t' a -> Parser bc t a Source #

Transform the type of tree that a Parser operates over.

Since: 0.1.0.0

data Split bc t a where Source #

A parser to run on children, and a subsequent continuation for how to parse the parent.

Since: 0.1.0.0

Constructors

Split 

Fields

  • :: Parser bc t a

    The parser to run on children.

  • -> ([a] -> Parser bc t b)

    Continuation for how to subsequently parse the current node.

  • -> Split bc t b
     

expect :: Parser bc t (Maybe a) -> Parser bc t a Source #

Swallow a parsed Maybe, failing the parser if it was Nothing.

Use try or optional as the inverse to this parser.

Since: 0.1.0.0

try :: Parser bc t a -> Parser bc t (Maybe a) Source #

Like optional, but slightly more efficient.

Since: 0.1.0.0