ginger-0.9.1.0: An implementation of the Jinja2 template language in Haskell

Safe HaskellNone
LanguageHaskell2010

Text.Ginger.GVal

Contents

Description

GVal is a generic unitype value, representing the kind of values that Ginger can understand.

Most of the types in this module are parametrized over an m type, which is the host monad for template execution, as passed to runGingerT. For most kinds of values, m is transparent, and in many cases a ToGVal instance can be written that works for all possible m; the reason we need to parametrize the values themselves over the carrier monad is because we want to support impure functions, which requires access to the underlying carrier monad (e.g. IO).

Synopsis

The Ginger Value type

data GVal m Source #

A variant type designed as the unitype for the template language. Any value referenced in a template, returned from within a template, or used in a template context, will be a GVal. m, in most cases, should be a Monad.

Some laws apply here, most notably:

Constructors

GVal 

Fields

Instances
FromGVal m (GVal m) Source # 
Instance details

Defined in Text.Ginger.GVal

ToGVal m (GVal m) Source #

Trivial instance for GVal itself.

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: GVal m -> GVal m Source #

Show (GVal m) Source #

For convenience, Show is implemented in a way that looks similar to JavaScript / JSON

Instance details

Defined in Text.Ginger.GVal

Methods

showsPrec :: Int -> GVal m -> ShowS #

show :: GVal m -> String #

showList :: [GVal m] -> ShowS #

IsString (GVal m) Source #

String -> GVal conversion uses the IsString class; because String is an alias for '[Char]', there is also a ToGVal instance for String, but it marshals strings as lists of characters, i.e., calling toGVal on a string produces a list of characters on the GVal side.

Instance details

Defined in Text.Ginger.GVal

Methods

fromString :: String -> GVal m #

ToJSON (GVal m) Source #

Conversion to JSON values attempts the following conversions, in order:

Note that the default conversions will never return booleans unless asJSON explicitly does this, because asText will always return *something*.

Instance details

Defined in Text.Ginger.GVal

PrintfArg (GVal m) Source # 
Instance details

Defined in Text.Ginger.GVal

Default (GVal m) Source #

The default GVal is equivalent to NULL.

Instance details

Defined in Text.Ginger.GVal

Methods

def :: GVal m #

ToHtml (GVal m) Source #

Converting to HTML hooks into the ToHtml instance for Text for most tags. Tags that have no obvious textual representation render as empty HTML.

Instance details

Defined in Text.Ginger.GVal

Methods

toHtml :: GVal m -> Html Source #

gappend :: GVal m -> GVal m -> GVal m Source #

marshalGVal :: GVal m -> GVal n Source #

Marshal a GVal between carrier monads. This will lose asFunction information, because functions cannot be transferred to other carrier monads, but it will keep all other data structures intact.

marshalGValEx :: (Functor m, Functor n) => (forall a. m a -> n a) -> (forall a. n a -> m a) -> GVal m -> GVal n Source #

Marshal a GVal between carrier monads. Unlike marshalGVal, asFunction information is retained by hoisting them using the provided hoisting functions. For Run monads, which is what GVal is typically used with, the hoistRun function can be used to construct suitable hoisting functions.

marshalFunction :: (Functor m, Functor n) => (forall a. m a -> n a) -> (forall a. n a -> m a) -> Function m -> Function n Source #

asHashMap :: GVal m -> Maybe (HashMap Text (GVal m)) Source #

Convenience wrapper around asDictItems to represent a GVal as a HashMap.

Representing functions as GVals

type Function m = [(Maybe Text, GVal m)] -> m (GVal m) Source #

A function that can be called from within a template execution context.

matchFuncArgs :: [Text] -> [(Maybe Text, GVal m)] -> (HashMap Text (GVal m), [GVal m], HashMap Text (GVal m)) Source #

Match arguments passed to a function at runtime against a list of declared argument names. matchFuncArgs argNames argsPassed returns (matchedArgs, positionalArgs, namedArgs), where matchedArgs is a list of arguments matched against declared names (by name or by position), positionalArgs are the unused positional (unnamed) arguments, and namedArgs are the unused named arguments.

Marshalling from Haskell to GVal

class ToGVal m a where Source #

Types that implement conversion to GVal.

Methods

toGVal :: a -> GVal m Source #

Instances
ToGVal m Value Source #

Convert Aeson Values to GVals over an arbitrary host monad. Because JSON cannot represent functions, this conversion will never produce a Function. Further, the ToJSON instance for such a GVal will always produce the exact Value that was use to construct the it.

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Value -> GVal m Source #

