summaryrefslogtreecommitdiff
path: root/src/Hakyll/Core/Routes.hs
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2012-11-12 16:10:06 +0100
committerJasper Van der Jeugt <m@jaspervdj.be>2012-11-12 16:10:06 +0100
commit760b4344377c81922ce5ab4ba05a41f88f45165d (patch)
treea2b7f45c61938879e4badce363f03c5abf85ae66 /src/Hakyll/Core/Routes.hs
parentc7d3c60c54926b54847bfc691e27f24dc644dd65 (diff)
downloadhakyll-760b4344377c81922ce5ab4ba05a41f88f45165d.tar.gz
WIP
Diffstat (limited to 'src/Hakyll/Core/Routes.hs')
-rw-r--r--src/Hakyll/Core/Routes.hs40
1 files changed, 28 insertions, 12 deletions
diff --git a/src/Hakyll/Core/Routes.hs b/src/Hakyll/Core/Routes.hs
index 25e3a14..63e32e7 100644
--- a/src/Hakyll/Core/Routes.hs
+++ b/src/Hakyll/Core/Routes.hs
@@ -1,3 +1,4 @@
+--------------------------------------------------------------------------------
-- | Once a target is compiled, the user usually wants to save it to the disk.
-- This is where the 'Routes' type comes in; it determines where a certain
-- target should be written.
@@ -24,7 +25,6 @@
-- not appear in your site directory.
--
-- * If an item matches multiple routes, the first rule will be chosen.
---
{-# LANGUAGE Rank2Types #-}
module Hakyll.Core.Routes
( Routes
@@ -38,33 +38,44 @@ module Hakyll.Core.Routes
, composeRoutes
) where
+
+--------------------------------------------------------------------------------
import Data.Monoid (Monoid, mempty, mappend)
import Control.Monad (mplus)
import System.FilePath (replaceExtension)
+
+--------------------------------------------------------------------------------
import Hakyll.Core.Identifier
import Hakyll.Core.Identifier.Pattern
import Hakyll.Core.Util.String
+
+--------------------------------------------------------------------------------
-- | Type used for a route
---
newtype Routes = Routes {unRoutes :: forall a. Identifier a -> Maybe FilePath}
+
+--------------------------------------------------------------------------------
instance Monoid Routes where
mempty = Routes $ const Nothing
mappend (Routes f) (Routes g) = Routes $ \id' -> f id' `mplus` g id'
+
+--------------------------------------------------------------------------------
-- | Apply a route to an identifier
---
runRoutes :: Routes -> Identifier a -> Maybe FilePath
runRoutes = unRoutes
+
+--------------------------------------------------------------------------------
-- | A route that uses the identifier as filepath. For example, the target with
-- ID @foo\/bar@ will be written to the file @foo\/bar@.
---
idRoute :: Routes
idRoute = Routes $ Just . toFilePath
+
+--------------------------------------------------------------------------------
-- | Set (or replace) the extension of a route.
--
-- Example:
@@ -82,29 +93,34 @@ idRoute = Routes $ Just . toFilePath
-- Result:
--
-- > Just "posts/the-art-of-trolling.html"
---
setExtension :: String -> Routes
-setExtension extension = Routes $ fmap (`replaceExtension` extension)
- . unRoutes idRoute
+setExtension extension = Routes $
+ fmap (`replaceExtension` extension) . unRoutes idRoute
+
+--------------------------------------------------------------------------------
-- | Apply the route if the identifier matches the given pattern, fail
-- otherwise
---
matchRoute :: Pattern a -> Routes -> Routes
matchRoute pattern (Routes route) = Routes $ \id' ->
if matches pattern (castIdentifier id') then route id' else Nothing
+
+--------------------------------------------------------------------------------
-- | Create a custom route. This should almost always be used with
-- 'matchRoute'
---
customRoute :: (Identifier a -> FilePath) -> Routes
customRoute f = Routes $ Just . f . castIdentifier
+
+--------------------------------------------------------------------------------
-- | A route that always gives the same result. Obviously, you should only use
-- this for a single compilation rule.
constRoute :: FilePath -> Routes
constRoute = customRoute . const
+
+--------------------------------------------------------------------------------
-- | Create a gsub route
--
-- Example:
@@ -114,13 +130,14 @@ constRoute = customRoute . const
-- Result:
--
-- > Just "tags/bar.xml"
---
gsubRoute :: String -- ^ Pattern
-> (String -> String) -- ^ Replacement
-> Routes -- ^ Resulting route
gsubRoute pattern replacement = customRoute $
replaceAll pattern replacement . toFilePath
+
+--------------------------------------------------------------------------------
-- | Compose routes so that @f `composeRoutes` g@ is more or less equivalent
-- with @f >>> g@.
--
@@ -134,10 +151,9 @@ gsubRoute pattern replacement = customRoute $
-- > Just "tags/bar.xml"
--
-- If the first route given fails, Hakyll will not apply the second route.
---
composeRoutes :: Routes -- ^ First route to apply
-> Routes -- ^ Second route to apply
-> Routes -- ^ Resulting route
composeRoutes (Routes f) (Routes g) = Routes $ \i -> do
p <- f i
- g $ parseIdentifier p
+ g $ fromFilePath p