hakyll/src/Hakyll/Core/Compiler.hs

399 lines
14 KiB
Haskell
Raw Normal View History

2011-02-12 09:26:58 +00:00
-- | A Compiler manages targets and dependencies between targets
--
-- The most distinguishing property of a 'Compiler' is that it is an Arrow. A
-- compiler of the type @Compiler a b@ is simply a compilation phase which takes
-- an @a@ as input, and produces a @b@ as output.
--
-- Compilers are chained using the '>>>' arrow operation. If we have a compiler
--
-- > getResourceString :: Compiler Resource String
--
-- which reads the resource, and a compiler
--
-- > readPage :: Compiler String (Page String)
--
-- we can chain these two compilers to get a
--
-- > (getResourceString >>> readPage) :: Compiler Resource (Page String)
--
-- Most compilers can be created by combining smaller compilers using '>>>'.
--
-- More advanced constructions are also possible using arrow, and sometimes
-- these are needed. For a good introduction to arrow, you can refer to
--
-- <http://en.wikibooks.org/wiki/Haskell/Understanding_arrows>
--
-- A construction worth writing a few paragraphs about here are the 'require'
-- functions. Different variants of this function are exported here, but they
-- all serve more or less the same goal.
--
-- When you use only '>>>' to chain your compilers, you get a linear pipeline --
-- it is not possible to add extra items from other compilers along the way.
-- This is where the 'require' functions come in.
--
-- This function allows you to reference other items, which are then added to
-- the pipeline. Let's look at this crappy ASCII illustration which represents
-- a pretty common scenario:
--
-- > read resource >>> pandoc render >>> layout >>> relativize URL's
-- >
-- > @templates/fancy.html@
--
-- We want to construct a pipeline of compilers to go from our resource to a
-- proper webpage. However, the @layout@ compiler takes more than just the
-- rendered page as input: it needs the @templates/fancy.html@ template as well.
--
-- This is an example of where we need the @require@ function. We can solve
-- this using a construction that looks like:
--
-- > ... >>> pandoc render >>> require >>> layout >>> ...
-- > |
-- > @templates/fancy.html@ ------/
--
-- This illustration can help us understand the type signature of 'require'.
--
-- > require :: (Binary a, Typeable a, Writable a)
2011-05-28 20:33:48 +00:00
-- > => Identifier a
2011-02-12 09:26:58 +00:00
-- > -> (b -> a -> c)
-- > -> Compiler b c
--
-- Let's look at it in detail:
--
-- > (Binary a, Typeable a, Writable a)
--
-- These are constraints for the @a@ type. @a@ (the template) needs to have
-- certain properties for it to be required.
--
2011-05-28 20:33:48 +00:00
-- > Identifier a
2011-02-12 09:26:58 +00:00
--
-- This is simply @templates/fancy.html@: the 'Identifier' of the item we want
-- to 'require', in other words, the name of the item we want to add to the
-- pipeline somehow.
--
-- > (b -> a -> c)
--
-- This is a function given by the user, specifying /how/ the two items shall be
-- merged. @b@ is the output of the previous compiler, and @a@ is the item we
-- just required -- the template. This means @c@ will be the final output of the
-- 'require' combinator.
--
-- > Compiler b c
--
-- Indeed, we have now constructed a compiler which takes a @b@ and produces a
-- @c@. This means that we have a linear pipeline again, thanks to the 'require'
-- function. So, the 'require' function actually helps to reduce to complexity
-- of Hakyll applications!
2010-12-25 17:15:44 +00:00
--
2011-05-17 09:00:53 +00:00
-- Note that require will fetch a previously compiled item: in our example of
-- the type @a@. It is /very/ important that the compiler which produced this
-- value, produced the right type as well!
--
2012-03-18 09:44:54 +00:00
{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables #-}
2010-12-25 17:15:44 +00:00
module Hakyll.Core.Compiler
( Compiler
, runCompiler
2010-12-29 21:59:38 +00:00
, getIdentifier
, getResource
2010-12-30 20:18:55 +00:00
, getRoute
2011-02-06 17:32:09 +00:00
, getRouteFor
2010-12-29 21:59:38 +00:00
, getResourceString
2011-05-06 08:28:35 +00:00
, getResourceLBS
2011-09-19 21:08:40 +00:00
, getResourceWith
2011-01-07 18:17:14 +00:00
, fromDependency
, require_
2010-12-25 17:15:44 +00:00
, require
2011-01-18 22:58:29 +00:00
, requireA
, requireAll_
2010-12-30 09:02:25 +00:00
, requireAll
2011-01-18 22:58:29 +00:00
, requireAllA
, cached
2011-01-17 21:43:44 +00:00
, unsafeCompiler
, traceShowCompiler
2011-02-09 12:02:28 +00:00
, mapCompiler
2011-02-21 12:02:35 +00:00
, timedCompiler
2012-02-13 21:30:48 +00:00
, byPattern
2011-02-25 13:36:34 +00:00
, byExtension
2010-12-25 17:15:44 +00:00
) where
2010-12-29 21:59:38 +00:00
import Prelude hiding ((.), id)
2012-02-13 20:44:38 +00:00
import Control.Arrow ((>>>), (&&&), arr, first)
import Control.Applicative ((<$>))
2012-03-18 09:44:54 +00:00
import Control.Exception (SomeException, handle)
import Control.Monad.Reader (ask)
2010-12-29 21:59:38 +00:00
import Control.Monad.Trans (liftIO)
2011-03-06 14:56:22 +00:00
import Control.Monad.Error (throwError)
import Control.Category (Category, (.), id)
2012-02-13 20:44:38 +00:00
import Data.List (find)
import System.Environment (getProgName)
2011-02-25 13:36:34 +00:00
import System.FilePath (takeExtension)
2010-12-29 21:59:38 +00:00
2010-12-28 10:12:45 +00:00
import Data.Binary (Binary)
2010-12-29 21:59:38 +00:00
import Data.Typeable (Typeable)
2011-05-06 08:28:35 +00:00
import Data.ByteString.Lazy (ByteString)
2010-12-25 17:15:44 +00:00
import Hakyll.Core.Identifier
2010-12-29 14:33:22 +00:00
import Hakyll.Core.Identifier.Pattern
2010-12-28 10:12:45 +00:00
import Hakyll.Core.CompiledItem
import Hakyll.Core.Writable
2011-04-05 20:14:49 +00:00
import Hakyll.Core.Resource
import Hakyll.Core.Resource.Provider
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Store
2011-02-11 12:30:55 +00:00
import Hakyll.Core.Rules.Internal
2011-02-03 15:07:49 +00:00
import Hakyll.Core.Routes
2011-02-21 12:02:35 +00:00
import Hakyll.Core.Logger
2010-12-29 21:59:38 +00:00
-- | Run a compiler, yielding the resulting target and it's dependencies. This
-- version of 'runCompilerJob' also stores the result
--
2011-03-06 14:56:22 +00:00
runCompiler :: Compiler () CompileRule -- ^ Compiler to run
2011-05-24 09:58:13 +00:00
-> Identifier () -- ^ Target identifier
2011-03-06 14:56:22 +00:00
-> ResourceProvider -- ^ Resource provider
2011-05-24 09:58:13 +00:00
-> [Identifier ()] -- ^ Universe
2011-03-06 14:56:22 +00:00
-> Routes -- ^ Route
-> Store -- ^ Store
-> Bool -- ^ Was the resource modified?
-> Logger -- ^ Logger
-> IO (Throwing CompileRule) -- ^ Resulting item
runCompiler compiler id' provider universe routes store modified logger = do
2011-01-04 10:13:08 +00:00
-- Run the compiler job
2012-03-18 09:44:54 +00:00
result <- handle (\(e :: SomeException) -> return $ Left $ show e) $
runCompilerJob compiler id' provider universe routes store modified
logger
2011-01-04 10:13:08 +00:00
2011-01-07 11:12:13 +00:00
-- Inspect the result
case result of
-- In case we compiled an item, we will store a copy in the cache first,
-- before we return control. This makes sure the compiled item can later
-- be accessed by e.g. require.
2011-03-06 14:56:22 +00:00
Right (CompileRule (CompiledItem x)) ->
2011-05-24 09:58:13 +00:00
storeSet store "Hakyll.Core.Compiler.runCompiler"
(castIdentifier id') x
2011-01-07 11:12:13 +00:00
-- Otherwise, we do nothing here
_ -> return ()
return result
2010-12-30 20:18:55 +00:00
-- | Get the identifier of the item that is currently being compiled
--
2011-05-24 09:58:13 +00:00
getIdentifier :: Compiler a (Identifier b)
getIdentifier = fromJob $ const $ CompilerM $
castIdentifier . compilerIdentifier <$> ask
2010-12-30 20:18:55 +00:00
-- | Get the resource that is currently being compiled
--
getResource :: Compiler a Resource
getResource = getIdentifier >>> arr fromIdentifier
2010-12-30 20:18:55 +00:00
-- | Get the route we are using for this item
--
getRoute :: Compiler a (Maybe FilePath)
2011-02-06 17:32:09 +00:00
getRoute = getIdentifier >>> getRouteFor
-- | Get the route for a specified item
--
2011-05-24 09:58:13 +00:00
getRouteFor :: Compiler (Identifier a) (Maybe FilePath)
2011-02-06 17:32:09 +00:00
getRouteFor = fromJob $ \identifier -> CompilerM $ do
2011-02-03 15:07:49 +00:00
routes <- compilerRoutes <$> ask
return $ runRoutes routes identifier
2010-12-29 21:59:38 +00:00
2010-12-30 20:18:55 +00:00
-- | Get the resource we are compiling as a string
--
getResourceString :: Compiler Resource String
2011-05-06 08:28:35 +00:00
getResourceString = getResourceWith resourceString
-- | Get the resource we are compiling as a lazy bytestring
--
getResourceLBS :: Compiler Resource ByteString
getResourceLBS = getResourceWith resourceLBS
-- | Overloadable function for 'getResourceString' and 'getResourceLBS'
--
getResourceWith :: (ResourceProvider -> Resource -> IO a)
-> Compiler Resource a
getResourceWith reader = fromJob $ \r -> CompilerM $ do
let filePath = unResource r
provider <- compilerResourceProvider <$> ask
if resourceExists provider r
then liftIO $ reader provider r
else throwError $ error' filePath
2011-03-07 10:04:01 +00:00
where
2011-05-06 08:28:35 +00:00
error' id' = "Hakyll.Core.Compiler.getResourceWith: resource "
2011-03-07 10:04:01 +00:00
++ show id' ++ " not found"
2010-12-25 17:15:44 +00:00
-- | Auxiliary: get a dependency
--
getDependency :: (Binary a, Writable a, Typeable a)
2011-05-24 09:58:13 +00:00
=> Identifier a -> CompilerM a
2011-03-06 14:56:22 +00:00
getDependency id' = CompilerM $ do
store <- compilerStore <$> ask
2011-03-06 14:56:22 +00:00
result <- liftIO $ storeGet store "Hakyll.Core.Compiler.runCompiler" id'
case result of
2011-05-18 22:41:39 +00:00
NotFound -> throwError notFound
WrongType e r -> throwError $ wrongType e r
Found x -> return x
where
2011-05-18 22:41:39 +00:00
notFound =
2011-05-30 09:45:22 +00:00
"Hakyll.Core.Compiler.getDependency: " ++ show id' ++ " was " ++
2011-05-18 22:41:39 +00:00
"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
-- | Variant of 'require' which drops the current value
--
require_ :: (Binary a, Typeable a, Writable a)
2011-05-24 09:58:13 +00:00
=> Identifier a
-> Compiler b a
require_ identifier =
fromDependency identifier >>> fromJob (const $ getDependency identifier)
2010-12-25 17:15:44 +00:00
-- | Require another target. Using this function ensures automatic handling of
-- dependencies
--
2010-12-28 10:12:45 +00:00
require :: (Binary a, Typeable a, Writable a)
2011-05-24 09:58:13 +00:00
=> Identifier a
2010-12-30 09:02:25 +00:00
-> (b -> a -> c)
2010-12-29 21:59:38 +00:00
-> Compiler b c
require identifier = requireA identifier . arr . uncurry
2010-12-25 17:15:44 +00:00
2011-01-18 22:58:29 +00:00
-- | Arrow-based variant of 'require'
--
requireA :: (Binary a, Typeable a, Writable a)
2011-05-24 09:58:13 +00:00
=> Identifier a
2011-01-18 22:58:29 +00:00
-> Compiler (b, a) c
-> Compiler b c
requireA identifier = (id &&& require_ identifier >>>)
-- | Variant of 'requireAll' which drops the current value
--
requireAll_ :: (Binary a, Typeable a, Writable a)
2011-05-24 08:12:10 +00:00
=> Pattern a
-> Compiler b [a]
requireAll_ pattern = fromDependencies (const getDeps) >>> fromJob requireAll_'
where
2011-05-24 09:58:13 +00:00
getDeps = map castIdentifier . filterMatches pattern . map castIdentifier
requireAll_' = const $ CompilerM $ do
deps <- getDeps . compilerUniverse <$> ask
mapM (unCompilerM . getDependency) deps
2011-01-18 22:58:29 +00:00
2010-12-29 14:33:22 +00:00
-- | Require a number of targets. Using this function ensures automatic handling
-- of dependencies
--
requireAll :: (Binary a, Typeable a, Writable a)
2011-05-24 08:12:10 +00:00
=> Pattern a
2010-12-30 09:02:25 +00:00
-> (b -> [a] -> c)
-> Compiler b c
requireAll pattern = requireAllA pattern . arr . uncurry
-- | Arrow-based variant of 'requireAll'
2011-01-18 22:58:29 +00:00
--
requireAllA :: (Binary a, Typeable a, Writable a)
2011-05-24 08:12:10 +00:00
=> Pattern a
2011-01-18 22:58:29 +00:00
-> Compiler (b, [a]) c
-> Compiler b c
requireAllA pattern = (id &&& requireAll_ pattern >>>)
2011-01-18 22:58:29 +00:00
cached :: (Binary a, Typeable a, Writable a)
=> String
-> Compiler Resource a
-> Compiler Resource a
cached name (Compiler d j) = Compiler d $ const $ CompilerM $ do
2011-02-21 12:15:11 +00:00
logger <- compilerLogger <$> ask
2011-05-24 09:58:13 +00:00
identifier <- castIdentifier . compilerIdentifier <$> ask
store <- compilerStore <$> ask
2010-12-31 14:15:35 +00:00
modified <- compilerResourceModified <$> ask
progName <- liftIO getProgName
2011-02-21 12:15:11 +00:00
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
2011-05-17 08:57:37 +00:00
case v of Found v' -> return v'
_ -> throwError (error' progName)
where
error' progName =
"Hakyll.Core.Compiler.cached: Cache corrupt! " ++
"Try running: " ++ progName ++ " clean"
2011-01-17 21:43:44 +00:00
-- | Create an unsafe compiler from a function in IO
--
unsafeCompiler :: (a -> IO b) -- ^ Function to lift
-> Compiler a b -- ^ Resulting compiler
unsafeCompiler f = fromJob $ CompilerM . liftIO . f
2011-02-09 12:02:28 +00:00
-- | Compiler for debugging purposes
--
traceShowCompiler :: Show a => Compiler a a
traceShowCompiler = fromJob $ \x -> CompilerM $ do
logger <- compilerLogger <$> ask
report logger $ show x
return x
2011-02-09 12:02:28 +00:00
-- | Map over a compiler
--
mapCompiler :: Compiler a b
-> Compiler [a] [b]
mapCompiler (Compiler d j) = Compiler d $ mapM j
2011-02-21 12:02:35 +00:00
-- | Log and time a compiler
--
timedCompiler :: String -- ^ Message
-> Compiler a b -- ^ Compiler to time
-> Compiler a b -- ^ Resulting compiler
timedCompiler msg (Compiler d j) = Compiler d $ \x -> CompilerM $ do
logger <- compilerLogger <$> ask
timed logger msg $ unCompilerM $ j x
2011-02-25 13:36:34 +00:00
2012-02-13 20:44:38 +00:00
-- | Choose a compiler by identifier
2011-02-25 13:36:34 +00:00
--
2012-02-13 20:44:38 +00:00
-- For example, assume that most content files need to be compiled
-- normally, but a select few need an extra step in the pipeline:
2011-02-25 13:36:34 +00:00
--
2012-02-13 21:30:48 +00:00
-- > compile $ pageCompiler >>> byPattern id
-- > [ ("projects.md", addProjectListCompiler)
-- > , ("sitemap.md", addSiteMapCompiler)
-- > ]
2011-02-25 13:36:34 +00:00
--
2012-02-13 21:30:48 +00:00
byPattern :: Compiler a b -- ^ Default compiler
-> [(Pattern (), Compiler a b)] -- ^ Choices
-> Compiler a b -- ^ Resulting compiler
byPattern defaultCompiler choices = Compiler deps job
2011-02-25 13:36:34 +00:00
where
-- Lookup the compiler, give an error when it is not found
2012-02-13 21:30:48 +00:00
lookup' identifier = maybe defaultCompiler snd $
find (\(p, _) -> matches p identifier) choices
2011-02-25 13:36:34 +00:00
-- Collect the dependencies of the choice
deps = do
2012-02-13 20:44:38 +00:00
identifier <- castIdentifier . dependencyIdentifier <$> ask
2011-02-25 13:36:34 +00:00
compilerDependencies $ lookup' identifier
-- Collect the job of the choice
job x = CompilerM $ do
2012-02-13 20:44:38 +00:00
identifier <- castIdentifier . compilerIdentifier <$> ask
2011-02-25 13:36:34 +00:00
unCompilerM $ compilerJob (lookup' identifier) x
2012-02-13 20:44:38 +00:00
-- | Choose a compiler by extension
--
-- Example:
--
-- > match "css/*" $ do
-- > route $ setExtension "css"
-- > compile $ byExtension (error "Not a (S)CSS file")
-- > [ (".css", compressCssCompiler)
-- > , (".scss", sass)
-- > ]
--
-- This piece of code will select the @compressCssCompiler@ for @.css@ files,
-- and the @sass@ compiler (defined elsewhere) for @.scss@ files.
--
byExtension :: Compiler a b -- ^ Default compiler
-> [(String, Compiler a b)] -- ^ Choices
-> Compiler a b -- ^ Resulting compiler
2012-02-13 21:30:48 +00:00
byExtension defaultCompiler = byPattern defaultCompiler . map (first extPattern)
where
extPattern c = predicate $ (== c) . takeExtension . toFilePath