ToGVal m Html Source #

This instance is slightly wrong; the asBoolean, asNumber, and asText methods all treat the HTML source as plain text. We do this to avoid parsing the HTML back into a Text (and dealing with possible parser errors); the reason this instance exists at all is that we still want to be able to pass pre-rendered HTML around sometimes, and as long as we don't call any numeric or string functions on it, everything is fine. When such HTML values accidentally do get used as strings, the HTML source will bleed into the visible text, but at least this will not introduce an XSS vulnerability.

It is therefore recommended to avoid passing Html values into templates, and also to avoid calling any string functions on Html values inside templates (e.g. capturing macro output and then passing it through a textual filter).

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Html -> GVal m Source #

ToGVal m ByteString Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: ByteString -> GVal m Source #

ToGVal m ByteString Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: ByteString -> GVal m Source #

ToGVal m Text Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Text -> GVal m Source #

ToGVal m Text Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Text -> GVal m Source #

ToGVal m Char Source #

Single characters are treated as length-1 Texts.

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Char -> GVal m Source #

ToGVal m Bool Source #

Booleans render as 1 or empty string, and otherwise behave as expected.

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Bool -> GVal m Source #

ToGVal m ZonedTime Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: ZonedTime -> GVal m Source #

ToGVal m TimeLocale Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: TimeLocale -> GVal m Source #

ToGVal m TimeZone Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: TimeZone -> GVal m Source #

ToGVal m LocalTime Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: LocalTime -> GVal m Source #

ToGVal m TimeOfDay Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: TimeOfDay -> GVal m Source #

ToGVal m Day Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Day -> GVal m Source #

ToGVal m Scientific Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Scientific -> GVal m Source #

ToGVal m Integer Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Integer -> GVal m Source #

ToGVal m Int Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Int -> GVal m Source #

ToGVal m () Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: () -> GVal m Source #

ToGVal m SourcePos Source # 
Instance details

Defined in Text.Ginger.Parse

Methods

toGVal :: SourcePos -> GVal m Source #

ToGVal m v => ToGVal m [v] Source #

Haskell lists become list-like GVals

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: [v] -> GVal m Source #

ToGVal m v => ToGVal m (Maybe v) Source #

Nothing becomes NULL, Just unwraps.

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: Maybe v -> GVal m Source #

ToGVal m (GVal m) Source #

Trivial instance for GVal itself.

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: GVal m -> GVal m Source #

ToGVal m p => ToGVal m (RuntimeError p) Source # 
Instance details

Defined in Text.Ginger.Run.Type

Methods

toGVal :: RuntimeError p -> GVal m Source #

(ToGVal m a, ToGVal m b) => ToGVal m (a, b) Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: (a, b) -> GVal m Source #

ToGVal m v => ToGVal m (HashMap Text v) Source #

HashMap of Text becomes a dictionary-like GVal

Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: HashMap Text v -> GVal m Source #

(ToGVal m a, ToGVal m b, ToGVal m c) => ToGVal m (a, b, c) Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: (a, b, c) -> GVal m Source #

(ToGVal m a, ToGVal m b, ToGVal m c, ToGVal m d) => ToGVal m (a, b, c, d) Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

toGVal :: (a, b, c, d) -> GVal m Source #

dayToDict :: Day -> [(Text, GVal m)] Source #

scientificToText :: Scientific -> Text Source #

Silly helper function, needed to bypass the default Show instance of Scientific in order to make integral Scientifics look like integers.

fromFunction :: Function m -> GVal m Source #

Turn a Function into a GVal

Convenience API for constructing heterogenous dictionaries.

type Pair m = (Text, GVal m) Source #

A key/value pair, used for constructing dictionary GVals using a compact syntax.

dict :: [Pair m] -> GVal m Source #

Construct a dictionary GVal from a list of pairs. Internally, this uses a hashmap, so element order will not be preserved.

orderedDict :: [Pair m] -> GVal m Source #

Construct an ordered dictionary GVal from a list of pairs. Internally, this conversion uses both a hashmap (for O(1) lookup) and the original list, so element order is preserved, but there is a bit of a memory overhead.

(~>) :: ToGVal m a => Text -> a -> Pair m infixr 8 Source #

Construct a pair from a key and a value.

Convenience API for constructing heterogenous lists

type Cons m = [GVal m] Source #

gcons :: ToGVal m a => a -> Cons m -> Cons m Source #

Alias for '(~:)'.

(~:) :: ToGVal m a => a -> Cons m -> Cons m infixr 5 Source #

