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

Safe HaskellNone
LanguageHaskell2010

Text.EDE.Filters

Contents

Description

A default set of prelude-like filters and the means to construct your own.

Please be aware that some of the defaultFilters are assumed to be present (for example during loop unrolling and assignment of else branches via empty).

It's recommended you supplement the default filters rather than replacing them completely. (But hey, it's your call!)

Synopsis

Prelude

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

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

Fractional

Textual

  • takeWord :: Text -> Text
  • dropWord :: Text -> Text
  • lowerHead :: Text -> Text
  • upperHead :: Text -> Text
  • toTitle :: Text -> Text
  • toCamel :: Text -> Text
  • toPascal :: Text -> Text
  • toSnake :: Text -> Text
  • toSpinal :: Text -> Text
  • toTrain :: Text -> Text
  • toLower :: Text -> Text
  • toUpper :: Text -> Text
  • toOrdinal :: Number -> Text

See: text-manipulate

Collection

Polymorphic

Constructing filters

data Binding Source

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

Constructors

BVal !Value 
BLam (Binding -> Result Binding) 

Classes

Restricted quoters

qapply :: Binding -> Binding -> Result Binding Source

Attempt to apply two Bindings.

qpoly2 :: Quote a => (Value -> Value -> a) -> Binding Source

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

qnum1 :: (Scientific -> Scientific) -> Binding Source

Quote an unary numeric function.

qnum2 :: Quote a => (Scientific -> Scientific -> a) -> Binding Source

Quote a binary numeric function.

qcol1 :: Quote a => (Text -> a) -> (Object -> a) -> (Array -> a) -> Binding Source

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

Errors

typeOf :: Value -> String Source

Retrieve a consistent type from a Value to use in error messages.