module Hakyll.Core.Compiler
( Compiler
, runCompiler
, getIdentifier
, getResource
, getRoute
, getRouteFor
, getResourceString
, getResourceLBS
, fromDependency
, require_
, require
, requireA
, requireAll_
, requireAll
, requireAllA
, cached
, unsafeCompiler
, traceShowCompiler
, mapCompiler
, timedCompiler
, byExtension
) where
import Prelude hiding ((.), id)
import Control.Arrow ((>>>), (&&&), arr)
import Control.Applicative ((<$>))
import Control.Monad.Reader (ask)
import Control.Monad.Trans (liftIO)
import Control.Monad.Error (throwError)
import Control.Category (Category, (.), id)
import Data.Maybe (fromMaybe)
import System.FilePath (takeExtension)
import Data.Binary (Binary)
import Data.Typeable (Typeable)
import Data.ByteString.Lazy (ByteString)
import Hakyll.Core.Identifier
import Hakyll.Core.Identifier.Pattern
import Hakyll.Core.CompiledItem
import Hakyll.Core.Writable
import Hakyll.Core.Resource
import Hakyll.Core.Resource.Provider
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Store
import Hakyll.Core.Rules.Internal
import Hakyll.Core.Routes
import Hakyll.Core.Logger
runCompiler :: Compiler () CompileRule
-> Identifier
-> ResourceProvider
-> [Identifier]
-> Routes
-> Store
-> Bool
-> Logger
-> IO (Throwing CompileRule)
runCompiler compiler id' provider universe routes store modified logger = do
result <- runCompilerJob compiler id' provider universe
routes store modified logger
case result of
Right (CompileRule (CompiledItem x)) ->
storeSet store "Hakyll.Core.Compiler.runCompiler" id' x
_ -> return ()
return result
getIdentifier :: Compiler a Identifier
getIdentifier = fromJob $ const $ CompilerM $ compilerIdentifier <$> ask
getResource :: Compiler a Resource
getResource = getIdentifier >>> arr fromIdentifier
getRoute :: Compiler a (Maybe FilePath)
getRoute = getIdentifier >>> getRouteFor
getRouteFor :: Compiler Identifier (Maybe FilePath)
getRouteFor = fromJob $ \identifier -> CompilerM $ do
routes <- compilerRoutes <$> ask
return $ runRoutes routes identifier
getResourceString :: Compiler Resource String
getResourceString = getResourceWith resourceString
getResourceLBS :: Compiler Resource ByteString
getResourceLBS = getResourceWith resourceLBS
getResourceWith :: (ResourceProvider -> Resource -> IO a)
-> Compiler Resource a
getResourceWith reader = fromJob $ \resource -> CompilerM $ do
let identifier = unResource resource
provider <- compilerResourceProvider <$> ask
if resourceExists provider resource
then liftIO $ reader provider resource
else throwError $ error' identifier
where
error' id' = "Hakyll.Core.Compiler.getResourceWith: resource "
++ show id' ++ " not found"
getDependency :: (Binary a, Writable a, Typeable a)
=> Identifier -> CompilerM a
getDependency id' = CompilerM $ do
store <- compilerStore <$> ask
result <- liftIO $ storeGet store "Hakyll.Core.Compiler.runCompiler" id'
case result of
NotFound -> throwError notFound
WrongType e r -> throwError $ wrongType e r
Found x -> return x
where
notFound =
"Hakyll.Core.Compiler.getDependency: " ++ show id' ++ " not found " ++
"not found in the cache, the cache might be corrupted or " ++
"the item you are referring to might not exist"
wrongType e r =
"Hakyll.Core.Compiler.getDependency: " ++ show id' ++ " was found " ++
"in the cache, but does not have the right type: expected " ++ show e ++
" but got " ++ show r
require_ :: (Binary a, Typeable a, Writable a)
=> Identifier
-> Compiler b a
require_ identifier =
fromDependency identifier >>> fromJob (const $ getDependency identifier)
require :: (Binary a, Typeable a, Writable a)
=> Identifier
-> (b -> a -> c)
-> Compiler b c
require identifier = requireA identifier . arr . uncurry
requireA :: (Binary a, Typeable a, Writable a)
=> Identifier
-> Compiler (b, a) c
-> Compiler b c
requireA identifier = (id &&& require_ identifier >>>)
requireAll_ :: (Binary a, Typeable a, Writable a)
=> Pattern
-> Compiler b [a]
requireAll_ pattern = fromDependencies (const getDeps) >>> fromJob requireAll_'
where
getDeps = filterMatches pattern
requireAll_' = const $ CompilerM $ do
deps <- getDeps . compilerUniverse <$> ask
mapM (unCompilerM . getDependency) deps
requireAll :: (Binary a, Typeable a, Writable a)
=> Pattern
-> (b -> [a] -> c)
-> Compiler b c
requireAll pattern = requireAllA pattern . arr . uncurry
requireAllA :: (Binary a, Typeable a, Writable a)
=> Pattern
-> Compiler (b, [a]) c
-> Compiler b c
requireAllA pattern = (id &&& requireAll_ pattern >>>)
cached :: (Binary a, Typeable a, Writable a)
=> String
-> Compiler Resource a
-> Compiler Resource a
cached name (Compiler d j) = Compiler d $ const $ CompilerM $ do
logger <- compilerLogger <$> ask
identifier <- compilerIdentifier <$> ask
store <- compilerStore <$> ask
modified <- compilerResourceModified <$> ask
report logger $ "Checking cache: " ++ if modified then "modified" else "OK"
if modified
then do v <- unCompilerM $ j $ fromIdentifier identifier
liftIO $ storeSet store name identifier v
return v
else do v <- liftIO $ storeGet store name identifier
case v of Found v' -> return v'
_ -> throwError error'
where
error' = "Hakyll.Core.Compiler.cached: Cache corrupt!"
unsafeCompiler :: (a -> IO b)
-> Compiler a b
unsafeCompiler f = fromJob $ CompilerM . liftIO . f
traceShowCompiler :: Show a => Compiler a a
traceShowCompiler = fromJob $ \x -> CompilerM $ do
logger <- compilerLogger <$> ask
report logger $ show x
return x
mapCompiler :: Compiler a b
-> Compiler [a] [b]
mapCompiler (Compiler d j) = Compiler d $ mapM j
timedCompiler :: String
-> Compiler a b
-> Compiler a b
timedCompiler msg (Compiler d j) = Compiler d $ \x -> CompilerM $ do
logger <- compilerLogger <$> ask
timed logger msg $ unCompilerM $ j x
byExtension :: Compiler a b
-> [(String, Compiler a b)]
-> Compiler a b
byExtension defaultCompiler choices = Compiler deps job
where
lookup' identifier =
let extension = takeExtension $ toFilePath identifier
in fromMaybe defaultCompiler $ lookup extension choices
deps = do
identifier <- dependencyIdentifier <$> ask
compilerDependencies $ lookup' identifier
job x = CompilerM $ do
identifier <- compilerIdentifier <$> ask
unCompilerM $ compilerJob (lookup' identifier) x