dzen-dhall-1.0.2: Configure dzen2 bars in Dhall language

Safe HaskellNone
LanguageHaskell2010

DzenDhall.AST

Synopsis

Documentation

data AST Source #

Constructors

ASTText Text

Text.

ASTs AST AST

Branching

ASTProp Property AST

Some property that does not change the visible size of the inner AST.

ASTShape Shape

Some shape (^r, ^i, ^co, etc.)

ASTPadding Int Padding AST 
EmptyAST 
Instances
Eq AST Source # 
Instance details

Defined in DzenDhall.AST

Methods

(==) :: AST -> AST -> Bool #

(/=) :: AST -> AST -> Bool #

Show AST Source # 
Instance details

Defined in DzenDhall.AST

Methods

showsPrec :: Int -> AST -> ShowS #

show :: AST -> String #

showList :: [AST] -> ShowS #

Generic AST Source # 
Instance details

Defined in DzenDhall.AST

Associated Types

type Rep AST :: Type -> Type #

Methods

from :: AST -> Rep AST x #

to :: Rep AST x -> AST #

Semigroup AST Source # 
Instance details

Defined in DzenDhall.AST

Methods

(<>) :: AST -> AST -> AST #

sconcat :: NonEmpty AST -> AST #

stimes :: Integral b => b -> AST -> AST #

Monoid AST Source # 
Instance details

Defined in DzenDhall.AST

Methods

mempty :: AST #

mappend :: AST -> AST -> AST #

mconcat :: [AST] -> AST #

Renderable AST Source # 
Instance details

Defined in DzenDhall.AST.Render

Methods

render :: AST -> Render () Source #

type Rep AST Source # 
Instance details

Defined in DzenDhall.AST

data Split a Source #

Represents (possibly partial) result of splitAST computation.

Constructors

EmptyL a

a split with empty LHS tree.

EmptyR a Int

a split that has no RHS tree.

Twain a a Int

a split with left side's length guaranteed to be equal to the given number (third constructor's argument).

Instances
Functor Split Source # 
Instance details

Defined in DzenDhall.AST

Methods

fmap :: (a -> b) -> Split a -> Split b #

(<$) :: a -> Split b -> Split a #

Eq a => Eq (Split a) Source # 
Instance details

Defined in DzenDhall.AST

Methods

(==) :: Split a -> Split a -> Bool #

(/=) :: Split a -> Split a -> Bool #

Show a => Show (Split a) Source # 
Instance details

Defined in DzenDhall.AST

Methods

showsPrec :: Int -> Split a -> ShowS #

show :: Split a -> String #

showList :: [Split a] -> ShowS #

getProgress :: Split a -> Int Source #

Get progress (width of LHS) of a Split, O(1).

(=>>) :: Semigroup a => Split a -> Split a -> Split a Source #

Join results of two (maybe partial) splits.

Example: -- read as "incomplete split with empty RHS and some LHS l of length n -- joined together with a complete split with LHS a of length n' and some -- RHS b is a complete split with LHS equal to (l <> a) with length (n + n') -- and RHS equal to b". EmptyR l n =>> Twain a b n' = Twain (l <> a) b (n + n')

split :: Int -> AST -> (AST, AST) Source #

Like splitAt, but for ASTs.

splitAST :: Int -> AST -> Split AST Source #

Split tree at the given position.