hakyllbars-1.0.1.0: A Hakyll compiler for Handlebars-like templates
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hakyllbars.Context

Synopsis

Documentation

newtype Context a Source #

Constructors

Context 

Instances

Instances details
Monoid (Context a) Source # 
Instance details

Defined in Hakyllbars.Context

Methods

mempty :: Context a #

mappend :: Context a -> Context a -> Context a #

mconcat :: [Context a] -> Context a #

Semigroup (Context a) Source # 
Instance details

Defined in Hakyllbars.Context

Methods

(<>) :: Context a -> Context a -> Context a #

sconcat :: NonEmpty (Context a) -> Context a #

stimes :: Integral b => b -> Context a -> Context a #

FromValue (Context a) a Source # 
Instance details

Defined in Hakyllbars.Context

IntoContext (Context a) a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue (Context a) a Source # 
Instance details

Defined in Hakyllbars.Context

data TemplateState a Source #

Constructors

TemplateState 

Instances

Instances details
IntoValue (TemplateRunner a (ContextValue a)) a Source # 
Instance details

Defined in Hakyllbars.Context

(IntoValue v a, FromValue w a) => FromValue (FunctionValue v w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(FromValue v a, IntoValue w a) => IntoValue (FunctionValue v w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(IntoValue v a, IntoValue x a, FromValue w a) => FromValue (FunctionValue2 v x w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(FromValue v a, FromValue x a, IntoValue w a) => IntoValue (FunctionValue2 v x w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(IntoValue v a, IntoValue x a, IntoValue y a, FromValue w a) => FromValue (FunctionValue3 v x y w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(FromValue v a, FromValue x a, FromValue y a, IntoValue w a) => IntoValue (FunctionValue3 v x y w a) a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoValue :: FunctionValue3 v x y w a -> ContextValue a Source #

(IntoValue v a, IntoValue x a, IntoValue y a, IntoValue z a, FromValue w a) => FromValue (FunctionValue4 v x y z w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(FromValue v a, FromValue x a, FromValue y a, FromValue z a, IntoValue w a) => IntoValue (FunctionValue4 v x y z w a) a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoValue :: FunctionValue4 v x y z w a -> ContextValue a Source #

tplWithContext :: Context a -> TemplateRunner a b -> TemplateRunner a b Source #

Place context within a given scope.

tplGet :: FromValue v a => String -> TemplateRunner a v Source #

Get a value from the context by name and convert it.

tplGetWithItemContext :: FromValue v a => Item a -> Context a -> String -> TemplateRunner a v Source #

Get a value from a specific item's context by name and convert it.

tplPut :: Context a -> TemplateRunner a () Source #

Place context in global scope.

tplWithCall :: String -> TemplateRunner a b -> TemplateRunner a b Source #

Perform an action within the scope of a call.

tplWithPos :: (x -> SourcePos) -> (x -> TemplateRunner a b) -> x -> TemplateRunner a b Source #

tplWithField :: String -> TemplateRunner a b -> TemplateRunner a b Source #

Perform an action within the scope of a field call.

tplFail :: String -> TemplateRunner a b Source #

Fail with an error message and trace.

tplTried :: String -> TemplateRunner a b Source #

Fail with a no-result message and trace.

tplTrace :: TemplateRunner a [String] Source #

Return the current call stack, with the most recent call first.

tplTraced :: String -> TemplateRunner a String Source #

Get a formatted trace message with the most recent call first.

field :: IntoValue v a => String -> (Item a -> TemplateRunner a v) -> Context a Source #

Apply f to an item if key is requested.

missingField :: Context a Source #

Reports missing field.

constField :: IntoValue v a => String -> v -> Context a Source #

Const-valued field, returns the same val per key.

itemsField :: String -> Context a -> [Item a] -> Context a Source #

Creates a field containing a list of items.

mapField :: (FromValue v a, IntoValue w a) => (v -> w) -> Context a -> Context a Source #

Mapping of function g after context f.

bindField :: (FromValue v a, IntoValue w a) => (v -> TemplateRunner a w) -> Context a -> Context a Source #

Binding of function g after context f.

composeField :: Context a -> Context a -> Context a Source #

Alternation of context g after context f.

hashMapField :: IntoValue v a => HashMap String v -> Context a Source #

Lookup of val by key into provided HashMap.

functionField2 :: (FromValue v a, FromValue x a, IntoValue w a) => String -> (v -> x -> TemplateRunner a w) -> Context a Source #

functionField3 :: (FromValue v a, FromValue x a, FromValue y a, IntoValue w a) => String -> (v -> x -> y -> TemplateRunner a w) -> Context a Source #

functionField4 :: (FromValue v a, FromValue x a, FromValue y a, FromValue z a, IntoValue w a) => String -> (v -> x -> y -> z -> TemplateRunner a w) -> Context a Source #

class IntoContext v a where Source #

Methods

intoContext :: v -> Context a Source #

Instances

Instances details
IntoContext Object a Source # 
Instance details

Defined in Hakyllbars.Context

IntoContext (Context a) a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue v a => IntoContext [(String, v)] a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoContext :: [(String, v)] -> Context a Source #

IntoValue v a => IntoContext (HashMap String v) a Source # 
Instance details

Defined in Hakyllbars.Context

type FunctionValue v w a = v -> TemplateRunner a w Source #

type FunctionValue2 v x w a = v -> FunctionValue x w a Source #

type FunctionValue3 v x y w a = v -> FunctionValue2 x y w a Source #

type FunctionValue4 v x y z w a = v -> FunctionValue3 x y z w a Source #

class IntoValue' (flag :: Bool) v a where Source #

Methods

intoValue' :: Proxy flag -> v -> ContextValue a Source #

Instances

Instances details
IntoValue' 'True String a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue v a => IntoValue' 'False [v] a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoValue' :: Proxy 'False -> [v] -> ContextValue a Source #

type family FString a :: Bool where ... Source #

Equations

FString Char = 'True 
FString _ = 'False 

class IntoValue v a where Source #

Inject a concrete type v into a ContextValue a.

Methods

intoValue :: v -> ContextValue a Source #

Instances

Instances details
IntoValue Value a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue Block a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue () a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoValue :: () -> ContextValue a Source #

IntoValue Bool a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue Double a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue Int a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue (Item a) a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue (Context a) a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue (ContextValue a) a Source # 
Instance details

Defined in Hakyllbars.Context

IntoValue v a => IntoValue (Maybe v) a Source # 
Instance details

Defined in Hakyllbars.Context

(FString v ~ flag, IntoValue' flag [v] a) => IntoValue [v] a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoValue :: [v] -> ContextValue a Source #

IntoValue (TemplateRunner a (ContextValue a)) a Source # 
Instance details

Defined in Hakyllbars.Context

(IntoValue v a, IntoValue x a) => IntoValue (v, x) a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoValue :: (v, x) -> ContextValue a Source #

(FromValue v a, IntoValue w a) => IntoValue (FunctionValue v w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(FromValue v a, FromValue x a, IntoValue w a) => IntoValue (FunctionValue2 v x w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(FromValue v a, FromValue x a, FromValue y a, IntoValue w a) => IntoValue (FunctionValue3 v x y w a) a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoValue :: FunctionValue3 v x y w a -> ContextValue a Source #

(FromValue v a, FromValue x a, FromValue y a, FromValue z a, IntoValue w a) => IntoValue (FunctionValue4 v x y z w a) a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

intoValue :: FunctionValue4 v x y z w a -> ContextValue a Source #

class FromValue v a where Source #

Extract a concrete value of type v from a ContextValue a.

Instances

Instances details
FromValue Block a Source # 
Instance details

Defined in Hakyllbars.Context

FromValue Bool a Source # 
Instance details

Defined in Hakyllbars.Context

FromValue Double a Source # 
Instance details

Defined in Hakyllbars.Context

FromValue Int a Source # 
Instance details

Defined in Hakyllbars.Context

FromValue (Item a) a Source # 
Instance details

Defined in Hakyllbars.Context

FromValue (Context a) a Source # 
Instance details

Defined in Hakyllbars.Context

FromValue (ContextValue a) a Source # 
Instance details

Defined in Hakyllbars.Context

(FString v ~ flag, FromValue' flag [v] a) => FromValue [v] a Source # 
Instance details

Defined in Hakyllbars.Context

(FromValue v a, FromValue x a) => FromValue (v, x) a Source # 
Instance details

Defined in Hakyllbars.Context

Methods

fromValue :: ContextValue a -> TemplateRunner a (v, x) Source #

(IntoValue v a, FromValue w a) => FromValue (FunctionValue v w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(IntoValue v a, IntoValue x a, FromValue w a) => FromValue (FunctionValue2 v x w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(IntoValue v a, IntoValue x a, IntoValue y a, FromValue w a) => FromValue (FunctionValue3 v x y w a) a Source # 
Instance details

Defined in Hakyllbars.Context

(IntoValue v a, IntoValue x a, IntoValue y a, IntoValue z a, FromValue w a) => FromValue (FunctionValue4 v x y z w a) a Source # 
Instance details

Defined in Hakyllbars.Context

class FromValue' (flag :: Bool) v a where Source #

Methods

fromValue' :: Proxy flag -> ContextValue a -> TemplateRunner a v Source #

Instances

Instances details
FromValue' 'True String a Source # 
Instance details

Defined in Hakyllbars.Context

FromValue v a => FromValue' 'False [v] a Source # 
Instance details

Defined in Hakyllbars.Context