Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
).
- data GVal m = GVal {}
- type Function m = [(Maybe Text, GVal m)] -> m (GVal m)
- matchFuncArgs :: [Text] -> [(Maybe Text, GVal m)] -> (HashMap Text (GVal m), [GVal m], HashMap Text (GVal m))
- class ToGVal m a where
- type Pair m = (Text, GVal m)
- dict :: [Pair m] -> GVal m
- orderedDict :: [Pair m] -> GVal m
- (~>) :: ToGVal m a => Text -> a -> Pair m
- scientificToText :: Scientific -> Text
- fromFunction :: Function m -> GVal m
- isList :: GVal m -> Bool
- isDict :: GVal m -> Bool
- lookupIndex :: Int -> GVal m -> Maybe (GVal m)
- lookupIndexMay :: Maybe Int -> GVal m -> Maybe (GVal m)
- lookupKey :: Text -> GVal m -> Maybe (GVal m)
- lookupLoose :: GVal m -> GVal m -> Maybe (GVal m)
- keys :: GVal m -> Maybe [Text]
- toNumber :: GVal m -> Maybe Scientific
- toInt :: GVal m -> Maybe Int
- toBoolean :: GVal m -> Bool
- toFunction :: GVal m -> Maybe (Function m)
The Ginger Value type
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:
- when isNull
is True
, then all of asFunction
, asText
, asNumber
,
asHtml
, asList
, asDictItems
, and length
should produce Nothing
- when isNull
is True
, then asBoolean
should produce False
- when asNumber
is not Nothing
, then asBoolean
should only return
False
for exactly zero
- Nothing
-ness of length
should match one or both of asList
/ asDictItems
GVal | |
|
ToGVal m (GVal m) Source | Trivial instance for |
Show (GVal m) Source | For convenience, |
IsString (GVal m) Source |
|
Default (GVal m) Source | The default |
ToHtml (GVal m) Source | Converting to HTML hooks into the ToHtml instance for |
Representing functions as GVal
s
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
Types that implement conversion to GVal
.
ToGVal m Value Source | Convert Aeson |
ToGVal m Html Source | This instance is slightly wrong; the It is therefore recommended to avoid passing |
ToGVal m Text Source | |
ToGVal m Text Source | |
ToGVal m Char Source | Single characters are treated as length-1 |
ToGVal m Bool Source | Booleans render as 1 or empty string, and otherwise behave as expected. |
ToGVal m Scientific Source | |
ToGVal m Integer Source | |
ToGVal m Int Source | |
ToGVal m v => ToGVal m [v] Source | Haskell lists become list-like |
ToGVal m v => ToGVal m (Maybe v) Source | |
ToGVal m (GVal m) Source | Trivial instance for |
(ToGVal m a, ToGVal m b) => ToGVal m (a, b) Source | |
ToGVal m v => ToGVal m (HashMap Text v) Source | |
(ToGVal m a, ToGVal m b, ToGVal m c) => ToGVal m (a, b, c) Source | |
(ToGVal m a, ToGVal m b, ToGVal m c, ToGVal m d) => ToGVal m (a, b, c, d) Source |
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.
scientificToText :: Scientific -> Text Source
Silly helper function, needed to bypass the default Show
instance of
Scientific
in order to make integral Scientific
s look like integers.
Inspecting GVal
s / Marshalling GVal
to Haskell
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.
keys :: GVal m -> Maybe [Text] Source
Treat a GVal
as a dictionary and list all the keys, with no particular
ordering.