| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Slick.Caching
Synopsis
- simpleJsonCache :: ShakeValue q => q -> Action Value -> Rules (Action Value)
- simpleJsonCache' :: forall q a. (ToJSON a, FromJSON a, ShakeValue q) => q -> Action a -> Rules (Action a)
- jsonCache :: ShakeValue q => (q -> Action Value) -> Rules (q -> Action Value)
- jsonCache' :: forall a q. (ToJSON a, FromJSON a, ShakeValue q) => (q -> Action a) -> Rules (q -> Action a)
Documentation
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.