diff options
-rw-r--r-- | src/Hakyll/Core/Compiler.hs | 10 | ||||
-rw-r--r-- | web/site.hs | 40 |
2 files changed, 46 insertions, 4 deletions
diff --git a/src/Hakyll/Core/Compiler.hs b/src/Hakyll/Core/Compiler.hs index 9a8f923..9fec69b 100644 --- a/src/Hakyll/Core/Compiler.hs +++ b/src/Hakyll/Core/Compiler.hs @@ -4,6 +4,7 @@ module Hakyll.Core.Compiler ( Compiler , getUnderlying + , getUnderlyingExtension , makeItem , getRoute , getResourceBody @@ -31,8 +32,8 @@ import Control.Applicative ((<$>)) import Data.Binary (Binary) import Data.ByteString.Lazy (ByteString) import Data.Typeable (Typeable) -import Prelude hiding (id, (.)) import System.Environment (getProgName) +import System.FilePath (takeExtension) -------------------------------------------------------------------------------- @@ -53,6 +54,13 @@ getUnderlying = compilerUnderlying <$> compilerAsk -------------------------------------------------------------------------------- +-- | Get the extension of the underlying identifier. Returns something like +-- @".html"@ +getUnderlyingExtension :: Compiler String +getUnderlyingExtension = takeExtension . toFilePath <$> getUnderlying + + +-------------------------------------------------------------------------------- makeItem :: a -> Compiler (Item a) makeItem x = do identifier <- getUnderlying diff --git a/web/site.hs b/web/site.hs index 6130bea..aac6368 100644 --- a/web/site.hs +++ b/web/site.hs @@ -1,8 +1,12 @@ -------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} -import Control.Monad (forM_) -import Data.Monoid (mappend) +import Control.Applicative ((<$>)) +import Control.Arrow (second) +import Control.Monad (forM_) +import Data.List (isPrefixOf) +import Data.Monoid (mappend) import Hakyll +import System.FilePath (dropTrailingPathSeparator, splitPath) import Text.Pandoc @@ -14,7 +18,17 @@ main = hakyllWith config $ do compile compressCssCompiler -- Static directories - forM_ ["images/*", "examples/*", "reference/**"] $ \f -> match f $ do + forM_ ["images/*", "examples/*"] $ \f -> match f $ do + route idRoute + compile copyFileCompiler + + -- Haddock stuff + match "reference/**.html" $ do + route idRoute + compile $ fmap (withUrls hackage) <$> getResourceString + + -- Haddock stuff + match ("reference/**" `mappend` complement "**.html") $ do route idRoute compile copyFileCompiler @@ -69,3 +83,23 @@ config = defaultConfiguration , deployCommand = "rsync --checksum -ave 'ssh -p 2222' \ \_site/* jaspervdj@jaspervdj.be:jaspervdj.be/tmp/hakyll4" } + + +-------------------------------------------------------------------------------- +-- | Turns +-- +-- > /usr/share/doc/ghc/html/libraries/base-4.6.0.0/Data-String.html +-- +-- into +-- +-- > http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-String.html +hackage :: String -> String +hackage url + | "/usr" `isPrefixOf` url = + "http://hackage.haskell.org/packages/archive/" ++ + packageName ++ "/" ++ version' ++ "/doc/html/" ++ baseName + | otherwise = url + where + (packageName, version') = second (drop 1) $ break (== '-') package + (baseName : package : _) = map dropTrailingPathSeparator $ + reverse $ splitPath url |