--------------------------------------------------------------------------------
-- | Exports a datastructure for the top-level hakyll configuration
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
    { -- | Directory in which the output written
      Configuration -> String
destinationDirectory :: FilePath
    , -- | Directory where hakyll's internal store is kept
      Configuration -> String
storeDirectory       :: FilePath
    , -- | Directory in which some temporary files will be kept
      Configuration -> String
tmpDirectory         :: FilePath
    , -- | Directory where hakyll finds the files to compile. This is @.@ by
      -- default.
      Configuration -> String
providerDirectory    :: FilePath
    , -- | Function to determine ignored files
      --
      -- In 'defaultConfiguration', the following files are ignored:
      --
      -- * files starting with a @.@
      --
      -- * files starting with a @#@
      --
      -- * files ending with a @~@
      --
      -- * files ending with @.swp@
      --
      -- Note that the files in 'destinationDirectory' and 'storeDirectory' will
      -- also be ignored. Note that this is the configuration parameter, if you
      -- want to use the test, you should use 'shouldIgnoreFile'.
      --
      Configuration -> String -> Bool
ignoreFile           :: FilePath -> Bool
    , -- | Function to determine HTML files whose links are to be checked.
      --
      -- In 'defaultConfiguration', files with the @.html@ extension are checked.
      Configuration -> String -> Bool
checkHtmlFile        :: FilePath -> Bool
    , -- | Function to determine files and directories that should not trigger
      -- a rebuild when touched in watch mode.
      --
      -- Paths are passed in relative to the providerDirectory.
      --
      -- All files that are ignored by 'ignoreFile' are also always ignored by
      -- 'watchIgnore'.
      Configuration -> String -> Bool
watchIgnore          :: FilePath -> Bool
    , -- | Here, you can plug in a system command to upload/deploy your site.
      --
      -- Example:
      --
      -- > rsync -ave 'ssh -p 2217' _site jaspervdj@jaspervdj.be:hakyll
      --
      -- You can execute this by using
      --
      -- > ./site deploy
      --
      Configuration -> String
deployCommand        :: String
    , -- | Function to deploy the site from Haskell.
      --
      -- By default, this command executes the shell command stored in
      -- 'deployCommand'. If you override it, 'deployCommand' will not
      -- be used implicitely.
      --
      -- The 'Configuration' object is passed as a parameter to this
      -- function.
      --
      Configuration -> Configuration -> IO ExitCode
deploySite           :: Configuration -> IO ExitCode
    , -- | Use an in-memory cache for items. This is faster but uses more
      -- memory.
      Configuration -> Bool
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"
      Configuration -> String
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
      Configuration -> Int
previewPort          :: Int
    , -- | Override other settings used by the preview server. Default is
      -- 'Static.defaultFileServerSettings'.
      Configuration -> String -> StaticSettings
previewSettings      :: FilePath -> Static.StaticSettings
    }

--------------------------------------------------------------------------------
instance Default Configuration where
    def :: Configuration
def = Configuration
defaultConfiguration

--------------------------------------------------------------------------------
-- | Default configuration for a hakyll application
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        = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem [String
".html", String
".xhtml"] forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
takeExtension
    , watchIgnore :: String -> Bool
watchIgnore          = 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 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
"."    forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
fileName = Bool
True
        | String
"#"    forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
fileName = Bool
True
        | String
"~"    forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
fileName = Bool
True
        | String
".swp" 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


--------------------------------------------------------------------------------
-- | Check if a file should be ignored
shouldIgnoreFile :: Configuration -> FilePath -> IO Bool
shouldIgnoreFile :: Configuration -> String -> IO Bool
shouldIgnoreFile Configuration
conf String
path = [IO Bool] -> IO Bool
orM
    [ 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)
    , 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' <- forall a. IO a -> (IOError -> IO a) -> IO a
catchIOError (String -> IO String
canonicalizePath String
dir) (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return String
dir)
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String
dir' forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
path'
        | Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String
dir forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
path'

    orM :: [IO Bool] -> IO Bool
    orM :: [IO Bool] -> IO Bool
orM []       = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
    orM (IO Bool
x : [IO Bool]
xs) = IO Bool
x forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
b -> if Bool
b then forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True else [IO Bool] -> IO Bool
orM [IO Bool]
xs

-- | Returns a function to check if a file should be ignored in watch mode
shouldWatchIgnore :: Configuration -> IO (FilePath -> IO Bool)
shouldWatchIgnore :: Configuration -> IO (String -> IO Bool)
shouldWatchIgnore Configuration
conf = do
    String
fullProviderDir <- String -> IO String
canonicalizePath forall a b. (a -> b) -> a -> b
$ Configuration -> String
providerDirectory Configuration
conf
    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') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Configuration -> String -> IO Bool
shouldIgnoreFile Configuration
conf String
path)