module Network.Gitit.Initialize ( initializeGititState
                                , recompilePageTemplate
                                , compilePageTemplate
                                , createStaticIfMissing
                                , createRepoIfMissing
                                , createDefaultPages
                                , createTemplateIfMissing )
where
import System.FilePath ((</>), (<.>))
import Data.FileStore
import qualified Data.Map as M
import qualified Data.Set as Set
import Network.Gitit.Util (readFileUTF8)
import Network.Gitit.Types
import Network.Gitit.State
import Network.Gitit.Framework
import Network.Gitit.Plugins
import Network.Gitit.Layout (defaultRenderPage)
import Paths_gitit (getDataFileName)
import Control.Exception (throwIO, try)
import System.Directory (copyFile, createDirectoryIfMissing, doesDirectoryExist, doesFileExist)
import Control.Monad (unless, forM_, liftM)
import Text.Pandoc
import System.Log.Logger (logM, Priority(..))
import qualified Text.StringTemplate as T
initializeGititState :: Config -> IO ()
initializeGititState conf = do
  let userFile' = userFile conf
      pluginModules' = pluginModules conf
  plugins' <- loadPlugins pluginModules'
  userFileExists <- doesFileExist userFile'
  users' <- if userFileExists
               then liftM (M.fromList . read) $ readFileUTF8 userFile'
               else return M.empty
  templ <- compilePageTemplate (templatesDir conf)
  updateGititState $ \s -> s { sessions      = Sessions M.empty
                             , users         = users'
                             , templatesPath = templatesDir conf
                             , renderPage    = defaultRenderPage templ
                             , plugins       = plugins' }
recompilePageTemplate :: IO ()
recompilePageTemplate = do
  tempsDir <- queryGititState templatesPath
  ct <- compilePageTemplate tempsDir
  updateGititState $ \st -> st{renderPage = defaultRenderPage ct}
compilePageTemplate :: FilePath -> IO (T.StringTemplate String)
compilePageTemplate tempsDir = do
  defaultGroup <- getDataFileName ("data" </> "templates") >>= T.directoryGroup
  customExists <- doesDirectoryExist tempsDir
  combinedGroup <-
    if customExists
       
       
       then do customGroup <- T.directoryGroup tempsDir
               return $ T.mergeSTGroups customGroup defaultGroup
       else do logM "gitit" WARNING $ "Custom template directory not found"
               return defaultGroup
  case T.getStringTemplate "page" combinedGroup of
        Just t    -> return t
        Nothing   -> error "Could not get string template"
createTemplateIfMissing :: Config -> IO ()
createTemplateIfMissing conf' = do
  templateExists <- doesDirectoryExist (templatesDir conf')
  unless templateExists $ do
    createDirectoryIfMissing True (templatesDir conf')
    templatePath <- getDataFileName $ "data" </> "templates"
    
    
    
    
    forM_ ["footer.st"] $ \t -> do
      copyFile (templatePath </> t) (templatesDir conf' </> t)
      logM "gitit" WARNING $ "Created " ++ (templatesDir conf' </> t)
createRepoIfMissing :: Config -> IO ()
createRepoIfMissing conf = do
  let fs = filestoreFromConfig conf
  repoExists <- try (initialize fs) >>= \res ->
    case res of
         Right _               -> do
           logM "gitit" WARNING $ "Created repository in " ++ repositoryPath conf
           return False
         Left RepositoryExists -> return True
         Left e                -> throwIO e >> return False
  unless repoExists $ createDefaultPages conf
createDefaultPages :: Config -> IO ()
createDefaultPages conf = do
    let fs = filestoreFromConfig conf
        pt = defaultPageType conf
        toPandoc = readMarkdown
                   def{ readerSmart = True }
        defOpts = def{ writerStandalone = False
                     , writerHTMLMathMethod = JsMath
                              (Just "/js/jsMath/easy/load.js")
                     , writerExtensions = if showLHSBirdTracks conf
                                             then Set.insert
                                                  Ext_literate_haskell
                                                  $ writerExtensions def
                                             else writerExtensions def
                     }
        
        converter = case pt of
                       Markdown  -> id
                       LaTeX     -> writeLaTeX defOpts . toPandoc
                       HTML      -> writeHtmlString defOpts . toPandoc
                       RST       -> writeRST defOpts . toPandoc
                       Textile   -> writeTextile defOpts . toPandoc
                       Org       -> writeOrg defOpts . toPandoc
                       DocBook   -> writeDocbook defOpts . toPandoc
                       MediaWiki -> writeMediaWiki defOpts . toPandoc
    welcomepath <- getDataFileName $ "data" </> "FrontPage" <.> "page"
    welcomecontents <- liftM converter $ readFileUTF8 welcomepath
    helppath <- getDataFileName $ "data" </> "Help" <.> "page"
    helpcontentsInitial <- liftM converter $ readFileUTF8 helppath
    markuppath <- getDataFileName $ "data" </> "markup" <.> show pt
    helpcontentsMarkup <- liftM converter $ readFileUTF8  markuppath
    let helpcontents = helpcontentsInitial ++ "\n\n" ++ helpcontentsMarkup
    usersguidepath <- getDataFileName "README.markdown"
    usersguidecontents <- liftM converter $ readFileUTF8 usersguidepath
    
    let header = "---\nformat: " ++
          show pt ++ (if defaultLHS conf then "+lhs" else "") ++
          "\n...\n\n"
    
    let auth = Author "Gitit" ""
    createIfMissing fs (frontPage conf <.> "page") auth "Default front page"
      $ header ++ welcomecontents
    createIfMissing fs "Help.page" auth "Default help page"
      $ header ++ helpcontents
    createIfMissing fs "Gitit User’s Guide.page" auth "User’s guide (README)"
      $ header ++ usersguidecontents
createIfMissing :: FileStore -> FilePath -> Author -> Description -> String -> IO ()
createIfMissing fs p a comm cont = do
  res <- try $ create fs p a comm cont
  case res of
       Right _ -> logM "gitit" WARNING ("Added " ++ p ++ " to repository")
       Left ResourceExists -> return ()
       Left e              -> throwIO e >> return ()
createStaticIfMissing :: Config -> IO ()
createStaticIfMissing conf = do
  let staticdir = staticDir conf
  staticExists <- doesDirectoryExist staticdir
  unless staticExists $ do
    let cssdir = staticdir </> "css"
    createDirectoryIfMissing True cssdir
    cssDataDir <- getDataFileName $ "data" </> "static" </> "css"
    
    forM_ ["custom.css"] $ \f -> do
      copyFile (cssDataDir </> f) (cssdir </> f)
      logM "gitit" WARNING $ "Created " ++ (cssdir </> f)
    
    logopath <- getDataFileName $ "data" </> "static" </> "img" </> "logo.png"
    createDirectoryIfMissing True $ staticdir </> "img"
    copyFile logopath $ staticdir </> "img" </> "logo.png"
    logM "gitit" WARNING $ "Created " ++ (staticdir </> "img" </> "logo.png")