This operator allows constructing heterogenous lists using cons-style syntax, e.g.:

>>> asText $ list ("Found " ~: (6 :: Int) ~: " items" ~: [] :: [GVal IO])
"Found 6 items"

list :: Cons m -> GVal m Source #

Construct a GVal from a list of GVals. This is equivalent to the toGVal implementation of [GVal m], but typed more narrowly for clarity and disambiguation.

Inspecting GVals / Marshalling GVal to Haskell

isList :: GVal m -> Bool Source #

Check if the given GVal is a list-like object

isDict :: GVal m -> Bool Source #

Check if the given GVal is a dictionary-like object

lookupIndex :: Int -> GVal m -> Maybe (GVal m) Source #

Treat a GVal as a flat list and look up a value by integer index. If the value is not a List, or if the index exceeds the list length, return Nothing.

lookupIndexMay :: Maybe Int -> GVal m -> Maybe (GVal m) Source #

Helper function; look up a value by an integer index when the index may or may not be available. If no index is given, return Nothing.

lookupKey :: Text -> GVal m -> Maybe (GVal m) Source #

Strictly-typed lookup: treat value as a dictionary-like object and look up the value at a given key.

lookupLoose :: GVal m -> GVal m -> Maybe (GVal m) Source #

Loosely-typed lookup: try dictionary-style lookup first (treat index as a string, and container as a dictionary), if that doesn't yield anything (either because the index is not string-ish, or because the container doesn't provide dictionary-style access), try index-based lookup.

lookupLooseDef :: GVal m -> GVal m -> GVal m -> GVal m Source #

Like lookupLoose, but fall back to the given default value if the key is not in the dictionary, or if the indexee is not a dictionary-like object.

(~!) :: FromGVal m v => GVal m -> GVal m -> Maybe v Source #

keys :: GVal m -> Maybe [Text] Source #

Treat a GVal as a dictionary and list all the keys, with no particular ordering.

toNumber :: GVal m -> Maybe Scientific Source #

Convert a GVal to a number.

toInt :: GVal m -> Maybe Int Source #

Convert a GVal to an Int. The conversion will fail when the value is not numeric, and also if it is too large to fit in an Int.

toInteger :: GVal m -> Maybe Integer Source #

Convert a GVal to an Integer The conversion will fail when the value is not an integer

toIntDef :: Int -> GVal m -> Int Source #

Convert a GVal to an Int, falling back to the given default if the conversion fails.

toInt0 :: GVal m -> Int Source #

Convert a GVal to an Int, falling back to zero (0) if the conversion fails.

toBoolean :: GVal m -> Bool Source #

Loose cast to boolean.

Numeric zero, empty strings, empty lists, empty objects, Null, and boolean False are considered falsy, anything else (including functions) is considered true-ish.

toFunction :: GVal m -> Maybe (Function m) Source #

Dynamically cast to a function. This yields Just a Function if the value is a function, Nothing if it's not.

class FromGVal m a where Source #

Minimal complete definition

Nothing

Instances
FromGVal m TimeLocale Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m TimeZone Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m ZonedTime Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m LocalTime Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m TimeOfDay Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m Day Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m () Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m Value Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m Bool Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m ByteString Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m ByteString Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m Text Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m Integer Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m Scientific Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m Int Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m a => FromGVal m [a] Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m a => FromGVal m (Maybe a) Source # 
Instance details

Defined in Text.Ginger.GVal

FromGVal m (GVal m) Source # 
Instance details

Defined in Text.Ginger.GVal

(FromGVal m a, FromGVal m b) => FromGVal m (a, b) Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

fromGValEither :: GVal m -> Either String (a, b) Source #

fromGVal :: GVal m -> Maybe (a, b) Source #

(FromGVal m a, FromGVal m b, FromGVal m c) => FromGVal m (a, b, c) Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

fromGValEither :: GVal m -> Either String (a, b, c) Source #

fromGVal :: GVal m -> Maybe (a, b, c) Source #

(FromGVal m a, FromGVal m b, FromGVal m c, FromGVal m d) => FromGVal m (a, b, c, d) Source # 
Instance details

Defined in Text.Ginger.GVal

Methods

fromGValEither :: GVal m -> Either String (a, b, c, d) Source #

fromGVal :: GVal m -> Maybe (a, b, c, d) Source #

fromGValM :: (Monad m, FromGVal m a) => GVal m -> m a Source #

pairwise :: (a -> b) -> (a, a) -> (b, b) Source #

packPair :: ([Char], [Char]) -> (Text, Text) Source #

unpackPair :: (Text, Text) -> ([Char], [Char]) Source #