module PostUtils (compilePost, extname, copyFolder) where

import CMark (commonmarkToHtml)
import Control.Monad (unless)
import Data.Maybe (fromJust)
import Data.Text (pack)
import Data.Text.Internal (Text)
import Lucid.Base (Html)
import Noli.Types
import System.Directory (copyFile, createDirectory, doesDirectoryExist, doesFileExist, listDirectory)
import Text.Regex (Regex, matchRegex, mkRegex)

postNameRegex :: Regex
postNameRegex = mkRegex "/?([A-Za-z_]+)\\.md$"

extname :: FilePath -> FilePath
extname = Prelude.reverse . Prelude.takeWhile ('.' /=) . Prelude.reverse

compilePost :: PostTemplate -> FilePath -> IO Post
compilePost postCompiler fp = do
  fileContents <- pack <$> readFile fp
  let compiledFileContents = commonmarkToHtml [] fileContents
      fn = fromJust $ getPostFileName fp
      t = getPostName fn
      compiledHtml = postCompiler (pack t) compiledFileContents
  return
    Post
      { title = pack t,
        location = fp,
        filename = pack fn,
        raw = fileContents,
        raw_html = compiledFileContents,
        compiled_html = compiledHtml
      }

getPostFileName :: FilePath -> Maybe String
getPostFileName fp = case match of
  Nothing -> Nothing
  Just (x : xs) -> Just x
  where
    match = matchRegex postNameRegex fp

getPostName :: String -> String
getPostName fn =
  let repl '_' = ' '
      repl x = x
   in Prelude.map repl fn

copyFolder :: FilePath -> FilePath -> IO ()
copyFolder source destination = do
  destinationExists <- doesDirectoryExist destination
  unless destinationExists $ createDirectory destination
  sourceFiles <- listDirectory source
  Prelude.mapM_ copyFile' sourceFiles
  where
    copyFile' source_file = do
      is_file <- doesFileExist $ source ++ source_file
      if is_file
        then copyFile (source ++ source_file) (destination ++ source_file)
        else copyFolder (source ++ source_file ++ "/") (destination ++ source_file ++ "/")