summaryrefslogtreecommitdiff
path: root/src/Hakyll
diff options
context:
space:
mode:
Diffstat (limited to 'src/Hakyll')
-rw-r--r--src/Hakyll/Core/CompiledItem.hs3
-rw-r--r--src/Hakyll/Core/Store.hs22
2 files changed, 14 insertions, 11 deletions
diff --git a/src/Hakyll/Core/CompiledItem.hs b/src/Hakyll/Core/CompiledItem.hs
index 2e492a2..e40ab56 100644
--- a/src/Hakyll/Core/CompiledItem.hs
+++ b/src/Hakyll/Core/CompiledItem.hs
@@ -7,7 +7,7 @@
--
-- * we need a 'Writable' instance so the results can be saved.
--
-{-# LANGUAGE ExistentialQuantification #-}
+{-# LANGUAGE ExistentialQuantification, DeriveDataTypeable #-}
module Hakyll.Core.CompiledItem
( CompiledItem (..)
, compiledItem
@@ -24,6 +24,7 @@ import Hakyll.Core.Writable
--
data CompiledItem = forall a. (Binary a, Typeable a, Writable a)
=> CompiledItem a
+ deriving (Typeable)
instance Writable CompiledItem where
write p (CompiledItem x) = write p x
diff --git a/src/Hakyll/Core/Store.hs b/src/Hakyll/Core/Store.hs
index 12e33a7..50ffa90 100644
--- a/src/Hakyll/Core/Store.hs
+++ b/src/Hakyll/Core/Store.hs
@@ -1,5 +1,6 @@
-- | A store for stroing and retreiving items
--
+{-# LANGUAGE ExistentialQuantification #-}
module Hakyll.Core.Store
( Store
, makeStore
@@ -14,20 +15,22 @@ import Data.Map (Map)
import qualified Data.Map as M
import Data.Binary (Binary, encodeFile, decodeFile)
-import Data.Typeable (Typeable)
+import Data.Typeable (Typeable, cast)
-import Hakyll.Core.CompiledItem
-import Hakyll.Core.Writable
import Hakyll.Core.Identifier
import Hakyll.Core.Util.File
+-- | Items we can store
+--
+data Storable = forall a. (Binary a, Typeable a) => Storable a
+
-- | Data structure used for the store
--
data Store = Store
{ -- | All items are stored on the filesystem
storeDirectory :: FilePath
, -- | And some items are also kept in-memory
- storeMap :: MVar (Map FilePath CompiledItem)
+ storeMap :: MVar (Map FilePath Storable)
}
-- | Initialize the store
@@ -42,10 +45,9 @@ makeStore directory = do
-- | Auxiliary: add an item to the map
--
-addToMap :: (Binary a, Typeable a, Writable a)
- => Store -> FilePath -> a -> IO ()
+addToMap :: (Binary a, Typeable a) => Store -> FilePath -> a -> IO ()
addToMap store path value =
- modifyMVar_ (storeMap store) $ return . M.insert path (compiledItem value)
+ modifyMVar_ (storeMap store) $ return . M.insert path (Storable value)
-- | Create a path
--
@@ -55,7 +57,7 @@ makePath store name identifier =
-- | Store an item
--
-storeSet :: (Binary a, Typeable a, Writable a)
+storeSet :: (Binary a, Typeable a)
=> Store -> String -> Identifier -> a -> IO ()
storeSet store name identifier value = do
makeDirectories path
@@ -66,14 +68,14 @@ storeSet store name identifier value = do
-- | Load an item
--
-storeGet :: (Binary a, Typeable a, Writable a)
+storeGet :: (Binary a, Typeable a)
=> Store -> String -> Identifier -> IO (Maybe a)
storeGet store name identifier = do
-- First check the in-memory map
map' <- readMVar $ storeMap store
case M.lookup path map' of
-- Found in the in-memory map
- Just c -> return $ Just $ unCompiledItem c
+ Just (Storable s) -> return $ cast s
-- Not found in the map, try the filesystem
Nothing -> do
exists <- doesFileExist path