Skip to content

Instantly share code, notes, and snippets.

@noteed
Created October 21, 2018 23:07
Show Gist options
  • Save noteed/73838ce9d4f4db03e7e75c816f01ecda to your computer and use it in GitHub Desktop.
Save noteed/73838ce9d4f4db03e7e75c816f01ecda to your computer and use it in GitHub Desktop.
Hakyll compiler for inline (embedded in site.hs) content
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.Binary (Binary (..))
import Data.Typeable (Typeable)
import Hakyll.Core.Compiler.Internal (compilerAsk, compilerProvider)
import Hakyll.Core.Provider (resourceFilePath)
import Hakyll
--------------------------------------------------------------------------------
main :: IO ()
main = hakyll $ do
create ["hello.txt"] $ do
route idRoute
compile inlineCompiler
--------------------------------------------------------------------------------
-- | This will copy any file directly by using a system call
newtype InlineContent = InlineContent FilePath
deriving (Binary, Eq, Ord, Show, Typeable)
--------------------------------------------------------------------------------
instance Writable InlineContent where
write dst (Item _ (InlineContent src)) = writeFile dst ("Created inline: " ++ src ++ "\n")
--------------------------------------------------------------------------------
inlineCompiler :: Compiler (Item InlineContent)
inlineCompiler = do
identifier <- getUnderlying
provider <- compilerProvider <$> compilerAsk
makeItem $ InlineContent $ resourceFilePath provider identifier
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment