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

Lasercutter

Synopsis

Core types

data Parser bc t a 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

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 #

runParser Source #

Arguments

:: (Monoid bc, IsTree t) 
=> (t -> bc)

A means of summarizing the current node for tracking breadcrumbs. If you don't need breadcrumbs, use const ().

-> t

The tree to parse.

-> Parser bc t a

How to parse the tree.

-> Maybe a 

Run a parser over a tree in a single pass.

Since: 0.1.0.0

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

Building parsers

Primitives

self :: Parser bc t t Source #

Get the current node.

Since: 0.1.0.0

proj :: (t -> a) -> Parser bc t a Source #

Project a value out of the current node. This is the main way to build primitive parsers.

Since: 0.1.0.0

Controlling failure

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

one :: Parser bc t [a] -> Parser bc t a Source #

Get the first result of a list of results, failing if there are none.

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

empty :: Alternative f => f a #

The identity of <|>

(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #

An associative binary operation

Traversing trees

onChildren :: Parser bc t a -> Parser bc t [a] Source #

Run the given parser on every immediate child of the current node.

Since: 0.1.0.0

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

Run a parser on the immediate children of the current node, returning the first success.

Since: 0.1.0.0

target :: (t -> Bool) -> Parser bc t a -> Parser bc t [a] Source #

Run the given parser on every predicate-satisfying subtree of the current node. This combinator is not recursive --- that is, if the predicate is satisfied by both a node and its descendent, the descendent *will not* receive the parser.

Since: 0.1.0.0

targetMap :: (t -> Maybe a) -> Parser bc t [a] Source #

Run the given function on every subtree, accumulating those which return Just.

Since: 0.1.0.0

Conditional parsing

when :: Parser bc t Bool -> Parser bc t a -> Parser bc t a Source #

when pc pa returns pa when pc evaluates to True, failing otherwise.

Since: 0.1.0.0

whenNode :: (t -> Bool) -> Parser bc t a -> Parser bc t a Source #

whenNode f pa returns pa when pc evaluates to True on the current node, failing otherwise.

Since: 0.1.0.0

ifS :: Selective f => f Bool -> f a -> f a -> f a #

Branch on a Boolean value, skipping unnecessary effects.

ifNode :: (t -> Bool) -> Parser bc t a -> Parser bc t a -> Parser bc t a Source #

ifNode f pt pf runs pt when f evaluates to True on the current node, running pf otherwise.

Since: 0.1.0.0

Breadcrumbs

All parsers support a notion of *breadcrumbs* --- a monoid that gets accumulated along subtrees. Callers to runParser can choose a *summarization* function which describes how to generate the breadcrumb monoid from the current node.

Breadcrumbs are often used to refine the results of target, which has no notion of history, and thus can be too coarse for many position-depending parsing tasks.

breadcrumbs :: Parser bc t bc Source #

Get the breadcrumbs at the current node. This is useful for refining the coarse-grained matches of target by restricting matches to certain subtrees.

Since: 0.1.0.0

onBreadcrumbs :: (bc -> a) -> Parser bc t a Source #

Get a value computed on the current breadcrumbs.

Since: 0.1.0.0

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

Transformer the breadcrumbs of a Parser.

Since: 0.1.0.0

Re-exports

The Parser is an instance of all of the following classes, and thus all of these methods are available on Parsers.

Profunctor

Even though Parsers are contravariant in their breadcrumbs and tree type, this instance targets only the tree. Use mapBreadcrumbs to modify the breadcrumbs.

dimap :: Profunctor p => (a -> b) -> (c -> d) -> p b c -> p a d #

Map over both arguments at the same time.

dimap f g ≡ lmap f . rmap g

rmap :: Profunctor p => (b -> c) -> p a b -> p a c #

Map the second argument covariantly.

rmapdimap id

lmap :: Profunctor p => (a -> b) -> p b c -> p a c #

Map the first argument contravariantly.

lmap f ≡ dimap f id

Applicative

liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c #

Lift a binary function to actions.

Some functors support an implementation of liftA2 that is more efficient than the default one. In particular, if fmap is an expensive operation, it is likely better to use liftA2 than to fmap over the structure and then use <*>.

This became a typeclass method in 4.10.0.0. Prior to that, it was a function defined in terms of <*> and fmap.

Using ApplicativeDo: 'liftA2 f as bs' can be understood as the do expression

do a <- as
   b <- bs
   pure (f a b)

Alternative

optional :: Alternative f => f a -> f (Maybe a) #

One or none.

guard :: Alternative f => Bool -> f () #

Conditional failure of Alternative computations. Defined by

guard True  = pure ()
guard False = empty

Examples

Expand

Common uses of guard include conditionally signaling an error in an error monad and conditionally rejecting the current choice in an Alternative-based parser.

As an example of signaling an error in the error monad Maybe, consider a safe division function safeDiv x y that returns Nothing when the denominator y is zero and Just (x `div` y) otherwise. For example:

>>> safeDiv 4 0
Nothing
>>> safeDiv 4 2
Just 2

A definition of safeDiv using guards, but not guard:

safeDiv :: Int -> Int -> Maybe Int
safeDiv x y | y /= 0    = Just (x `div` y)
            | otherwise = Nothing

A definition of safeDiv using guard and Monad do-notation:

safeDiv :: Int -> Int -> Maybe Int
safeDiv x y = do
  guard (y /= 0)
  return (x `div` y)

asum :: (Foldable t, Alternative f) => t (f a) -> f a #

The sum of a collection of actions, generalizing concat.

>>> asum [Just "Hello", Nothing, Just "World"]
Just "Hello"

Filterable

mapMaybe :: Filterable f => (a -> Maybe b) -> f a -> f b #

Like mapMaybe.

catMaybes :: Filterable f => f (Maybe a) -> f a #

Selective

Parsers are boring Selective functors that are unfortunately unable to elide any effects. Nevertheless, the Selective API is often quite useful for everyday parsing tasks.

select :: Selective f => f (Either a b) -> f (a -> b) -> f b #

(<*?) :: Selective f => f (Either a b) -> f (a -> b) -> f b infixl 4 #

An operator alias for select, which is sometimes convenient. It tries to follow the notational convention for Applicative operators. The angle bracket pointing to the left means we always use the corresponding value. The value on the right, however, may be skipped, hence the question mark.

branch :: Selective f => f (Either a b) -> f (a -> c) -> f (b -> c) -> f c #

The branch function is a natural generalisation of select: instead of skipping an unnecessary effect, it chooses which of the two given effectful functions to apply to a given argument; the other effect is unnecessary. It is possible to implement branch in terms of select, which is a good puzzle (give it a try!).

We can also implement select via branch:

selectB :: Selective f => f (Either a b) -> f (a -> b) -> f b
selectB x y = branch x y (pure id)

fromMaybeS :: Selective f => f a -> f (Maybe a) -> f a #

A lifted version of fromMaybe.

orElse :: (Selective f, Semigroup e) => f (Either e a) -> f (Either e a) -> f (Either e a) #

Return the first Right value. If both are Left's, accumulate errors.

andAlso :: (Selective f, Semigroup a) => f (Either e a) -> f (Either e a) -> f (Either e a) #

Accumulate the Right values, or return the first Left.

(<||>) :: Selective f => f Bool -> f Bool -> f Bool #

A lifted version of lazy Boolean OR.

(<&&>) :: Selective f => f Bool -> f Bool -> f Bool #

A lifted version of lazy Boolean AND.

foldS :: (Selective f, Foldable t, Monoid a) => t (f (Either e a)) -> f (Either e a) #

Generalised folding with the short-circuiting behaviour.

anyS :: Selective f => (a -> f Bool) -> [a] -> f Bool #

A lifted version of any. Retains the short-circuiting behaviour.

allS :: Selective f => (a -> f Bool) -> [a] -> f Bool #

A lifted version of all. Retains the short-circuiting behaviour.

bindS :: (Bounded a, Enum a, Eq a, Selective f) => f a -> (a -> f b) -> f b #

A restricted version of monadic bind. Fails with an error if the Bounded and Enum instances for a do not cover all values of a.