module PostUtils (compilePost, extname, copyFolder, parseFrontMatter) where import CMark (commonmarkToHtml) import Control.Monad (unless) import qualified Data.ByteString as BS import Data.Frontmatter (IResult (Done), parseYamlFrontmatter) import Data.Maybe (fromJust) import Data.Text (pack) import Data.Text.Encoding (decodeUtf8) import Data.Text.Internal (Text) import Data.Yaml (Object) 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 (frontMatter, fileContents) <- parseFrontMatter fp let compiledFileContents = commonmarkToHtml [] fileContents fn = fromJust $ getPostFileName fp t = frontmatter_title frontMatter compiledHtml = postCompiler t compiledFileContents return Post { title = t, location = fp, filename = pack fn, raw = fileContents, raw_html = compiledFileContents, compiled_html = compiledHtml } parseFrontMatter :: FilePath -> IO (FrontMatter, Text) parseFrontMatter fp = do f <- BS.readFile fp case parseYamlFrontmatter f of Done ri fm -> return (fm, decodeUtf8 ri) _ -> error "Parse failure" getPostFileName :: FilePath -> Maybe String getPostFileName fp = case match of Nothing -> Nothing Just (x : xs) -> Just x where match = matchRegex postNameRegex fp 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 ++ "/")