Skip to content

Commit

Permalink
use cabal for build. clean up type signatures and remove unused code
Browse files Browse the repository at this point in the history
  • Loading branch information
irv committed Feb 23, 2014
1 parent 53970de commit f016d96
Show file tree
Hide file tree
Showing 3 changed files with 78 additions and 38 deletions.
2 changes: 2 additions & 0 deletions Setup.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
import Distribution.Simple
main = defaultMain
54 changes: 16 additions & 38 deletions src/site.hs
Original file line number Diff line number Diff line change
@@ -1,33 +1,29 @@
{-# LANGUAGE OverloadedStrings #-}
import Data.FileStore hiding (create)
import Prelude hiding (id)
import Control.Category (id)
import Hakyll
import Text.Blaze.Html.Renderer.String (renderHtml)
import Text.Blaze.Html5 ((!),toValue)
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as A
import Data.Monoid (mempty, mconcat, mempty, mappend,(<>))
import Data.List (elemIndex, intercalate)
import Data.Monoid (mconcat, mappend,(<>))
import Data.List (elemIndex)
import Data.Maybe (fromMaybe)
import System.FilePath (combine, dropExtension, takeFileName)
import Text.Pandoc (bottomUp, def, Pandoc, writeHtmlString, readMarkdown, Block(Para), Inline(Link))
import Text.Pandoc.Options
import qualified Data.Map as M
import Control.Applicative ((<$>))
import Data.Algorithm.DiffOutput
import Data.Algorithm.Diff hiding(getDiff)
import Control.Monad(foldM,forM_,liftM)
import Control.Monad.Trans (liftIO)
import Control.Monad(forM_)

fileStore :: FileStore
fileStore = gitFileStore "articles"

--getRevisionList :: Compiler [(Revision, Revision)]
getRevisionList :: Compiler [(Revision, Revision)]
getRevisionList = do
path <- toFilePath <$> getUnderlying
unsafeCompiler $ getRevisions $ takeFileName path


getDiff :: FilePath -> [(Revision, Revision)] -> IO [[Diff [String]]]
getDiff page = mapM ( getFileDiff (takeFileName page) )

--renderDiff :: [Diff, [String]] -> String
Expand All @@ -46,34 +42,30 @@ renderDiff d = return (ppDiff d)
-- Second -> "\n"
-- otherwise -> ""

--getFileDiff :: FilePath -> (Revision, Revision) -> IO [Diff, [String]]
getFileDiff :: FilePath -> (Revision, Revision) -> IO [Diff [String]]
getFileDiff f (a,b) = diff fileStore f (Just $ revId b) (Just $ revId a)

getRevisions :: FilePath -> IO [(Revision, Revision)]
getRevisions f = do
revList <- history fileStore [f] (TimeRange Nothing Nothing) Nothing
return $ makePairList revList
-- makePairList [1..4] => [(1,2),(2,3),(3,4)]
-- eg. makePairList [1..4] == [(1,2),(2,3),(3,4)]
where makePairList xs = [(y, x) | x <- xs, y <- xs, y == getListPrev x (reverse xs), x /= y]

getListPrev :: Eq a => a -> [a] -> a
getListPrev i l = l !! checkBounds (fromMaybe 0 (i `elemIndex` l) +1 )
where checkBounds x | x > length l -1 = length l-1 | otherwise = x

--constructDiff :: String -> [[Diff, [String]]] -> Compiler (Item String)
constructDiff :: String -> [[Diff [String]]] -> Compiler (Item String)

constructDiff i d = makeItem i
>>= loadAndApplyTemplate "templates/diff.html" (field "diff" (\_ -> diff' d) <> commonContext)
>>= loadAndApplyTemplate "templates/default.html" commonContext
>>= relativizeUrls
where diff' [] = return []
diff' x = renderDiff $ head x

applyDiffMarkup :: undefined
applyDiffMarkup = undefined

-- makeRevisionCompiler ::
-- Compiler (Page String)
-- (Identifier (Page String), Compiler () (Page String))
makeRevisionCompiler :: Compiler (Item String)
makeRevisionCompiler = do
path <- toFilePath <$> getUnderlying
revisionList <- getRevisionList
Expand All @@ -90,7 +82,7 @@ makeRevisionCompiler = do
routePage :: Routes
routePage = customRoute fileToDirectory

--fileToDirectory :: Identifier a -> FilePath
fileToDirectory :: Identifier -> FilePath
fileToDirectory = flip combine "index.html" . dropExtension . toFilePath

addRevisionList :: Compiler String
Expand All @@ -109,8 +101,6 @@ renderRevision rl = renderHtml $ H.tr $ do
compressorCompiler :: String -> Item String -> Compiler (Item String)
compressorCompiler t = withItemBody(unixFilter "yui-compressor" ["--type", t])

--makeDiffIdentifier a b = constRoute "diffs" `composeRoutes`

main :: IO ()
main = hakyll $ do
let static = route idRoute >> compile copyFileCompiler
Expand Down Expand Up @@ -174,8 +164,8 @@ main = hakyll $ do
let ids' = map (fromFilePath) ids
mapM buildDiffs ids'

forM_ diffs $ \diff ->
create (createDiffIdentifiers diff) $ do
forM_ diffs $ \d ->
create (createDiffIdentifiers d) $ do
route idRoute
compile $ do
path <- toFilePath <$> getUnderlying
Expand All @@ -200,7 +190,7 @@ main = hakyll $ do
<> commonContext)
>>= relativizeUrls

--buildDiffs :: Identifier -> IO (Identifier,[(Revision, Revision)])
buildDiffs :: Identifier -> IO (M.Map Identifier [(Revision, Revision)])
buildDiffs id' = do
revs <- getRevisions $ toFilePath id'
--return $ (id', revs)
Expand All @@ -213,19 +203,6 @@ createDiffIdentifiers diffs = map fromFilePath (fp diffs)
f i (a,b) = i ++ "/" ++ revId a ++ "_" ++ revId b ++ ".html"
fp = M.foldrWithKey (\k x ks-> ks ++ map (f ((combine "articles") $ dropExtension (toFilePath k))) x) []

-- Pandoc options
--options :: WriterOptions
options = def{ writerTableOfContents = True,
writerTemplate = "$if(toc)$\n$toc$\n$endif$\n$body$",
writerWrapText = True,
writerColumns = 72,
writerTabStop = 4,
writerStandalone = True,
writerSectionDivs = True,
writerHtml5 = True,
writerReferenceLinks = False

}
commonContext :: Context String
commonContext = mconcat
[ dateField "date" "%B %e, %Y"
Expand All @@ -237,6 +214,7 @@ commonContext = mconcat
return $ fromMaybe "" metadata
, defaultContext
]

contentCtx :: Tags -> Context String
contentCtx tags = mconcat
[ tagsField "tags" tags
Expand Down
60 changes: 60 additions & 0 deletions whistlepig.cabal
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
-- Initial whistlepig.cabal generated by cabal init. For further
-- documentation, see http://haskell.org/cabal/users-guide/

-- The name of the package.
name: whistlepig

-- The package version. See the Haskell package versioning policy (PVP)
-- for standards guiding when and how versions should be incremented.
-- http://www.haskell.org/haskellwiki/Package_versioning_policy
-- PVP summary: +-+------- breaking API changes
-- | | +----- non-breaking API additions
-- | | | +--- code changes with no API change
version: 0.1.0.0

-- A short (one-line) description of the package.
synopsis: My website, a static site generated using the Hakyll framework

-- A longer description of the package.
-- description:

-- URL for the project homepage or repository.
homepage: https://github.com/irv/Whistlepig

-- The license under which the package is released.
license: BSD3

-- The file containing the license text.
license-file: LICENSE

-- The package author(s).
author: Andy Irving

-- An email address to which users can send suggestions, bug reports, and
-- patches.
maintainer: [email protected]

-- A copyright notice.
-- copyright:

category: Web

build-type: Simple

-- Constraint on the version of Cabal needed to build this package.
cabal-version: >=1.8


executable whistlepig
-- .hs or .lhs file containing the Main module.
-- main-is:

-- Modules included in this executable, other than Main.
-- other-modules:

-- Other library packages from which modules are imported.
build-depends: base ==4.6.*, hakyll >=4.4.*

-- Directories containing source files.
hs-source-dirs: src

0 comments on commit f016d96

Please sign in to comment.