module Hakyll.Core.Configuration
    ( Configuration (..)
    , shouldIgnoreFile
    , shouldWatchIgnore
    , defaultConfiguration
    ) where
import           Data.Default     (Default (..))
import           Data.List        (isPrefixOf, isSuffixOf)
import           System.Directory (canonicalizePath)
import           System.Exit      (ExitCode)
import           System.FilePath  (isAbsolute, normalise, takeFileName, makeRelative)
import           System.IO.Error  (catchIOError)
import           System.Process   (system)
data Configuration = Configuration
    { 
      Configuration -> FilePath
destinationDirectory :: FilePath
    , 
      Configuration -> FilePath
storeDirectory       :: FilePath
    , 
      Configuration -> FilePath
tmpDirectory         :: FilePath
    , 
      
      Configuration -> FilePath
providerDirectory    :: FilePath
    , 
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      
      Configuration -> FilePath -> Bool
ignoreFile           :: FilePath -> Bool
    , 
      
      
      
      
      
      
      Configuration -> FilePath -> Bool
watchIgnore          :: FilePath -> Bool
    , 
      
      
      
      
      
      
      
      
      
      Configuration -> FilePath
deployCommand        :: String
    , 
      
      
      
      
      
      
      
      
      Configuration -> Configuration -> IO ExitCode
deploySite           :: Configuration -> IO ExitCode
    , 
      
      Configuration -> Bool
inMemoryCache        :: Bool
    , 
      
      
      
      Configuration -> FilePath
previewHost          :: String
    , 
      
      
      Configuration -> Int
previewPort          :: Int
    }
instance Default Configuration where
    def :: Configuration
def = Configuration
defaultConfiguration
defaultConfiguration :: Configuration
defaultConfiguration :: Configuration
defaultConfiguration = Configuration :: FilePath
-> FilePath
-> FilePath
-> FilePath
-> (FilePath -> Bool)
-> (FilePath -> Bool)
-> FilePath
-> (Configuration -> IO ExitCode)
-> Bool
-> FilePath
-> Int
-> Configuration
Configuration
    { destinationDirectory :: FilePath
destinationDirectory = FilePath
"_site"
    , storeDirectory :: FilePath
storeDirectory       = FilePath
"_cache"
    , tmpDirectory :: FilePath
tmpDirectory         = FilePath
"_cache/tmp"
    , providerDirectory :: FilePath
providerDirectory    = FilePath
"."
    , ignoreFile :: FilePath -> Bool
ignoreFile           = FilePath -> Bool
ignoreFile'
    , watchIgnore :: FilePath -> Bool
watchIgnore          = Bool -> FilePath -> Bool
forall a b. a -> b -> a
const Bool
False
    , deployCommand :: FilePath
deployCommand        = FilePath
"echo 'No deploy command specified' && exit 1"
    , deploySite :: Configuration -> IO ExitCode
deploySite           = FilePath -> IO ExitCode
system (FilePath -> IO ExitCode)
-> (Configuration -> FilePath) -> Configuration -> IO ExitCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Configuration -> FilePath
deployCommand
    , inMemoryCache :: Bool
inMemoryCache        = Bool
True
    , previewHost :: FilePath
previewHost          = FilePath
"127.0.0.1"
    , previewPort :: Int
previewPort          = Int
8000
    }
  where
    ignoreFile' :: FilePath -> Bool
ignoreFile' FilePath
path
        | FilePath
"."    FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
fileName = Bool
True
        | FilePath
"#"    FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
fileName = Bool
True
        | FilePath
"~"    FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` FilePath
fileName = Bool
True
        | FilePath
".swp" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` FilePath
fileName = Bool
True
        | Bool
otherwise                    = Bool
False
      where
        fileName :: FilePath
fileName = FilePath -> FilePath
takeFileName FilePath
path
shouldIgnoreFile :: Configuration -> FilePath -> IO Bool
shouldIgnoreFile :: Configuration -> FilePath -> IO Bool
shouldIgnoreFile Configuration
conf FilePath
path = [IO Bool] -> IO Bool
orM
    [ FilePath -> IO Bool
inDir (Configuration -> FilePath
destinationDirectory Configuration
conf)
    , FilePath -> IO Bool
inDir (Configuration -> FilePath
storeDirectory Configuration
conf)
    , FilePath -> IO Bool
inDir (Configuration -> FilePath
tmpDirectory Configuration
conf)
    , Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Configuration -> FilePath -> Bool
ignoreFile Configuration
conf FilePath
path')
    ]
  where
    path' :: FilePath
path'    = FilePath -> FilePath
normalise FilePath
path
    absolute :: Bool
absolute = FilePath -> Bool
isAbsolute FilePath
path
    inDir :: FilePath -> IO Bool
inDir FilePath
dir
        | Bool
absolute  = do
            FilePath
dir' <- IO FilePath -> (IOError -> IO FilePath) -> IO FilePath
forall a. IO a -> (IOError -> IO a) -> IO a
catchIOError (FilePath -> IO FilePath
canonicalizePath FilePath
dir) (IO FilePath -> IOError -> IO FilePath
forall a b. a -> b -> a
const (IO FilePath -> IOError -> IO FilePath)
-> IO FilePath -> IOError -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
dir)
            Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
dir' FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
path'
        | Bool
otherwise = Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
dir FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` FilePath
path'
    orM :: [IO Bool] -> IO Bool
    orM :: [IO Bool] -> IO Bool
orM []       = Bool -> IO Bool
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 (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
b -> if Bool
b then Bool -> IO Bool
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 (FilePath -> IO Bool)
shouldWatchIgnore Configuration
conf = do
    FilePath
fullProviderDir <- FilePath -> IO FilePath
canonicalizePath (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ Configuration -> FilePath
providerDirectory Configuration
conf
    (FilePath -> IO Bool) -> IO (FilePath -> IO Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (\FilePath
path ->
              let path' :: FilePath
path' = FilePath -> FilePath -> FilePath
makeRelative FilePath
fullProviderDir FilePath
path
              in (Bool -> Bool -> Bool
|| Configuration -> FilePath -> Bool
watchIgnore Configuration
conf FilePath
path') (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Configuration -> FilePath -> IO Bool
shouldIgnoreFile Configuration
conf FilePath
path)