slick-0.1.1.0

Safe HaskellNone
LanguageHaskell2010

Slick

Contents

Synopsis

Slick

This module re-exports everything you need to use Slick

Mustache

compileTemplate' :: FilePath -> Action Template Source #

Like compileTemplate but tracks changes to template files and partials within Shake.

Pandoc

markdownToHTML :: Text -> Action Value Source #

Convert markdown text into a Value; The Value has a "content" key containing rendered HTML Metadata is assigned on the respective keys in the Value

markdownToHTML' :: FromJSON a => Text -> Action a Source #

Like markdownToHTML but allows returning any JSON serializable object

makePandocReader :: PandocReader textType -> textType -> Action (Pandoc, Value) Source #

Given a reader from Readers this creates a loader which given the source document will read its metadata into a Value returning both the Pandoc object and the metadata within an Action

makePandocReader' :: FromJSON a => PandocReader textType -> textType -> Action (Pandoc, a) Source #

Like makePandocReader but will deserialize the metadata into any object which implements FromJSON. Failure to deserialize will fail the Shake build.

loadUsing :: PandocReader textType -> PandocWriter -> textType -> Action Value Source #

Load in a source document using the given PandocReader, then render the Pandoc into text using the given PandocWriter. Returns a Value wherein the rendered text is set to the "content" key and any metadata is set to its respective key in the Value

loadUsing' :: FromJSON a => PandocReader textType -> PandocWriter -> textType -> Action a Source #

Like loadUsing but allows also deserializes the Value into any object which implements FromJSON. Failure to deserialize will fail the Shake build.

Aeson

convert :: (FromJSON a, ToJSON a, FromJSON b) => a -> Action b Source #

Attempt to convert between two JSON serializable objects (or Values). Failure to deserialize fails the Shake build.

Shake

simpleJsonCache :: ShakeValue q => q -> Action Value -> Rules (Action Value) Source #

A wrapper around jsonCache which simplifies caching of values which do NOT depend on an input parameter. Unfortunately Shake still requires that the key type implement several typeclasses, however this is easily accomplished using GeneralizedNewtypeDeriving and a wrapper around (). example usage:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where
newtype ProjectList = ProjectList ()
  deriving (Show, Eq, Hashable, Binary, NFData)

Within your shake Rules:

projectCache = simpleJsonCache (ProjectList ()) $ do
  -- load your project list here; returning it as a Value

simpleJsonCache' :: forall q a. (ToJSON a, FromJSON a, ShakeValue q) => q -> Action a -> Rules (Action a) Source #

Like simpleJsonCache but allows caching any JSON serializable object.

jsonCache :: ShakeValue q => (q -> Action Value) -> Rules (q -> Action Value) Source #

A wrapper around addOracleCache which given a q which is a ShakeValue allows caching and retrieving Values within Shake. See documentation on addOracleCache or see Slick examples for more info.

-- We need to define a unique datatype as our cache key
newtype PostFilePath =
  PostFilePath String
-- We can derive the classes we need (using GeneralizedNewtypeDeriving) 
-- so long as the underlying type implements them
  deriving (Show, Eq, Hashable, Binary, NFData)
-- now in our shake rules we can create a cache by providing a loader action

do
postCache <- jsonCache $ \(PostFilePath path) ->
  readFile' path >>= markdownToHTML . Text.pack
-- Now use postCache inside an Action to load your post with caching!

jsonCache' :: forall a q. (ToJSON a, FromJSON a, ShakeValue q) => (q -> Action a) -> Rules (q -> Action a) Source #

Like jsonCache but allows caching/retrieving any JSON serializable objects.

Re-exported

overText :: (Text -> Text) -> Value #

Creates a Lambda which first renders the contained section and then applies the supplied function

compileTemplate :: String -> Text -> Either ParseError Template #

Compiles a Template directly from Text without checking for missing partials. the result will be a Template with an empty partials cache.

compileTemplateWithCache :: [FilePath] -> TemplateCache -> FilePath -> IO (Either ParseError Template) #

Compile a mustache template providing a list of precompiled templates that do not have to be recompiled.

localAutomaticCompile :: FilePath -> IO (Either ParseError Template) #

Compile the template with the search space set to only the current directory

automaticCompile :: [FilePath] -> FilePath -> IO (Either ParseError Template) #

Compiles a mustache template provided by name including the mentioned partials.

The same can be done manually using getFile, mustacheParser and getPartials.

This function also ensures each partial is only compiled once even though it may be included by other partials including itself.

A reference to the included template will be found in each including templates partials section.

substituteNode :: Node Text -> SubM () #

Main substitution function

substituteAST :: STree -> SubM () #

Substitute an entire STree rather than just a single Node

catchSubstitute :: SubM a -> SubM (a, Text) #

Catch the results of running the inner substitution.

checkedSubstituteValue :: Template -> Value -> ([SubstitutionError], Text) #

Substitutes all mustache defined tokens (or tags) for values found in the provided data structure and report any errors and warnings encountered during substitution.

This function always produces results, as in a fully substituted/rendered template, it never halts on errors. It simply reports them in the first part of the tuple. Sites with errors are usually substituted with empty string.

The second value in the tuple is a template rendered with errors ignored. Therefore if you must enforce that there were no errors during substitution you must check that the error list in the first tuple value is empty.

