{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Slick.Caching {-# DEPRECATED "No longer necessary with slick >= 0.3.0.0" #-}
( simpleJsonCache
, simpleJsonCache'
, jsonCache
, jsonCache'
)
where
import Data.Aeson as A
import Data.ByteString.Lazy
import Development.Shake hiding (Resource)
import Development.Shake.Classes
import GHC.Generics (Generic)
newtype CacheQuery q =
CacheQuery q
deriving (Int -> CacheQuery q -> ShowS
[CacheQuery q] -> ShowS
CacheQuery q -> String
(Int -> CacheQuery q -> ShowS)
-> (CacheQuery q -> String)
-> ([CacheQuery q] -> ShowS)
-> Show (CacheQuery q)
forall q. Show q => Int -> CacheQuery q -> ShowS
forall q. Show q => [CacheQuery q] -> ShowS
forall q. Show q => CacheQuery q -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall q. Show q => Int -> CacheQuery q -> ShowS
showsPrec :: Int -> CacheQuery q -> ShowS
$cshow :: forall q. Show q => CacheQuery q -> String
show :: CacheQuery q -> String
$cshowList :: forall q. Show q => [CacheQuery q] -> ShowS
showList :: [CacheQuery q] -> ShowS
Show, CacheQuery q -> CacheQuery q -> Bool
(CacheQuery q -> CacheQuery q -> Bool)
-> (CacheQuery q -> CacheQuery q -> Bool) -> Eq (CacheQuery q)
forall q. Eq q => CacheQuery q -> CacheQuery q -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall q. Eq q => CacheQuery q -> CacheQuery q -> Bool
== :: CacheQuery q -> CacheQuery q -> Bool
$c/= :: forall q. Eq q => CacheQuery q -> CacheQuery q -> Bool
/= :: CacheQuery q -> CacheQuery q -> Bool
Eq, (forall x. CacheQuery q -> Rep (CacheQuery q) x)
-> (forall x. Rep (CacheQuery q) x -> CacheQuery q)
-> Generic (CacheQuery q)
forall x. Rep (CacheQuery q) x -> CacheQuery q
forall x. CacheQuery q -> Rep (CacheQuery q) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall q x. Rep (CacheQuery q) x -> CacheQuery q
forall q x. CacheQuery q -> Rep (CacheQuery q) x
$cfrom :: forall q x. CacheQuery q -> Rep (CacheQuery q) x
from :: forall x. CacheQuery q -> Rep (CacheQuery q) x
$cto :: forall q x. Rep (CacheQuery q) x -> CacheQuery q
to :: forall x. Rep (CacheQuery q) x -> CacheQuery q
Generic, Get (CacheQuery q)
[CacheQuery q] -> Put
CacheQuery q -> Put
(CacheQuery q -> Put)
-> Get (CacheQuery q)
-> ([CacheQuery q] -> Put)
-> Binary (CacheQuery q)
forall q. Binary q => Get (CacheQuery q)
forall q. Binary q => [CacheQuery q] -> Put
forall q. Binary q => CacheQuery q -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
$cput :: forall q. Binary q => CacheQuery q -> Put
put :: CacheQuery q -> Put
$cget :: forall q. Binary q => Get (CacheQuery q)
get :: Get (CacheQuery q)
$cputList :: forall q. Binary q => [CacheQuery q] -> Put
putList :: [CacheQuery q] -> Put
Binary, CacheQuery q -> ()
(CacheQuery q -> ()) -> NFData (CacheQuery q)
forall q. NFData q => CacheQuery q -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall q. NFData q => CacheQuery q -> ()
rnf :: CacheQuery q -> ()
NFData, Eq (CacheQuery q)
Eq (CacheQuery q) =>
(Int -> CacheQuery q -> Int)
-> (CacheQuery q -> Int) -> Hashable (CacheQuery q)
Int -> CacheQuery q -> Int
CacheQuery q -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall q. Hashable q => Eq (CacheQuery q)
forall q. Hashable q => Int -> CacheQuery q -> Int
forall q. Hashable q => CacheQuery q -> Int
$chashWithSalt :: forall q. Hashable q => Int -> CacheQuery q -> Int
hashWithSalt :: Int -> CacheQuery q -> Int
$chash :: forall q. Hashable q => CacheQuery q -> Int
hash :: CacheQuery q -> Int
Hashable)
type instance RuleResult (CacheQuery q) = ByteString
jsonCache :: ShakeValue q => (q -> Action Value) -> Rules (q -> Action Value)
jsonCache :: forall q.
ShakeValue q =>
(q -> Action Value) -> Rules (q -> Action Value)
jsonCache = (q -> Action Value) -> Rules (q -> Action Value)
forall a q.
(ToJSON a, FromJSON a, ShakeValue q) =>
(q -> Action a) -> Rules (q -> Action a)
jsonCache'
jsonCache'
:: forall a q
. (ToJSON a, FromJSON a, ShakeValue q)
=> (q -> Action a)
-> Rules (q -> Action a)
jsonCache' :: forall a q.
(ToJSON a, FromJSON a, ShakeValue q) =>
(q -> Action a) -> Rules (q -> Action a)
jsonCache' q -> Action a
loader = FromJSON a => (CacheQuery q -> Action ByteString) -> q -> Action a
(CacheQuery q -> Action ByteString) -> q -> Action a
unpackJSON
((CacheQuery q -> Action ByteString) -> q -> Action a)
-> Rules (CacheQuery q -> Action ByteString)
-> Rules (q -> Action a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CacheQuery q -> Action ByteString)
-> Rules (CacheQuery q -> Action ByteString)
forall q a.
(RuleResult q ~ a, ShakeValue q, ShakeValue a, Partial) =>
(q -> Action a) -> Rules (q -> Action a)
addOracleCache (\(CacheQuery q
q) -> a -> ByteString
forall a. ToJSON a => a -> ByteString
A.encode (a -> ByteString) -> Action a -> Action ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> q -> Action a
loader q
q)
where
unpackJSON
:: FromJSON a => (CacheQuery q -> Action ByteString) -> q -> Action a
unpackJSON :: FromJSON a => (CacheQuery q -> Action ByteString) -> q -> Action a
unpackJSON CacheQuery q -> Action ByteString
runCacheQuery = \q
q -> do
ByteString
bytes <- CacheQuery q -> Action ByteString
runCacheQuery (CacheQuery q -> Action ByteString)
-> CacheQuery q -> Action ByteString
forall a b. (a -> b) -> a -> b
$ q -> CacheQuery q
forall q. q -> CacheQuery q
CacheQuery q
q
case ByteString -> Either String a
forall a. FromJSON a => ByteString -> Either String a
A.eitherDecode ByteString
bytes of
Left String
err -> String -> Action a
forall a. String -> Action a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err
Right a
res -> a -> Action a
forall a. a -> Action a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
res
simpleJsonCache :: ShakeValue q => q -> Action Value -> Rules (Action Value)
simpleJsonCache :: forall q. ShakeValue q => q -> Action Value -> Rules (Action Value)
simpleJsonCache = q -> Action Value -> Rules (Action Value)
forall q a.
(ToJSON a, FromJSON a, ShakeValue q) =>
q -> Action a -> Rules (Action a)
simpleJsonCache'
simpleJsonCache'
:: forall q a
. (ToJSON a, FromJSON a, ShakeValue q)
=> q
-> Action a
-> Rules (Action a)
simpleJsonCache' :: forall q a.
(ToJSON a, FromJSON a, ShakeValue q) =>
q -> Action a -> Rules (Action a)
simpleJsonCache' q
q Action a
loader = do
q -> Action a
cacheGetter <- (q -> Action a) -> Rules (q -> Action a)
forall a q.
(ToJSON a, FromJSON a, ShakeValue q) =>
(q -> Action a) -> Rules (q -> Action a)
jsonCache' (Action a -> q -> Action a
forall a b. a -> b -> a
const Action a
loader)
Action a -> Rules (Action a)
forall a. a -> Rules a
forall (m :: * -> *) a. Monad m => a -> m a
return (Action a -> Rules (Action a)) -> Action a -> Rules (Action a)
forall a b. (a -> b) -> a -> b
$ q -> Action a
cacheGetter q
q