Skip to content

Instantly share code, notes, and snippets.

@wenkokke
Last active August 29, 2015 14:07
Show Gist options
  • Save wenkokke/ebeba49c0d08b63ce4d2 to your computer and use it in GitHub Desktop.
Save wenkokke/ebeba49c0d08b63ce4d2 to your computer and use it in GitHub Desktop.
A (probably very unidiomatic) Shake script which renders the last modified Markdown to a PDF using Pandoc/LaTeX.
{-# LANGUAGE DeriveDataTypeable #-}
import Control.Applicative ((<$>))
import Control.Monad (filterM)
import Data.Foldable (or)
import Data.List (isSuffixOf,maximumBy)
import Data.Ord (comparing)
import Data.Traversable (traverse)
import Development.Shake
import Development.Shake.FilePath
import Prelude hiding (or)
import System.Console.CmdArgs
import qualified System.Directory as Dir
-- | Check if the give path is a Markdown file by checking the extension.
isMarkdown :: FilePath -> Bool
isMarkdown file = "markdown" `isSuffixOf` file || "md" `isSuffixOf` file
-- | Get the file in the given directory which was last modified,
-- filtered by an optional filter.
getLastModifiedFileBy :: (FilePath -> Bool) -> FilePath -> IO (Maybe FilePath)
getLastModifiedFileBy predicate directory = do
files <- filterM Dir.doesFileExist
=<< map (directory </>) . filter predicate
<$> Dir.getDirectoryContents directory
if null files
then return Nothing
else do
modificationTimes <- mapM Dir.getModificationTime files
return . Just . fst $
maximumBy (comparing snd) (zip files modificationTimes)
-- | Options to `lastmd`.
data Options = Options
{ bibliography :: Maybe FilePath
, target :: String
, publicDirectory :: FilePath
} deriving (Data, Typeable)
-- | Render the last modified Markdown file to a PDF using Pandoc.
main :: IO ()
main = do
-- Basic configuration
currentDirectory <- Dir.getCurrentDirectory
lastModifiedMarkdownFile <- getLastModifiedFileBy isMarkdown currentDirectory
-- Compute default options
let defaultBibliography = (-<.> "bib") <$> lastModifiedMarkdownFile
defaultBibliographyExists <- or <$> Dir.doesFileExist `traverse` defaultBibliography
let defaultBibliography' =
if defaultBibliographyExists then defaultBibliography else Nothing
defaultTarget = "pdf"
defaultPublicDirectory = currentDirectory </> "Public"
defaultPublicDirectoryExists <- Dir.doesDirectoryExist defaultPublicDirectory
let defaultTargetDirectory =
if defaultPublicDirectoryExists then defaultPublicDirectory else currentDirectory
defaultOptions = Options
{ bibliography = defaultBibliography'
&= typ "FILE"
&= help "An optional bibliography file to pass to Pandoc"
, target = defaultTarget
&= typ "EXTENSION"
&= help "Format to render to"
, publicDirectory = defaultTargetDirectory
&= typ "DIRECTORY"
&= help "Where to place the rendered files"
&= explicit &= name "d" &= name "publicdirectory"
}
&= summary "LastMD v1.0, (c) Pepijn Kokke 2014"
&= program "lastmd"
-- Parse options
opts <- cmdArgs defaultOptions
let
toPublic, fromPublic :: FilePath -> FilePath
toPublic file = publicDirectory opts </> takeFileName file -<.> target opts
fromPublic file = currentDirectory </> takeFileName file -<.> "md"
-- Run Shake
case lastModifiedMarkdownFile of
Nothing -> error ("no markdown files in " ++ currentDirectory)
Just fn -> shake shakeOptions $ do
want [toPublic fn]
publicDirectory opts </> "*" <.> target opts *> \out -> do
let src = fromPublic out
need [src]
() <- case bibliography opts of
Nothing -> cmd "pandoc" "-o" out "-f" "markdown" src
Just bib -> cmd "pandoc" "--bibliography" bib "-o" out "-f" "markdown" src
cmd "open" out
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment