hakyll/src/Hakyll/Core/Store.hs

104 lines
3 KiB
Haskell
Raw Normal View History

2010-12-26 15:12:57 +00:00
-- | A store for stroing and retreiving items
--
2011-05-18 22:41:39 +00:00
{-# LANGUAGE ExistentialQuantification, ScopedTypeVariables #-}
2010-12-26 15:12:57 +00:00
module Hakyll.Core.Store
( Store
2011-05-17 08:57:37 +00:00
, StoreGet (..)
2010-12-26 15:12:57 +00:00
, makeStore
, storeSet
, storeGet
) where
import Control.Concurrent.MVar (MVar, newMVar, readMVar, modifyMVar_)
2010-12-26 15:12:57 +00:00
import System.FilePath ((</>))
import System.Directory (doesFileExist)
import Data.Maybe (fromMaybe)
import Data.Map (Map)
import qualified Data.Map as M
2010-12-26 15:12:57 +00:00
import Data.Binary (Binary, encodeFile, decodeFile)
2011-05-18 22:41:39 +00:00
import Data.Typeable (Typeable, TypeRep, cast, typeOf)
2010-12-26 15:12:57 +00:00
import Hakyll.Core.Identifier
import Hakyll.Core.Util.File
-- | Items we can store
--
data Storable = forall a. (Binary a, Typeable a) => Storable a
2011-05-17 08:57:37 +00:00
-- | Result when an item from the store
--
data StoreGet a = Found a
| NotFound
2011-05-18 22:41:39 +00:00
| WrongType TypeRep TypeRep
deriving (Show, Eq)
2011-05-17 08:57:37 +00:00
2010-12-26 15:12:57 +00:00
-- | 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 Storable)
2010-12-26 15:12:57 +00:00
}
-- | Initialize the store
--
makeStore :: FilePath -> IO Store
makeStore directory = do
mvar <- newMVar M.empty
return Store
{ storeDirectory = directory
, storeMap = mvar
}
-- | Auxiliary: add an item to the map
--
addToMap :: (Binary a, Typeable a) => Store -> FilePath -> a -> IO ()
addToMap store path value =
modifyMVar_ (storeMap store) $ return . M.insert path (Storable value)
2010-12-26 15:12:57 +00:00
-- | Create a path
--
2011-05-24 09:58:13 +00:00
makePath :: Store -> String -> Identifier a -> FilePath
makePath store name identifier = storeDirectory store </> name
</> group </> toFilePath identifier </> "hakyllstore"
where
group = fromMaybe "" $ identifierGroup identifier
2010-12-26 15:12:57 +00:00
-- | Store an item
--
storeSet :: (Binary a, Typeable a)
2011-05-24 09:58:13 +00:00
=> Store -> String -> Identifier a -> a -> IO ()
2010-12-26 15:12:57 +00:00
storeSet store name identifier value = do
makeDirectories path
encodeFile path value
addToMap store path value
2010-12-26 15:12:57 +00:00
where
path = makePath store name identifier
-- | Load an item
--
2011-05-18 22:41:39 +00:00
storeGet :: forall a. (Binary a, Typeable a)
2011-05-24 09:58:13 +00:00
=> Store -> String -> Identifier a -> IO (StoreGet a)
2010-12-26 15:12:57 +00:00
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
2011-05-17 08:57:37 +00:00
Just (Storable s) -> return $ case cast s of
2011-05-18 22:41:39 +00:00
Nothing -> WrongType (typeOf s) $ typeOf (undefined :: a)
2011-05-17 08:57:37 +00:00
Just s' -> Found s'
-- Not found in the map, try the filesystem
Nothing -> do
exists <- doesFileExist path
if not exists
-- Not found in the filesystem either
2011-05-17 08:57:37 +00:00
then return NotFound
-- Found in the filesystem
else do v <- decodeFile path
addToMap store path v
2011-05-17 08:57:37 +00:00
return $ Found v
2010-12-26 15:12:57 +00:00
where
path = makePath store name identifier