{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Haxl.Core.DataCache
( DataCache(..)
, SubCache(..)
, emptyDataCache
, filter
, insert
, insertNotShowable
, insertWithShow
, lookup
, showCache
, readCache
) where
import Prelude hiding (lookup, filter)
import Control.Exception
import Unsafe.Coerce
import Data.Typeable
import Data.Hashable
import qualified Data.HashTable.IO as H
newtype DataCache res = DataCache (HashTable TypeRep (SubCache res))
data SubCache res =
forall req a . (Hashable (req a), Eq (req a), Typeable (req a)) =>
SubCache (req a -> String) (a -> String) ! (HashTable (req a) (res a))
type HashTable k v = H.BasicHashTable k v
emptyDataCache :: IO (DataCache res)
emptyDataCache = DataCache <$> H.new
insert
:: (Hashable (req a), Typeable (req a), Eq (req a), Show (req a), Show a)
=> req a
-> res a
-> DataCache res
-> IO ()
insert = insertWithShow show show
insertNotShowable
:: (Hashable (req a), Typeable (req a), Eq (req a))
=> req a
-> res a
-> DataCache res
-> IO ()
insertNotShowable = insertWithShow notShowable notShowable
insertWithShow
:: (Hashable (req a), Typeable (req a), Eq (req a))
=> (req a -> String)
-> (a -> String)
-> req a
-> res a
-> DataCache res
-> IO ()
insertWithShow showRequest showResult request result (DataCache m) =
H.mutateIO m (typeOf request) (mutate showRequest showResult request result)
notShowable :: a
notShowable = error "insertNotShowable"
mutate :: (Hashable (req a), Typeable (req a), Eq (req a))
=> (req a -> String)
-> (a -> String)
-> req a
-> res a
-> Maybe (SubCache res)
-> IO (Maybe (SubCache res), ())
mutate showRequest showResult request result Nothing = do
newTable <- H.new
H.insert newTable request result
return (Just (SubCache showRequest showResult newTable), ())
mutate _ _ request result (Just sc@(SubCache _ _ oldTable)) = do
H.insert oldTable (unsafeCoerce request) (unsafeCoerce result)
return (Just sc, ())
lookup
:: Typeable (req a)
=> req a
-> DataCache res
-> IO (Maybe (res a))
lookup req (DataCache m) = do
mbRes <- H.lookup m (typeOf req)
case mbRes of
Nothing -> return Nothing
Just (SubCache _ _ sc) ->
unsafeCoerce (H.lookup sc (unsafeCoerce req))
filter
:: forall res
. (forall a. res a -> IO Bool)
-> DataCache res
-> IO (DataCache res)
filter pred (DataCache cache) = do
cacheList <- H.toList cache
filteredCache <- filterSubCache `mapM` cacheList
DataCache <$> H.fromList filteredCache
where
filterSubCache
:: (TypeRep, SubCache res)
-> IO (TypeRep, SubCache res)
filterSubCache (ty, SubCache showReq showRes hm) = do
filteredList <- H.foldM go [] hm
filteredSC <- H.fromList filteredList
return (ty, SubCache showReq showRes filteredSC)
where
go res (request, rvar) = do
predRes <- pred rvar
return $ if predRes then (request, rvar):res else res
showCache
:: forall res
. DataCache res
-> (forall a . res a -> IO (Maybe (Either SomeException a)))
-> IO [(TypeRep, [(String, Either SomeException String)])]
showCache (DataCache cache) readRes = H.foldM goSubCache [] cache
where
goSubCache
:: [(TypeRep, [(String, Either SomeException String)])]
-> (TypeRep, SubCache res)
-> IO [(TypeRep, [(String, Either SomeException String)])]
goSubCache res (ty, SubCache showReq showRes hm) = do
subCacheResult <- H.foldM go [] hm
return $ (ty, subCacheResult):res
where
go res (request, rvar) = do
maybe_r <- readRes rvar
return $ case maybe_r of
Nothing -> res
Just (Left e) -> (showReq request, Left e) : res
Just (Right result) ->
(showReq request, Right (showRes result)) : res
readCache
:: forall res ret
. DataCache res
-> (forall a . res a -> IO ret)
-> IO [(TypeRep, [Either SomeException ret])]
readCache (DataCache cache) readRes = H.foldM goSubCache [] cache
where
goSubCache
:: [(TypeRep, [Either SomeException ret])]
-> (TypeRep, SubCache res)
-> IO [(TypeRep, [Either SomeException ret])]
goSubCache res (ty, SubCache _showReq _showRes hm) = do
subCacheResult <- H.foldM go [] hm
return $ (ty, subCacheResult):res
where
go res (_request, rvar) = do
r <- try $ readRes rvar
return $ r : res