summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/Resource
diff options
context:
space:
mode:
Diffstat (limited to 'src/Hakyll/Core/Resource')
-rw-r--r--src/Hakyll/Core/Resource/Metadata.hs118
-rw-r--r--src/Hakyll/Core/Resource/MetadataCache.hs61
-rw-r--r--src/Hakyll/Core/Resource/Modified.hs82
-rw-r--r--src/Hakyll/Core/Resource/Pattern.hs160
-rw-r--r--src/Hakyll/Core/Resource/Provider.hs45
-rw-r--r--src/Hakyll/Core/Resource/Provider/Internal.hs84
6 files changed, 0 insertions, 550 deletions
diff --git a/src/Hakyll/Core/Resource/Metadata.hs b/src/Hakyll/Core/Resource/Metadata.hs
deleted file mode 100644
index 44b0721..0000000
--- a/src/Hakyll/Core/Resource/Metadata.hs
+++ /dev/null
@@ -1,118 +0,0 @@
---------------------------------------------------------------------------------
--- | Internal module to parse metadata
-module Hakyll.Core.Resource.Metadata
- ( loadMetadata
- ) where
-
-
---------------------------------------------------------------------------------
-import Control.Applicative ((<$>), (<*), (<*>))
-import Control.Arrow (second)
-import qualified Data.ByteString.Char8 as BC
-import qualified Data.Map as M
-import System.IO as IO
-import Text.Parsec ((<?>))
-import qualified Text.Parsec as P
-import Text.Parsec.String (Parser)
-
-
---------------------------------------------------------------------------------
-import Hakyll.Core.Resource
-import Hakyll.Core.Resource.Provider.Internal
-import Hakyll.Core.Util.String
-
-
---------------------------------------------------------------------------------
-loadMetadata :: ResourceProvider -> Resource -> IO (Metadata, Maybe String)
-loadMetadata rp r = do
- hasHeader <- probablyHasMetadataHeader fp
- (md, body) <- if hasHeader
- then second Just <$> loadMetadataHeader fp
- else return (M.empty, Nothing)
-
- emd <- if resourceExists rp mr then loadMetadataFile mfp else return M.empty
-
- return (M.union md emd, body)
- where
- fp = unResource r
- mr = resourceMetadataResource r
- mfp = unResource mr
-
-
---------------------------------------------------------------------------------
-loadMetadataHeader :: FilePath -> IO (Metadata, String)
-loadMetadataHeader fp = do
- contents <- readFile fp
- case P.parse page fp contents of
- Left err -> error (show err)
- Right (md, b) -> return (M.fromList md, b)
-
-
---------------------------------------------------------------------------------
-loadMetadataFile :: FilePath -> IO Metadata
-loadMetadataFile fp = do
- contents <- readFile fp
- case P.parse metadata fp contents of
- Left err -> error (show err)
- Right md -> return $ M.fromList md
-
-
---------------------------------------------------------------------------------
--- | Check if a file "probably" has a metadata header. The main goal of this is
--- to exclude binary files (which are unlikely to start with "---").
-probablyHasMetadataHeader :: FilePath -> IO Bool
-probablyHasMetadataHeader fp = do
- handle <- IO.openFile fp IO.ReadMode
- bs <- BC.hGet handle 1024
- IO.hClose handle
- return $ isMetadataHeader bs
- where
- isMetadataHeader bs =
- let pre = BC.takeWhile (\x -> x /= '\n' && x /= '\r') bs
- in BC.length pre >= 3 && BC.all (== '-') pre
-
-
---------------------------------------------------------------------------------
--- | Space or tab, no newline
-inlineSpace :: Parser Char
-inlineSpace = P.oneOf ['\t', ' '] <?> "space"
-
-
---------------------------------------------------------------------------------
--- | Parse a single metadata field
-metadataField :: Parser (String, String)
-metadataField = do
- key <- P.manyTill P.alphaNum $ P.char ':'
- P.skipMany1 inlineSpace <?> "space followed by metadata for: " ++ key
- value <- P.manyTill P.anyChar P.newline
- trailing' <- P.many trailing
- return (key, trim $ value ++ concat trailing')
- where
- trailing = (++) <$> P.many1 inlineSpace <*> P.manyTill P.anyChar P.newline
-
-
---------------------------------------------------------------------------------
--- | Parse a metadata block
-metadata :: Parser [(String, String)]
-metadata = P.many metadataField
-
-
---------------------------------------------------------------------------------
--- | Parse a metadata block, including delimiters and trailing newlines
-metadataBlock :: Parser [(String, String)]
-metadataBlock = do
- open <- P.many1 (P.char '-') <* P.many inlineSpace <* P.newline
- metadata' <- metadata
- _ <- P.choice $ map (P.string . replicate (length open)) ['-', '.']
- P.skipMany inlineSpace
- P.skipMany1 P.newline
- return metadata'
-
-
---------------------------------------------------------------------------------
--- | Parse a page consisting of a metadata header and a body
-page :: Parser ([(String, String)], String)
-page = do
- metadata' <- P.option [] metadataBlock
- body <- P.many P.anyChar
- return (metadata', body)
diff --git a/src/Hakyll/Core/Resource/MetadataCache.hs b/src/Hakyll/Core/Resource/MetadataCache.hs
deleted file mode 100644
index b459674..0000000
--- a/src/Hakyll/Core/Resource/MetadataCache.hs
+++ /dev/null
@@ -1,61 +0,0 @@
---------------------------------------------------------------------------------
-module Hakyll.Core.Resource.MetadataCache
- ( resourceMetadata
- , resourceBody
- , resourceInvalidateMetadataCache
- ) where
-
-
---------------------------------------------------------------------------------
-import Hakyll.Core.Resource
-import Hakyll.Core.Resource.Metadata
-import Hakyll.Core.Resource.Provider.Internal
-import qualified Hakyll.Core.Store as Store
-
-
---------------------------------------------------------------------------------
-resourceMetadata :: ResourceProvider -> Resource -> IO Metadata
-resourceMetadata rp r = do
- load rp r
- Store.Found md <- Store.get (resourceStore rp)
- [name, unResource r, "metadata"]
- return md
-
-
---------------------------------------------------------------------------------
-resourceBody :: ResourceProvider -> Resource -> IO String
-resourceBody rp r = do
- load rp r
- Store.Found bd <- Store.get (resourceStore rp)
- [name, unResource r, "body"]
- maybe (resourceString r) return bd
-
-
---------------------------------------------------------------------------------
-resourceInvalidateMetadataCache :: ResourceProvider -> Resource -> IO ()
-resourceInvalidateMetadataCache rp r = do
- Store.delete (resourceStore rp) [name, unResource r, "metadata"]
- Store.delete (resourceStore rp) [name, unResource r, "body"]
-
-
---------------------------------------------------------------------------------
-load :: ResourceProvider -> Resource -> IO ()
-load rp r = do
- mmd <- Store.get store mdk :: IO (Store.Result Metadata)
- case mmd of
- -- Already loaded
- Store.Found _ -> return ()
- -- Not yet loaded
- _ -> do
- (metadata, body) <- loadMetadata rp r
- Store.set store mdk metadata
- Store.set store bk body
- where
- store = resourceStore rp
- mdk = [name, unResource r, "metadata"]
- bk = [name, unResource r, "body"]
-
-
---------------------------------------------------------------------------------
-name :: String
-name = "Hakyll.Core.Resource.Provider.MetadataCache"
diff --git a/src/Hakyll/Core/Resource/Modified.hs b/src/Hakyll/Core/Resource/Modified.hs
deleted file mode 100644
index 8492108..0000000
--- a/src/Hakyll/Core/Resource/Modified.hs
+++ /dev/null
@@ -1,82 +0,0 @@
---------------------------------------------------------------------------------
-module Hakyll.Core.Resource.Modified
- ( resourceModified
- , resourceModificationTime
- ) where
-
-
---------------------------------------------------------------------------------
-import Control.Applicative ((<$>), (<*>))
-import Control.Monad (when)
-import qualified Crypto.Hash.MD5 as MD5
-import qualified Data.ByteString as B
-import qualified Data.ByteString.Lazy as BL
-import Data.IORef
-import qualified Data.Map as M
-import Data.Time (UTCTime)
-import System.Directory (getModificationTime)
-
-
---------------------------------------------------------------------------------
-import Hakyll.Core.Resource
-import Hakyll.Core.Resource.MetadataCache
-import Hakyll.Core.Resource.Provider.Internal
-import Hakyll.Core.Store (Store)
-import qualified Hakyll.Core.Store as Store
-
-
---------------------------------------------------------------------------------
--- | A resource is modified if it or its metadata has changed
-resourceModified :: ResourceProvider -> Resource -> IO Bool
-resourceModified rp r
- | not exists = return False
- | otherwise = do
- cache <- readIORef cacheRef
- case M.lookup r cache of
- Just m -> return m
- Nothing -> do
- -- Check if the actual file was modified, and do a recursive
- -- call to check if the metadata file was modified
- m <- (||)
- <$> fileDigestModified store (unResource r)
- <*> resourceModified rp (resourceMetadataResource r)
- modifyIORef cacheRef (M.insert r m)
-
- -- Important! (But ugly)
- when m $ resourceInvalidateMetadataCache rp r
-
- return m
- where
- exists = resourceExists rp r
- store = resourceStore rp
- cacheRef = resourceModifiedCache rp
-
-
---------------------------------------------------------------------------------
--- | Utility: Check if a the digest of a file was modified
-fileDigestModified :: Store -> FilePath -> IO Bool
-fileDigestModified store fp = do
- -- Get the latest seen digest from the store, and calculate the current
- -- digest for the
- lastDigest <- Store.get store key
- newDigest <- fileDigest fp
- if Store.Found newDigest == lastDigest
- -- All is fine, not modified
- then return False
- -- Resource modified; store new digest
- else do
- Store.set store key newDigest
- return True
- where
- key = ["Hakyll.Core.Resource.Provider.fileModified", fp]
-
-
---------------------------------------------------------------------------------
--- | Utility: Retrieve a digest for a given file
-fileDigest :: FilePath -> IO B.ByteString
-fileDigest = fmap MD5.hashlazy . BL.readFile
-
-
---------------------------------------------------------------------------------
-resourceModificationTime :: Resource -> IO UTCTime
-resourceModificationTime = getModificationTime . unResource
diff --git a/src/Hakyll/Core/Resource/Pattern.hs b/src/Hakyll/Core/Resource/Pattern.hs
deleted file mode 100644
index c2f1132..0000000
--- a/src/Hakyll/Core/Resource/Pattern.hs
+++ /dev/null
@@ -1,160 +0,0 @@
---------------------------------------------------------------------------------
--- | Module providing pattern matching and capturing on file names.
--- 'Pattern's come in two kinds:
---
--- * Simple glob patterns, like @foo\/*@;
---
--- * Custom, arbitrary predicates of the type @Identifier -> Bool@.
---
--- They both have advantages and disadvantages. By default, globs are used,
--- unless you construct your 'Pattern' using the 'predicate' function.
---
--- A very simple pattern could be, for example, @foo\/bar@. This pattern will
--- only match the exact @foo\/bar@ identifier.
---
--- To match more than one identifier, there are different captures that one can
--- use:
---
--- * @*@: matches at most one element of an identifier;
---
--- * @**@: matches one or more elements of an identifier.
---
--- Some examples:
---
--- * @foo\/*@ will match @foo\/bar@ and @foo\/foo@, but not @foo\/bar\/qux@;
---
--- * @**@ will match any identifier;
---
--- * @foo\/**@ will match @foo\/bar@ and @foo\/bar\/qux@, but not @bar\/foo@;
---
--- * @foo\/*.html@ will match all HTML files in the @foo\/@ directory.
---
--- The 'capture' function allows the user to get access to the elements captured
--- by the capture elements in the pattern.
---
--- Like an 'Identifier', a 'Pattern' also has a type parameter. This is simply
--- an extra layer of safety, and can be discarded using the 'castPattern'
--- function.
-module Hakyll.Core.Resource.Pattern
- ( Pattern
- , parsePattern
- , capture
- ) where
-
-
---------------------------------------------------------------------------------
-import Control.Arrow ((&&&), (>>>))
-import Control.Monad (msum)
-import Data.List (inits, isPrefixOf, tails)
-import GHC.Exts (IsString, fromString)
-
-
---------------------------------------------------------------------------------
-import Hakyll.Core.Resource
-
-
---------------------------------------------------------------------------------
--- | One base element of a pattern
-data GlobComponent
- = Capture
- | CaptureMany
- | Literal String
- deriving (Eq, Show)
-
-
---------------------------------------------------------------------------------
--- | Type that allows matching on identifiers
-newtype Pattern = Pattern [GlobComponent]
- deriving (Show)
-
-
---------------------------------------------------------------------------------
-instance IsString Pattern where
- fromString = parsePattern
-
-
---------------------------------------------------------------------------------
--- | Parse a pattern from a string
-parsePattern :: String -> Pattern
-parsePattern = Pattern . parse
- where
- parse str =
- let (chunk, rest) = break (`elem` "\\*") str
- in case rest of
- ('\\' : x : xs) -> Literal (chunk ++ [x]) : parse xs
- ('*' : '*' : xs) -> Literal chunk : CaptureMany : parse xs
- ('*' : xs) -> Literal chunk : Capture : parse xs
- xs -> Literal chunk : Literal xs : []
-
-
---------------------------------------------------------------------------------
--- | Split a list at every possible point, generate a list of (init, tail)
--- cases. The result is sorted with inits decreasing in length.
-splits :: [a] -> [([a], [a])]
-splits = inits &&& tails >>> uncurry zip >>> reverse
-
-
---------------------------------------------------------------------------------
--- | Match a glob against a pattern, generating a list of captures
-capture :: Pattern -> Resource -> Maybe [String]
-capture (Pattern p) rs = capture' p (unResource rs)
-
-
---------------------------------------------------------------------------------
--- | Internal verion of 'capture'
-capture' :: [GlobComponent] -> String -> Maybe [String]
-capture' [] [] = Just [] -- An empty match
-capture' [] _ = Nothing -- No match
-capture' (Literal l : ms) str
- -- Match the literal against the string
- | l `isPrefixOf` str = capture' ms $ drop (length l) str
- | otherwise = Nothing
-capture' (Capture : ms) str =
- -- Match until the next /
- let (chunk, rest) = break (== '/') str
- in msum $ [ fmap (i :) (capture' ms (t ++ rest)) | (i, t) <- splits chunk ]
-capture' (CaptureMany : ms) str =
- -- Match everything
- msum $ [ fmap (i :) (capture' ms t) | (i, t) <- splits str ]
-
-
---------------------------------------------------------------------------------
--- | Create an identifier from a pattern by filling in the captures with a given
--- string
---
--- Example:
---
--- > fromCapture (parsePattern "tags/*") "foo"
---
--- Result:
---
--- > "tags/foo"
-{-
-fromCapture :: Pattern -> String -> Identifier
-fromCapture pattern = fromCaptures pattern . repeat
--}
-
-
---------------------------------------------------------------------------------
--- | Create an identifier from a pattern by filling in the captures with the
--- given list of strings
---
-{-
-fromCaptures :: Pattern -> [String] -> String
-fromCaptures (Pattern p) = fromCaptures' p
--}
-
-
---------------------------------------------------------------------------------
--- | Internally used version of 'fromCaptures'
-{-
-fromCaptures' :: [GlobComponent] -> [String] -> String
-fromCaptures' [] _ = mempty
-fromCaptures' (m : ms) [] = case m of
- Literal l -> l `mappend` fromCaptures' ms []
- _ -> error $ "Hakyll.Core.Identifier.Pattern.fromCaptures': "
- ++ "identifier list exhausted"
-fromCaptures' (m : ms) ids@(i : is) = case m of
- Literal l -> l `mappend` fromCaptures' ms ids
- _ -> i `mappend` fromCaptures' ms is
--}
diff --git a/src/Hakyll/Core/Resource/Provider.hs b/src/Hakyll/Core/Resource/Provider.hs
deleted file mode 100644
index 8f4c83f..0000000
--- a/src/Hakyll/Core/Resource/Provider.hs
+++ /dev/null
@@ -1,45 +0,0 @@
---------------------------------------------------------------------------------
--- | This module provides an wrapper API around the file system which does some
--- caching.
-module Hakyll.Core.Resource.Provider
- ( -- * Constructing resource providers
- ResourceProvider
- , newResourceProvider
-
- -- * Querying resource properties
- , resourceList
- , resourceExists
- , resourceModified
- , resourceModificationTime
-
- -- * Access to raw resource content
- , resourceString
- , resourceLBS
-
- -- * Access to metadata and body content
- , resourceMetadata
- , resourceBody
- ) where
-
-
---------------------------------------------------------------------------------
-import Hakyll.Core.Resource
-import qualified Hakyll.Core.Resource.MetadataCache as Internal
-import Hakyll.Core.Resource.Modified
-import Hakyll.Core.Resource.Provider.Internal
-
-
---------------------------------------------------------------------------------
--- | Wrapper to ensure metadata cache is invalidated if necessary
-resourceMetadata :: ResourceProvider -> Resource -> IO Metadata
-resourceMetadata rp r = do
- _ <- resourceModified rp r
- Internal.resourceMetadata rp r
-
-
---------------------------------------------------------------------------------
--- | Wrapper to ensure metadata cache is invalidated if necessary
-resourceBody :: ResourceProvider -> Resource -> IO String
-resourceBody rp r = do
- _ <- resourceModified rp r
- Internal.resourceBody rp r
diff --git a/src/Hakyll/Core/Resource/Provider/Internal.hs b/src/Hakyll/Core/Resource/Provider/Internal.hs
deleted file mode 100644
index fb93fcc..0000000
--- a/src/Hakyll/Core/Resource/Provider/Internal.hs
+++ /dev/null
@@ -1,84 +0,0 @@
---------------------------------------------------------------------------------
-module Hakyll.Core.Resource.Provider.Internal
- ( ResourceProvider (..)
- , newResourceProvider
-
- , resourceList
- , resourceExists
- , resourceMetadataResource
-
- , resourceString
- , resourceLBS
- ) where
-
-
---------------------------------------------------------------------------------
-import Control.Applicative ((<$>))
-import qualified Data.ByteString.Lazy as BL
-import Data.IORef
-import Data.Map (Map)
-import qualified Data.Map as M
-import Data.Set (Set)
-import qualified Data.Set as S
-import System.FilePath (addExtension)
-
-
---------------------------------------------------------------------------------
-import Hakyll.Core.Resource
-import Hakyll.Core.Store
-import Hakyll.Core.Util.File
-
-
---------------------------------------------------------------------------------
--- | Responsible for retrieving and listing resources
-data ResourceProvider = ResourceProvider
- { -- | A list of all files found
- resourceSet :: Set Resource
- , -- | Cache keeping track of modified files
- resourceModifiedCache :: IORef (Map Resource Bool)
- , -- | Underlying persistent store for caching
- resourceStore :: Store
- }
-
-
---------------------------------------------------------------------------------
--- | Create a resource provider
-newResourceProvider :: Store -- ^ Store to use
- -> (FilePath -> Bool) -- ^ Should we ignore this file?
- -> FilePath -- ^ Search directory
- -> IO ResourceProvider -- ^ Resulting provider
-newResourceProvider store ignore directory = do
- list <- map resource . filter (not . ignore) <$>
- getRecursiveContents False directory
- cache <- newIORef M.empty
- return $ ResourceProvider (S.fromList list) cache store
-
-
---------------------------------------------------------------------------------
-resourceList :: ResourceProvider -> [Resource]
-resourceList = S.toList . resourceSet
-
-
---------------------------------------------------------------------------------
--- | Check if a given resiyrce exists
-resourceExists :: ResourceProvider -> Resource -> Bool
-resourceExists provider = (`S.member` resourceSet provider)
-
-
---------------------------------------------------------------------------------
--- | Each resource may have an associated metadata resource (with a @.metadata@
--- filename)
-resourceMetadataResource :: Resource -> Resource
-resourceMetadataResource = resource . flip addExtension "metadata" . unResource
-
-
---------------------------------------------------------------------------------
--- | Get the raw body of a resource as string
-resourceString :: Resource -> IO String
-resourceString = readFile . unResource
-
-
---------------------------------------------------------------------------------
--- | Get the raw body of a resource of a lazy bytestring
-resourceLBS :: Resource -> IO BL.ByteString
-resourceLBS = BL.readFile . unResource