ede-0.2.9: Templating language with similar syntax and features to Liquid or Jinja2.

Safe HaskellNone
LanguageHaskell2010

Text.EDE.Filters

Contents

Description

The means to construct your own filters.

Synopsis

Prelude

The default filters available to a template are documented by the subsequent categories.

These filters cannot be overriden and attempting to supply your own filters to renderWith will cause the similarly named filters to disappear when they are merged with the prelude during evaluation. (See: union)

Boolean

  • ! :: Bool -> Bool (See: not)
  • && :: Bool -> Bool -> Bool
  • || :: Bool -> Bool -> Bool

Equality

  • == :: a -> a -> Bool
  • != :: a -> a -> Bool (See: /=)

Relational

  • > :: a -> a -> Bool
  • >= :: a -> a -> Bool
  • <= :: a -> a -> Bool
  • <= :: a -> a -> Bool

Numeric

  • + :: Scientific -> Scientific -> Scientific
  • - :: Scientific -> Scientific -> Scientific
  • * :: Scientific -> Scientific -> Scientific
  • abs :: Scientific -> Scientific
  • signum :: Scientific -> Scientific
  • negate :: Scientific -> Scientific

Fractional

  • truncate :: Scientific -> Scientific
  • round :: Scientific -> Scientific
  • ceiling :: Scientific -> Scientific
  • floor :: Scientific -> Scientific

Textual

Collection

  • length :: Collection -> Scientific (See: Text.length, Vector.length, HashMap.size)
  • empty :: Collection -> Bool (See: Text:null, Vector.null, HashMap.null)

Polymorphic

Constructing filters

data Term Source #

A HOAS representation of (possibly partially applied) values in the environment.

Constructors

TVal !Value 
TLam (Term -> Result Term) 

Instances

Pretty Term Source # 

Methods

pretty :: Term -> Doc #

prettyList :: [Term] -> Doc #

Quote Term Source # 

Methods

quote :: Id -> Int -> Term -> Term Source #

Classes

class Quote a where Source #

Methods

quote :: Id -> Int -> a -> Term Source #

quote :: ToJSON a => Id -> Int -> a -> Term Source #

Instances

Quote Bool Source # 

Methods

quote :: Id -> Int -> Bool -> Term Source #

Quote Double Source # 

Methods

quote :: Id -> Int -> Double -> Term Source #

Quote Int Source # 

Methods

quote :: Id -> Int -> Int -> Term Source #

Quote Integer Source # 

Methods

quote :: Id -> Int -> Integer -> Term Source #

Quote Builder Source # 

Methods

quote :: Id -> Int -> Builder -> Term Source #

Quote Scientific Source # 

Methods

quote :: Id -> Int -> Scientific -> Term Source #

Quote Text Source # 

Methods

quote :: Id -> Int -> Text -> Term Source #

Quote Object Source # 

Methods

quote :: Id -> Int -> Object -> Term Source #

Quote Array Source # 

Methods

quote :: Id -> Int -> Array -> Term Source #

Quote Value Source # 

Methods

quote :: Id -> Int -> Value -> Term Source #

Quote Text Source # 

Methods

quote :: Id -> Int -> Text -> Term Source #

Quote Term Source # 

Methods

quote :: Id -> Int -> Term -> Term Source #

Quote [Text] Source # 

Methods

quote :: Id -> Int -> [Text] -> Term Source #

Quote [Value] Source # 

Methods

quote :: Id -> Int -> [Value] -> Term Source #

(Unquote a, Quote b) => Quote (a -> b) Source # 

Methods

quote :: Id -> Int -> (a -> b) -> Term Source #

Restricted quoters

(@:) :: Quote a => Id -> a -> (Id, Term) Source #

qapply :: Delta -> Term -> Term -> Result Term Source #

Fully apply two Terms.

qpoly2 :: Quote a => Id -> (Value -> Value -> a) -> (Id, Term) Source #

Quote a binary function which takes the most general binding value.

qnum1 :: Id -> (Scientific -> Scientific) -> (Id, Term) Source #

Quote an unary numeric function.

qnum2 :: Quote a => Id -> (Scientific -> Scientific -> a) -> (Id, Term) Source #

Quote a binary numeric function.

qcol1 :: (Quote a, Quote b, Quote c) => Id -> (Text -> a) -> (Object -> b) -> (Array -> c) -> (Id, Term) Source #

Quote a comprehensive set of unary functions to create a binding that supports all collection types.

Errors

typeErr :: Id -> Int -> Doc -> Doc -> Result a Source #

argumentErr :: Pretty a => Id -> Int -> a -> Result b Source #