summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/Provider
diff options
context:
space:
mode:
Diffstat (limited to 'src/Hakyll/Core/Provider')
-rw-r--r--src/Hakyll/Core/Provider/Internal.hs2
-rw-r--r--src/Hakyll/Core/Provider/Metadata.hs134
-rw-r--r--src/Hakyll/Core/Provider/MetadataCache.hs9
3 files changed, 77 insertions, 68 deletions
diff --git a/src/Hakyll/Core/Provider/Internal.hs b/src/Hakyll/Core/Provider/Internal.hs
index 34400fd..c298653 100644
--- a/src/Hakyll/Core/Provider/Internal.hs
+++ b/src/Hakyll/Core/Provider/Internal.hs
@@ -20,7 +20,6 @@ module Hakyll.Core.Provider.Internal
--------------------------------------------------------------------------------
-import Control.Applicative ((<$>), (<*>))
import Control.DeepSeq (NFData (..), deepseq)
import Control.Monad (forM)
import Data.Binary (Binary (..))
@@ -28,7 +27,6 @@ import qualified Data.ByteString.Lazy as BL
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
-import Data.Monoid (mempty)
import Data.Set (Set)
import qualified Data.Set as S
import Data.Time (Day (..), UTCTime (..))
diff --git a/src/Hakyll/Core/Provider/Metadata.hs b/src/Hakyll/Core/Provider/Metadata.hs
index 7e4d7ed..0b0291c 100644
--- a/src/Hakyll/Core/Provider/Metadata.hs
+++ b/src/Hakyll/Core/Provider/Metadata.hs
@@ -1,33 +1,31 @@
--------------------------------------------------------------------------------
-- | Internal module to parse metadata
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE RecordWildCards #-}
module Hakyll.Core.Provider.Metadata
( loadMetadata
- , metadata
- , page
+ , parsePage
- -- This parser can be reused in some places
- , metadataKey
+ , MetadataException (..)
) where
--------------------------------------------------------------------------------
-import Control.Applicative
import Control.Arrow (second)
+import Control.Exception (Exception, throwIO)
+import Control.Monad (guard)
import qualified Data.ByteString.Char8 as BC
-import Data.List (intercalate)
+import Data.List.Extended (breakWhen)
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 Data.Maybe (fromMaybe)
+import Data.Monoid ((<>))
+import qualified Data.Text as T
+import qualified Data.Text.Encoding as T
+import qualified Data.Yaml as Yaml
import Hakyll.Core.Identifier
import Hakyll.Core.Metadata
import Hakyll.Core.Provider.Internal
-import Hakyll.Core.Util.Parser
-import Hakyll.Core.Util.String
+import System.IO as IO
--------------------------------------------------------------------------------
@@ -36,13 +34,13 @@ loadMetadata p identifier = do
hasHeader <- probablyHasMetadataHeader fp
(md, body) <- if hasHeader
then second Just <$> loadMetadataHeader fp
- else return (M.empty, Nothing)
+ else return (mempty, Nothing)
emd <- case mi of
- Nothing -> return M.empty
+ Nothing -> return mempty
Just mi' -> loadMetadataFile $ resourceFilePath p mi'
- return (M.union md emd, body)
+ return (md <> emd, body)
where
normal = setVersion Nothing identifier
fp = resourceFilePath p identifier
@@ -52,19 +50,17 @@ loadMetadata p identifier = do
--------------------------------------------------------------------------------
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)
+ fileContent <- readFile fp
+ case parsePage fileContent of
+ Right x -> return x
+ Left err -> throwIO $ MetadataException fp err
--------------------------------------------------------------------------------
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
+ errOrMeta <- Yaml.decodeFileEither fp
+ either (fail . show) return errOrMeta
--------------------------------------------------------------------------------
@@ -83,53 +79,71 @@ probablyHasMetadataHeader fp = do
--------------------------------------------------------------------------------
--- | Space or tab, no newline
-inlineSpace :: Parser Char
-inlineSpace = P.oneOf ['\t', ' '] <?> "space"
+-- | Parse the page metadata and body.
+splitMetadata :: String -> (Maybe String, String)
+splitMetadata str0 = fromMaybe (Nothing, str0) $ do
+ guard $ leading >= 3
+ let !str1 = drop leading str0
+ guard $ all isNewline (take 1 str1)
+ let !(!meta, !content0) = breakWhen isTrailing str1
+ guard $ not $ null content0
+ let !content1 = drop (leading + 1) content0
+ !content2 = dropWhile isNewline $ dropWhile isInlineSpace content1
+ -- Adding this newline fixes the line numbers reported by the YAML parser.
+ -- It's a bit ugly but it works.
+ return (Just ('\n' : meta), content2)
+ where
+ -- Parse the leading "---"
+ !leading = length $ takeWhile (== '-') str0
+
+ -- Predicate to recognize the trailing "---" or "..."
+ isTrailing [] = False
+ isTrailing (x : xs) =
+ isNewline x && length (takeWhile isDash xs) == leading
+
+ -- Characters
+ isNewline c = c == '\n' || c == '\r'
+ isDash c = c == '-' || c == '.'
+ isInlineSpace c = c == '\t' || c == ' '
--------------------------------------------------------------------------------
--- | Parse Windows newlines as well (i.e. "\n" or "\r\n")
-newline :: Parser String
-newline = P.string "\n" <|> P.string "\r\n"
+parseMetadata :: String -> Either Yaml.ParseException Metadata
+parseMetadata = Yaml.decodeEither' . T.encodeUtf8 . T.pack
--------------------------------------------------------------------------------
--- | Parse a single metadata field
-metadataField :: Parser (String, String)
-metadataField = do
- key <- metadataKey
- _ <- P.char ':'
- P.skipMany1 inlineSpace <?> "space followed by metadata for: " ++ key
- value <- P.manyTill P.anyChar newline
- trailing' <- P.many trailing
- return (key, trim $ intercalate " " $ value : trailing')
+parsePage :: String -> Either Yaml.ParseException (Metadata, String)
+parsePage fileContent = case mbMetaBlock of
+ Nothing -> return (mempty, content)
+ Just metaBlock -> case parseMetadata metaBlock of
+ Left err -> Left err
+ Right meta -> return (meta, content)
where
- trailing = P.many1 inlineSpace *> P.manyTill P.anyChar newline
+ !(!mbMetaBlock, !content) = splitMetadata fileContent
--------------------------------------------------------------------------------
--- | Parse a metadata block
-metadata :: Parser [(String, String)]
-metadata = P.many metadataField
+-- | Thrown in the IO monad if things go wrong. Provides a nice-ish error
+-- message.
+data MetadataException = MetadataException FilePath Yaml.ParseException
--------------------------------------------------------------------------------
--- | Parse a metadata block, including delimiters and trailing newlines
-metadataBlock :: Parser [(String, String)]
-metadataBlock = do
- open <- P.many1 (P.char '-') <* P.many inlineSpace <* newline
- metadata' <- metadata
- _ <- P.choice $ map (P.string . replicate (length open)) ['-', '.']
- P.skipMany inlineSpace
- P.skipMany1 newline
- return metadata'
+instance Exception MetadataException
--------------------------------------------------------------------------------
--- | 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)
+instance Show MetadataException where
+ show (MetadataException fp err) =
+ fp ++ ": " ++ Yaml.prettyPrintParseException err ++ hint
+
+ where
+ hint = case err of
+ Yaml.InvalidYaml (Just (Yaml.YamlParseException {..}))
+ | yamlProblem == problem -> "\n" ++
+ "Hint: if the metadata value contains characters such\n" ++
+ "as ':' or '-', try enclosing it in quotes."
+ _ -> ""
+
+ problem = "mapping values are not allowed in this context"
diff --git a/src/Hakyll/Core/Provider/MetadataCache.hs b/src/Hakyll/Core/Provider/MetadataCache.hs
index 28d2bd5..46dbf3e 100644
--- a/src/Hakyll/Core/Provider/MetadataCache.hs
+++ b/src/Hakyll/Core/Provider/MetadataCache.hs
@@ -8,9 +8,6 @@ module Hakyll.Core.Provider.MetadataCache
--------------------------------------------------------------------------------
import Control.Monad (unless)
-import qualified Data.Map as M
-
---------------------------------------------------------------------------------
import Hakyll.Core.Identifier
import Hakyll.Core.Metadata
import Hakyll.Core.Provider.Internal
@@ -21,11 +18,11 @@ import qualified Hakyll.Core.Store as Store
--------------------------------------------------------------------------------
resourceMetadata :: Provider -> Identifier -> IO Metadata
resourceMetadata p r
- | not (resourceExists p r) = return M.empty
+ | not (resourceExists p r) = return mempty
| otherwise = do
-- TODO keep time in md cache
load p r
- Store.Found md <- Store.get (providerStore p)
+ Store.Found (BinaryMetadata md) <- Store.get (providerStore p)
[name, toFilePath r, "metadata"]
return md
@@ -52,7 +49,7 @@ load p r = do
mmof <- Store.isMember store mdk
unless mmof $ do
(md, body) <- loadMetadata p r
- Store.set store mdk md
+ Store.set store mdk (BinaryMetadata md)
Store.set store bk body
where
store = providerStore p