substituteValue :: Template -> Value -> Text #

Substitutes all mustache defined tokens (or tags) for values found in the provided data structure.

checkedSubstitute :: ToMustache k => Template -> k -> ([SubstitutionError], Text) #

Substitutes all mustache defined tokens (or tags) for values found in the provided data structure and report any errors and warnings encountered during substitution.

This function always produces results, as in a fully substituted/rendered template, it never halts on errors. It simply reports them in the first part of the tuple. Sites with errors are usually substituted with empty string.

The second value in the tuple is a template rendered with errors ignored. Therefore if you must enforce that there were no errors during substitution you must check that the error list in the first tuple value is empty.

Equivalent to checkedSubstituteValue . toMustache.

substitute :: ToMustache k => Template -> k -> Text #

Substitutes all mustache defined tokens (or tags) for values found in the provided data structure.

Equivalent to substituteValue . toMustache.

(~=) :: ToJSON ι => Text -> ι -> Pair infixr 8 #

Map keys to values that provide a ToJSON instance

Recommended in conjunction with the OverloadedStrings extension.

object :: [Pair] -> Value #

Convenience function for creating Object values.

This function is supposed to be used in conjuction with the ~> and ~= operators.

Examples

Expand
  data Address = Address { ... }

  instance Address ToJSON where
    ...

  data Person = Person { name :: String, address :: Address }

  instance ToMustache Person where
    toMustache (Person { name, address }) = object
      [ "name" ~> name
      , "address" ~= address
      ]

Here we can see that we can use the ~> operator for values that have themselves a ToMustache instance, or alternatively if they lack such an instance but provide an instance for the ToJSON typeclass we can use the ~= operator.

class ToMustache ω where #

Conversion class

Minimal complete definition

toMustache

Methods

toMustache :: ω -> Value #

Instances
ToMustache Bool 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Char 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Double 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Float 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Int 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Integer 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache () 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: () -> Value #

listToMustache :: [()] -> Value

ToMustache Text 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Scientific 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Value 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Text 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache Value 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache α => ToMustache [α] 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: [α] -> Value #

listToMustache :: [[α]] -> Value

ToMustache ω => ToMustache (Maybe ω) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: Maybe ω -> Value #

listToMustache :: [Maybe ω] -> Value

ToMustache ω => ToMustache (Set ω) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: Set ω -> Value #

listToMustache :: [Set ω] -> Value

ToMustache ω => ToMustache (Seq ω) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: Seq ω -> Value #

listToMustache :: [Seq ω] -> Value

ToMustache ω => ToMustache (HashSet ω) 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache ω => ToMustache (Vector ω) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: Vector ω -> Value #

listToMustache :: [Vector ω] -> Value

ToMustache (STree -> SubM STree) 
Instance details

Defined in Text.Mustache.Internal.Types

(ToMustache α, ToMustache β) => ToMustache (α, β) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: (α, β) -> Value #

listToMustache :: [(α, β)] -> Value

ToMustache ω => ToMustache (Map String ω) 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache ω => ToMustache (Map Text ω) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: Map Text ω -> Value #

listToMustache :: [Map Text ω] -> Value

ToMustache ω => ToMustache (Map Text ω) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: Map Text ω -> Value #

listToMustache :: [Map Text ω] -> Value

ToMustache ω => ToMustache (HashMap String ω) 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache ω => ToMustache (HashMap Text ω) 
Instance details

Defined in Text.Mustache.Internal.Types

ToMustache ω => ToMustache (HashMap Text ω) 
Instance details

Defined in Text.Mustache.Internal.Types

(ToMustache α, ToMustache β, ToMustache γ) => ToMustache (α, β, γ) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: (α, β, γ) -> Value #

listToMustache :: [(α, β, γ)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ) => ToMustache (α, β, γ, δ) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: (α, β, γ, δ) -> Value #

listToMustache :: [(α, β, γ, δ)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε) => ToMustache (α, β, γ, δ, ε) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: (α, β, γ, δ, ε) -> Value #

listToMustache :: [(α, β, γ, δ, ε)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ) => ToMustache (α, β, γ, δ, ε, ζ) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: (α, β, γ, δ, ε, ζ) -> Value #

listToMustache :: [(α, β, γ, δ, ε, ζ)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ, ToMustache η) => ToMustache (α, β, γ, δ, ε, ζ, η) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: (α, β, γ, δ, ε, ζ, η) -> Value #

listToMustache :: [(α, β, γ, δ, ε, ζ, η)] -> Value

(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ, ToMustache η, ToMustache θ) => ToMustache (α, β, γ, δ, ε, ζ, η, θ) 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

toMustache :: (α, β, γ, δ, ε, ζ, η, θ) -> Value #

listToMustache :: [(α, β, γ, δ, ε, ζ, η, θ)] -> Value

data Template #

A compiled Template with metadata.

Constructors

Template 
Instances
Show Template 
Instance details

Defined in Text.Mustache.Internal.Types

Lift TemplateCache 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

lift :: TemplateCache -> Q Exp #

Lift Template 
Instance details

Defined in Text.Mustache.Internal.Types

Methods

lift :: Template -> Q Exp #

MonadReader (Context Value, TemplateCache) SubM 
Instance details

Defined in Text.Mustache.Internal.Types