{-# LANGUAGE OverloadedStrings #-}

import           Control.Applicative (empty)
import qualified Data.Text           as T
import           Hakyll              ((.&&.))
import           Hakyll              (Compiler, Configuration (..),
                                      Context (Context),
                                      ContextField (ListField), Identifier,
                                      Item, MonadMetadata, TmpFile (TmpFile))
import qualified Hakyll              as H
import qualified System.FilePath     as FilePath (replaceExtension,
                                                  takeDirectory)
import qualified System.Process      as Process (readCreateProcess, shell,
                                                 system)
import qualified Text.Pandoc         as Pandoc

main :: IO ()
main = H.hakyllWith configuration $ do

  -- Static files
  H.match "assets/**" $ do
    H.route H.idRoute
    H.compile H.copyFileCompiler

  H.match "css/**.hs" $ do
    H.route . H.customRoute $ const "style.css"
    H.compile $ do
      H.unsafeCompiler (Process.readCreateProcess (Process.shell "cd css && runghc Style.hs") "")
        >>= H.makeItem

  H.match "cv/**" $ H.version "html" $ do
    H.route $ H.setExtension "html"
    let context =
          metadataListField `mappend`
          H.defaultContext
    H.compile $ H.pandocCompiler
      >>= H.loadAndApplyTemplate "templates/resume.html" context
      >>= H.relativizeUrls

  H.match "cv/**" $ H.version "tex" $ do
    H.route $ H.setExtension "tex"
    let context =
          metadataListField `mappend`
          H.defaultContext
    H.compile $ H.getResourceBody
      >>= H.readPandoc
      >>= writeLaTeX
      >>= H.loadAndApplyTemplate "templates/resume.tex" context

  H.match "project/**" $ do
    H.route $ H.setExtension "html"
    let context =
          metadataListField `mappend`
          H.defaultContext
    H.compile $ H.pandocCompiler
      >>= H.loadAndApplyTemplate "templates/project.html" context
      >>= H.relativizeUrls

  H.match "index.html" $ do
    H.route H.idRoute
    let layoutContext =
          H.constField "isResume" "true" `mappend`
          H.defaultContext
    let context =
          H.listField "experience" H.defaultContext (H.loadAll ("cv/experience/*" .&&. H.hasVersion "html")) `mappend`
          H.listField "education" H.defaultContext (H.loadAll ("cv/education/*" .&&. H.hasVersion "html")) `mappend`
          H.listField "skills" H.defaultContext (H.loadAll ("cv/skill/*" .&&. H.hasVersion "html")) `mappend`
          H.listField "hobbies" H.defaultContext (H.loadAll ("cv/hobby/*" .&&. H.hasVersion "html")) `mappend`
          H.defaultContext
    H.compile $
      H.getResourceBody
        >>= H.applyAsTemplate context
        >>= H.loadAndApplyTemplate "templates/layout.html" layoutContext
        >>= H.relativizeUrls

  H.match "projects.html" $ do
    H.route H.idRoute
    let layoutContext =
          H.constField "isProjects" "true" `mappend`
          H.defaultContext
    let context =
          H.listField "projects" H.defaultContext (H.loadAll "project/*") `mappend`
          H.defaultContext
    H.compile $
      H.getResourceBody
        >>= H.applyAsTemplate context
        >>= H.loadAndApplyTemplate "templates/layout.html" layoutContext
        >>= H.relativizeUrls

  H.match "cv.tex" $ do
    H.route $ H.setExtension ".pdf"
    let context =
          H.listField "experience" H.defaultContext (H.loadAll ("cv/experience/*" .&&. H.hasVersion "tex")) `mappend`
          H.listField "education" H.defaultContext (H.loadAll ("cv/education/*" .&&. H.hasVersion "tex")) `mappend`
          H.listField "skills" H.defaultContext (H.loadAll ("cv/skill/*" .&&. H.hasVersion "tex")) `mappend`
          H.listField "hobbies" H.defaultContext (H.loadAll ("cv/hobby/*" .&&. H.hasVersion "tex")) `mappend`
          H.defaultContext
    H.compile $
      H.getResourceBody
        >>= H.applyAsTemplate context
        >>= H.readPandoc
        >>= writeLaTeX
        >>= H.loadAndApplyTemplate "templates/layout.tex" context
        >>= generatePdf

  H.match "templates/**" $
    H.compile H.templateBodyCompiler

writeLaTeX :: Item Pandoc.Pandoc -> Compiler (Item String)
writeLaTeX = traverse $ \pandoc ->
  case Pandoc.runPure (Pandoc.writeLaTeX Pandoc.def pandoc) of
    Left err -> fail $ show err
    Right x  -> return (T.unpack x)

configuration :: Configuration
configuration = H.defaultConfiguration
  { destinationDirectory = "public"
  }

metadataListField :: Context a
metadataListField = Context $ \k _ i -> do
   values <- getMetadataListField (H.itemIdentifier i) k
   case values of
     Just vs -> do
       listItems <- mapM H.makeItem vs
       return $ ListField (H.field "item" (return . H.itemBody)) listItems
     Nothing ->
       empty

getMetadataListField :: MonadMetadata m => Identifier -> String -> m (Maybe [String])
getMetadataListField identifier key = do
   metadata <- H.getMetadata identifier
   return $ H.lookupStringList key metadata

generatePdf :: Item String -> Compiler (Item TmpFile)
generatePdf item = do
    TmpFile texPath <- H.newTmpFile "file.tex"
    let tmpDir  = FilePath.takeDirectory texPath
        pdfPath = FilePath.replaceExtension texPath "pdf"

    H.unsafeCompiler $ do
        writeFile texPath $ H.itemBody item
        _ <- Process.system $ unwords ["cd resume", "&&", "pdflatex", "-halt-on-error",
            "-output-directory", "../" ++ tmpDir, "../" ++ texPath, ">/dev/null", "2>&1"]
        _ <- Process.system $ unwords ["cd resume", "&&", "pdflatex", "-halt-on-error",
            "-output-directory", "../" ++ tmpDir, "../" ++ texPath, ">/dev/null", "2>&1"]
        return ()

    H.makeItem $ TmpFile pdfPath