module Text.Hakyll.File
( toDestination
, toURL
, toRoot
, removeSpaces
, makeDirectories
, getRecursiveContents
, havingExtension
, isCacheValid
, directory
) where
import System.Directory
import System.FilePath
import Control.Monad
import Data.List (isPrefixOf)
import Control.Monad.Reader (liftIO)
import Text.Hakyll.Hakyll (Hakyll)
removeLeadingSeparator :: FilePath -> FilePath
removeLeadingSeparator [] = []
removeLeadingSeparator path
| head path' `elem` pathSeparators = tail path'
| otherwise = path'
where
path' = if "$root" `isPrefixOf` path then drop 5 path
else path
toDestination :: FilePath -> FilePath
toDestination path = "_site" </> removeLeadingSeparator path
toURL :: FilePath -> FilePath
toURL path = if takeExtension path `elem` [ ".markdown"
, ".md"
, ".mdn"
, ".mdwn"
, ".mkd"
, ".mkdn"
, ".mkdwn"
, ".rst"
, ".text"
, ".tex"
]
then flip addExtension ".html" $ dropExtension path
else path
toRoot :: FilePath -> FilePath
toRoot = emptyException . joinPath . map parent . splitPath
. takeDirectory . removeLeadingSeparator
where
parent = const ".."
emptyException [] = "."
emptyException x = x
removeSpaces :: FilePath -> FilePath
removeSpaces = map swap
where
swap ' ' = '-'
swap x = x
makeDirectories :: FilePath -> Hakyll ()
makeDirectories path = liftIO $ createDirectoryIfMissing True dir
where
dir = takeDirectory path
getRecursiveContents :: FilePath -> Hakyll [FilePath]
getRecursiveContents topdir = do
names <- liftIO $ getDirectoryContents topdir
let properNames = filter isProper names
paths <- forM properNames $ \name -> do
let path = topdir </> name
isDirectory <- liftIO $ doesDirectoryExist path
if isDirectory
then getRecursiveContents path
else return [path]
return (concat paths)
where
isProper = not . (== '.') . head
havingExtension :: String -> [FilePath] -> [FilePath]
havingExtension extension = filter ((==) extension . takeExtension)
directory :: (FilePath -> Hakyll ()) -> FilePath -> Hakyll ()
directory action dir = getRecursiveContents dir >>= mapM_ action
isCacheValid :: FilePath
-> [FilePath]
-> Hakyll Bool
isCacheValid cache depends = do
exists <- liftIO $ doesFileExist cache
if not exists
then return False
else do dependsModified <- liftIO $ mapM getModificationTime depends
cacheModified <- liftIO $ getModificationTime cache
return (cacheModified >= maximum dependsModified)