summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core
diff options
context:
space:
mode:
Diffstat (limited to 'src/Hakyll/Core')
-rw-r--r--src/Hakyll/Core/Compiler/Internal.hs3
-rw-r--r--src/Hakyll/Core/Configuration.hs6
-rw-r--r--src/Hakyll/Core/Dependencies.hs6
-rw-r--r--src/Hakyll/Core/Metadata.hs14
-rw-r--r--src/Hakyll/Core/Provider/Internal.hs7
-rw-r--r--src/Hakyll/Core/Provider/Metadata.hs37
-rw-r--r--src/Hakyll/Core/Rules/Default.hs24
-rw-r--r--src/Hakyll/Core/Runtime.hs5
-rw-r--r--src/Hakyll/Core/UnixFilter.hs19
9 files changed, 37 insertions, 84 deletions
diff --git a/src/Hakyll/Core/Compiler/Internal.hs b/src/Hakyll/Core/Compiler/Internal.hs
index 259cd35..8424d69 100644
--- a/src/Hakyll/Core/Compiler/Internal.hs
+++ b/src/Hakyll/Core/Compiler/Internal.hs
@@ -248,5 +248,6 @@ compilerGetMatches :: Pattern -> Compiler [Identifier]
compilerGetMatches pattern = do
universe <- compilerUniverse <$> compilerAsk
let matching = filterMatches pattern $ S.toList universe
- compilerTellDependencies [PatternDependency pattern matching]
+ set' = S.fromList matching
+ compilerTellDependencies [PatternDependency pattern set']
return matching
diff --git a/src/Hakyll/Core/Configuration.hs b/src/Hakyll/Core/Configuration.hs
index f9927de..52b23ec 100644
--- a/src/Hakyll/Core/Configuration.hs
+++ b/src/Hakyll/Core/Configuration.hs
@@ -69,6 +69,11 @@ data Configuration = Configuration
, -- | Use an in-memory cache for items. This is faster but uses more
-- memory.
inMemoryCache :: Bool
+ , -- | Override default host for preview server. Default is "127.0.0.1",
+ -- which binds only on the loopback address.
+ -- One can also override the host as a command line argument:
+ -- ./site preview -h "0.0.0.0"
+ previewHost :: String
, -- | Override default port for preview server. Default is 8000.
-- One can also override the port as a command line argument:
-- ./site preview -p 1234
@@ -91,6 +96,7 @@ defaultConfiguration = Configuration
, deployCommand = "echo 'No deploy command specified' && exit 1"
, deploySite = system . deployCommand
, inMemoryCache = True
+ , previewHost = "127.0.0.1"
, previewPort = 8000
}
where
diff --git a/src/Hakyll/Core/Dependencies.hs b/src/Hakyll/Core/Dependencies.hs
index 7597e61..ebb6fd0 100644
--- a/src/Hakyll/Core/Dependencies.hs
+++ b/src/Hakyll/Core/Dependencies.hs
@@ -32,7 +32,7 @@ import Hakyll.Core.Identifier.Pattern
--------------------------------------------------------------------------------
data Dependency
- = PatternDependency Pattern [Identifier]
+ = PatternDependency Pattern (Set Identifier)
| IdentifierDependency Identifier
deriving (Show, Typeable)
@@ -91,7 +91,7 @@ dependenciesFor id' = do
return $ concatMap dependenciesFor' $ fromMaybe [] $ M.lookup id' facts
where
dependenciesFor' (IdentifierDependency i) = [i]
- dependenciesFor' (PatternDependency _ is) = is
+ dependenciesFor' (PatternDependency _ is) = S.toList is
--------------------------------------------------------------------------------
@@ -116,7 +116,7 @@ checkChangedPatterns = do
go _ ds (IdentifierDependency i) = return $ IdentifierDependency i : ds
go id' ds (PatternDependency p ls) = do
universe <- ask
- let ls' = filterMatches p universe
+ let ls' = S.fromList $ filterMatches p universe
if ls == ls'
then return $ PatternDependency p ls : ds
else do
diff --git a/src/Hakyll/Core/Metadata.hs b/src/Hakyll/Core/Metadata.hs
index a123c18..3ce854f 100644
--- a/src/Hakyll/Core/Metadata.hs
+++ b/src/Hakyll/Core/Metadata.hs
@@ -5,7 +5,6 @@ module Hakyll.Core.Metadata
, getMetadataField
, getMetadataField'
, makePatternDependency
- , metadataFiles
) where
@@ -13,7 +12,7 @@ module Hakyll.Core.Metadata
import Control.Monad (forM)
import Data.Map (Map)
import qualified Data.Map as M
-import System.FilePath.Posix ((</>), takeDirectory)
+import qualified Data.Set as S
--------------------------------------------------------------------------------
@@ -62,13 +61,4 @@ getMetadataField' identifier key = do
makePatternDependency :: MonadMetadata m => Pattern -> m Dependency
makePatternDependency pattern = do
matches' <- getMatches pattern
- return $ PatternDependency pattern matches'
-
---------------------------------------------------------------------------------
--- | Returns a list of all directory-wise metadata files, subdir first, global last
-metadataFiles :: Identifier -> [Identifier]
-metadataFiles identifier = local : go (takeDirectory $ toFilePath identifier) where
- go "." = [fromFilePath "metadata"]
- go dir = fromFilePath (dir </> "metadata") : go (takeDirectory dir)
- local = fromFilePath $ toFilePath identifier ++ ".metadata"
-
+ return $ PatternDependency pattern (S.fromList matches')
diff --git a/src/Hakyll/Core/Provider/Internal.hs b/src/Hakyll/Core/Provider/Internal.hs
index fdf1342..34400fd 100644
--- a/src/Hakyll/Core/Provider/Internal.hs
+++ b/src/Hakyll/Core/Provider/Internal.hs
@@ -31,8 +31,7 @@ import Data.Maybe (fromMaybe)
import Data.Monoid (mempty)
import Data.Set (Set)
import qualified Data.Set as S
-import Data.Time (Day (..), UTCTime (..),
- secondsToDiffTime)
+import Data.Time (Day (..), UTCTime (..))
import Data.Typeable (Typeable)
import System.Directory (getModificationTime)
import System.FilePath (addExtension, (</>))
@@ -62,11 +61,11 @@ newtype BinaryTime = BinaryTime {unBinaryTime :: UTCTime}
--------------------------------------------------------------------------------
instance Binary BinaryTime where
put (BinaryTime (UTCTime (ModifiedJulianDay d) dt)) =
- put d >> put (floor dt :: Integer)
+ put d >> put (toRational dt)
get = fmap BinaryTime $ UTCTime
<$> (ModifiedJulianDay <$> get)
- <*> (secondsToDiffTime <$> get)
+ <*> (fromRational <$> get)
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Core/Provider/Metadata.hs b/src/Hakyll/Core/Provider/Metadata.hs
index 889291f..7e4d7ed 100644
--- a/src/Hakyll/Core/Provider/Metadata.hs
+++ b/src/Hakyll/Core/Provider/Metadata.hs
@@ -20,8 +20,6 @@ import System.IO as IO
import Text.Parsec ((<?>))
import qualified Text.Parsec as P
import Text.Parsec.String (Parser)
-import System.FilePath.Posix
-import Control.Monad (liftM)
--------------------------------------------------------------------------------
@@ -30,7 +28,7 @@ import Hakyll.Core.Metadata
import Hakyll.Core.Provider.Internal
import Hakyll.Core.Util.Parser
import Hakyll.Core.Util.String
-import Hakyll.Core.Identifier.Pattern
+
--------------------------------------------------------------------------------
loadMetadata :: Provider -> Identifier -> IO (Metadata, Maybe String)
@@ -44,9 +42,7 @@ loadMetadata p identifier = do
Nothing -> return M.empty
Just mi' -> loadMetadataFile $ resourceFilePath p mi'
- gmd <- loadGlobalMetadata p identifier
-
- return (M.unions [md, gmd], body)
+ return (M.union md emd, body)
where
normal = setVersion Nothing identifier
fp = resourceFilePath p identifier
@@ -137,32 +133,3 @@ page = do
metadata' <- P.option [] metadataBlock
body <- P.many P.anyChar
return (metadata', body)
-
-
---------------------------------------------------------------------------------
--- | Load directory-wise metadata
-loadGlobalMetadata :: Provider -> Identifier -> IO Metadata
-loadGlobalMetadata p fp = liftM M.fromList $ loadgm fp where
- loadgm :: Identifier -> IO [(String, String)]
- loadgm = liftM concat . mapM loadOne . reverse . filter (resourceExists p) . metadataFiles
- loadOne mfp =
- let path = resourceFilePath p mfp
- dir = takeDirectory $ toFilePath mfp
- -- TODO: It might be better to print warning and continue
- in either (error.show) (findMetadata dir) . P.parse namedMetadata path <$> readFile path
- findMetadata dir =
- concatMap snd . filter (flip matches fp . fromGlob . normalise . combine dir . fst)
-
-namedMetadata :: Parser [(String, [(String, String)])]
-namedMetadata = liftA2 (:) (namedMetadataBlock False) $ P.many $ namedMetadataBlock True
-
-namedMetadataBlock :: Bool -> Parser (String, [(String, String)])
-namedMetadataBlock isNamed = do
- name <- if isNamed
- then P.many1 (P.char '-') *> P.many inlineSpace *> P.manyTill P.anyChar newline
- else pure "**"
- metadata' <- metadata
- P.skipMany P.space
- return (name, metadata')
-
-
diff --git a/src/Hakyll/Core/Rules/Default.hs b/src/Hakyll/Core/Rules/Default.hs
deleted file mode 100644
index fee78c5..0000000
--- a/src/Hakyll/Core/Rules/Default.hs
+++ /dev/null
@@ -1,24 +0,0 @@
-{-# LANGUAGE OverloadedStrings #-}
-module Hakyll.Core.Rules.Default
- ( internalRules
- , addMetadataDependencies
- )
-where
-import Hakyll.Core.Rules
-import Hakyll.Core.Compiler
-import Hakyll.Core.Compiler.Internal (compilerTellDependencies)
-import Hakyll.Core.Metadata (getMatches, metadataFiles)
-import Hakyll.Core.Identifier.Pattern(fromList)
-
-internalRules :: Rules ()
-internalRules = do
- match "metadata" $ compile $ makeItem ()
- match "**/metadata" $ compile $ makeItem ()
- match "**.metadata" $ compile $ makeItem ()
-
---------------------------------------------------------------------------------
-addMetadataDependencies :: Compiler ()
-addMetadataDependencies =
- compilerTellDependencies . map IdentifierDependency =<< getMatches . fromList =<< fmap metadataFiles getUnderlying
-
-
diff --git a/src/Hakyll/Core/Runtime.hs b/src/Hakyll/Core/Runtime.hs
index 12285ad..824d11b 100644
--- a/src/Hakyll/Core/Runtime.hs
+++ b/src/Hakyll/Core/Runtime.hs
@@ -35,7 +35,6 @@ import qualified Hakyll.Core.Logger as Logger
import Hakyll.Core.Provider
import Hakyll.Core.Routes
import Hakyll.Core.Rules.Internal
-import Hakyll.Core.Rules.Default
import Hakyll.Core.Store (Store)
import qualified Hakyll.Core.Store as Store
import Hakyll.Core.Util.File
@@ -54,7 +53,7 @@ run config verbosity rules = do
provider <- newProvider store (shouldIgnoreFile config) $
providerDirectory config
Logger.message logger "Running rules..."
- ruleSet <- runRules (rules >> internalRules) provider
+ ruleSet <- runRules rules provider
-- Get old facts
mOldFacts <- Store.get store factsKey
@@ -187,7 +186,7 @@ chase trail id'
config <- runtimeConfiguration <$> ask
Logger.debug logger $ "Processing " ++ show id'
- let compiler = addMetadataDependencies >> todo M.! id'
+ let compiler = todo M.! id'
read' = CompilerRead
{ compilerConfig = config
, compilerUnderlying = id'
diff --git a/src/Hakyll/Core/UnixFilter.hs b/src/Hakyll/Core/UnixFilter.hs
index 34b2ecb..edc8eac 100644
--- a/src/Hakyll/Core/UnixFilter.hs
+++ b/src/Hakyll/Core/UnixFilter.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
--------------------------------------------------------------------------------
-- | A Compiler that supports unix filters.
module Hakyll.Core.UnixFilter
@@ -20,7 +22,6 @@ import System.IO (Handle, hClose, hFlush, hGetContents,
hPutStr, hSetEncoding, localeEncoding)
import System.Process
-
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
@@ -105,8 +106,22 @@ unixFilterIO :: Monoid o
-> i
-> IO (o, String, ExitCode)
unixFilterIO writer reader programName args input = do
+ -- The problem on Windows is that `proc` is unable to execute
+ -- batch stubs (eg. anything created using 'gem install ...') even if its in
+ -- `$PATH`. A solution to this issue is to execute the batch file explicitly
+ -- using `cmd /c batchfile` but there is no rational way to know where said
+ -- batchfile is on the system. Hence, we detect windows using the
+ -- CPP and instead of using `proc` to create the process, use `shell`
+ -- which will be able to execute everything `proc` can
+ -- as well as batch files.
+#ifdef mingw32_HOST_OS
+ let pr = shell $ unwords (programName : args)
+#else
+ let pr = proc programName args
+#endif
+
(Just inh, Just outh, Just errh, pid) <-
- createProcess (proc programName args)
+ createProcess pr
{ std_in = CreatePipe
, std_out = CreatePipe
, std_err = CreatePipe