module Hakyll.Core.Configuration
( Configuration (..)
, shouldIgnoreFile
, shouldWatchIgnore
, defaultConfiguration
) where
import Data.Default (Default (..))
import Data.List (isPrefixOf, isSuffixOf)
import qualified Network.Wai.Application.Static as Static
import System.Directory (canonicalizePath)
import System.Exit (ExitCode)
import System.FilePath (isAbsolute, makeRelative, normalise,
takeExtension, takeFileName)
import System.IO.Error (catchIOError)
import System.Process (system)
data Configuration = Configuration
{
Configuration -> String
destinationDirectory :: FilePath
,
Configuration -> String
storeDirectory :: FilePath
,
Configuration -> String
tmpDirectory :: FilePath
,
Configuration -> String
providerDirectory :: FilePath
,
Configuration -> String -> Bool
ignoreFile :: FilePath -> Bool
,
Configuration -> String -> Bool
checkHtmlFile :: FilePath -> Bool
,
Configuration -> String -> Bool
watchIgnore :: FilePath -> Bool
,
Configuration -> String
deployCommand :: String
,
Configuration -> Configuration -> IO ExitCode
deploySite :: Configuration -> IO ExitCode
,
Configuration -> Bool
inMemoryCache :: Bool
,
Configuration -> String
previewHost :: String
,
Configuration -> Int
previewPort :: Int
,
Configuration -> String -> StaticSettings
previewSettings :: FilePath -> Static.StaticSettings
}
instance Default Configuration where
def :: Configuration
def = Configuration
defaultConfiguration
defaultConfiguration :: Configuration
defaultConfiguration :: Configuration
defaultConfiguration = Configuration
{ destinationDirectory :: String
destinationDirectory = String
"_site"
, storeDirectory :: String
storeDirectory = String
"_cache"
, tmpDirectory :: String
tmpDirectory = String
"_cache/tmp"
, providerDirectory :: String
providerDirectory = String
"."
, ignoreFile :: String -> Bool
ignoreFile = String -> Bool
ignoreFile'
, checkHtmlFile :: String -> Bool
checkHtmlFile = (String -> [String] -> Bool) -> [String] -> String -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem [String
".html", String
".xhtml"] (String -> Bool) -> (String -> String) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
takeExtension
, watchIgnore :: String -> Bool
watchIgnore = Bool -> String -> Bool
forall a b. a -> b -> a
const Bool
False
, deployCommand :: String
deployCommand = String
"echo 'No deploy command specified' && exit 1"
, deploySite :: Configuration -> IO ExitCode
deploySite = String -> IO ExitCode
system (String -> IO ExitCode)
-> (Configuration -> String) -> Configuration -> IO ExitCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Configuration -> String
deployCommand
, inMemoryCache :: Bool
inMemoryCache = Bool
True
, previewHost :: String
previewHost = String
"127.0.0.1"
, previewPort :: Int
previewPort = Int
8000
, previewSettings :: String -> StaticSettings
previewSettings = String -> StaticSettings
Static.defaultFileServerSettings
}
where
ignoreFile' :: String -> Bool
ignoreFile' String
path
| String
"." String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
fileName = Bool
True
| String
"#" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
fileName = Bool
True
| String
"~" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
fileName = Bool
True
| String
".swp" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
fileName = Bool
True
| Bool
otherwise = Bool
False
where
fileName :: String
fileName = String -> String
takeFileName String
path
shouldIgnoreFile :: Configuration -> FilePath -> IO Bool
shouldIgnoreFile :: Configuration -> String -> IO Bool
shouldIgnoreFile Configuration
conf String
path = [IO Bool] -> IO Bool
orM
[ String -> IO Bool
inDir (String
"dist-newstyle")
, String -> IO Bool
inDir (String
".stack-work")
, String -> IO Bool
inDir (Configuration -> String
destinationDirectory Configuration
conf)
, String -> IO Bool
inDir (Configuration -> String
storeDirectory Configuration
conf)
, String -> IO Bool
inDir (Configuration -> String
tmpDirectory Configuration
conf)
, Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Configuration -> String -> Bool
ignoreFile Configuration
conf String
path')
]
where
path' :: String
path' = String -> String
normalise String
path
absolute :: Bool
absolute = String -> Bool
isAbsolute String
path
inDir :: String -> IO Bool
inDir String
dir
| Bool
absolute = do
String
dir' <- IO String -> (IOError -> IO String) -> IO String
forall a. IO a -> (IOError -> IO a) -> IO a
catchIOError (String -> IO String
canonicalizePath String
dir) (IO String -> IOError -> IO String
forall a b. a -> b -> a
const (IO String -> IOError -> IO String)
-> IO String -> IOError -> IO String
forall a b. (a -> b) -> a -> b
$ String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
dir)
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ String
dir' String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
path'
| Bool
otherwise = Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ String
dir String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
path'
orM :: [IO Bool] -> IO Bool
orM :: [IO Bool] -> IO Bool
orM [] = Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
orM (IO Bool
x : [IO Bool]
xs) = IO Bool
x IO Bool -> (Bool -> IO Bool) -> IO Bool
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
b -> if Bool
b then Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True else [IO Bool] -> IO Bool
orM [IO Bool]
xs
shouldWatchIgnore :: Configuration -> IO (FilePath -> IO Bool)
shouldWatchIgnore :: Configuration -> IO (String -> IO Bool)
shouldWatchIgnore Configuration
conf = do
String
fullProviderDir <- String -> IO String
canonicalizePath (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ Configuration -> String
providerDirectory Configuration
conf
(String -> IO Bool) -> IO (String -> IO Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (\String
path ->
let path' :: String
path' = String -> String -> String
makeRelative String
fullProviderDir String
path
in (Bool -> Bool -> Bool
|| Configuration -> String -> Bool
watchIgnore Configuration
conf String
path') (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Configuration -> String -> IO Bool
shouldIgnoreFile Configuration
conf String
path)