module WWWStaticusPlugins
( staticusPluginsDefault
,staticusPluginInit
,staticusPluginCfg
,staticusPluginCopy
,staticusPluginPandoc
,staticusPluginFill
,staticusPluginWrite
,staticusPluginCards
) where
import WWWStaticus
import qualified Data.Map.Strict as M
import qualified Data.Text as T
import System.Directory
import Control.Monad
import Data.Maybe
import Data.Either
import Data.List
import Data.List.Split
import Data.List.Utils
import Data.Tuple.Extra
import Text.Pandoc
import Text.Regex
--
-- PLUGIN IDEAS
--
-- timestamp plugin/ do not refresh if md did not change? dir timestamp?
-- but check if depends on upstream stuff as git
--
-- super `gallery and everythin` plugin, just throw images,videos,
-- zips,tars,source files,mds etc inside a folder-> gen page!
--
-- flexible layout, main pic, secondary pics, multiple templates 1 2 3
--
-- scale images
--
-- asciinema, git, videos (generate both from single one)
--
-- contact form? (use nginx log? save post request??)
--
-- pdf plugin
--
-- autotranslate/ multilang
--
-- |little helper to get values out of a map easily
-- error if not found.
par k m = case M.lookup k m of
Just x -> x
Nothing -> error $ "key not found: "++k
-- |little helper to get values out of a map easily
-- defaulting to empty string.
par' k m = case M.lookup k m of
Just x -> x
Nothing -> ""
-- |A default set of plugins that you can use to kickstart your page
-- Use now, Adapt later.
staticusPluginsDefault::[StaticusPlugin]
staticusPluginsDefault=[ staticusPluginInit
,staticusPluginCfg
,staticusPluginCopy [".jpg",".png",".zip",".css",".js",".ico",".mp4",".ogv",".hs",".glade"]
,staticusPluginCards
,staticusPluginPandoc
,staticusPluginFill
,staticusPluginWrite
]
-- |Creates target directory and sets basic params in map:
-- TODO: cleanup!
staticusPluginInit::StaticusPlugin
staticusPluginInit = StaticusPlugin "init" id runIO
where runIO m =
do putStrLn $ "processing: " ++ par "path" m ++ " ..."
when (not isHome) (createDirectory outdir)
c <- getDirList (par "path" m)
t <- getDirList (par "dir_in" m)
let menutop= concat $ map (\x->"
=1 && brc!!0==x then " active" else "")++"\">"++x++"") (menu t)
let submenu= if isHome then "" else concat $ map (\x->""++cln x++"") (menu c)
let breadcrumbs=concat $ map (\(x,d)->""++(if d==0 then "" else "")++cln x++(if d==0 then "" else "")++"") (zip ("home":brc) [brcl,brcl-1..])
md <- readFile $ par "path" m++"/"++"index.md"
tmpl <- readFile $ par "dir_in" m++"/"++"template.html"
return $ M.union (M.fromList [ ("outdir",outdir)
,("index.md",md)
,("template.html",tmpl)
,("menutop",menutop)
,("submenu",submenu)
,("breadcrumbs",if isHome then "" else breadcrumbs)
,("title",if null brc then "Home" else cln $ last brc)
]) m
where outdir = par "dir_out" m ++ "/" ++ intercalate "/" brc
htmlroot_dir = htmlroot ++ "/" ++ intercalate "/" brc
htmlroot = par "html_root" m
brc = remUnder $ splitOn "/" (drop (length (par "dir_in" m)) (par "path" m))
brcl = length brc
remUnder = filter (not.null) . map (dropWhile(=='_').dropWhile(/='_'))
menu = remUnder . filter (not . isPrefixOf "00_") . map (last.splitOn "/") . sortBy (flip compare)
isHome = par "path" m==par "dir_in" m
cln x = replace "-" " " x
-- |This plugin will simply copy files of given extension from source
-- to the target directory. give it a list of file extensions.
-- example [".png",".zip",".css"]
staticusPluginCopy::[String]->StaticusPlugin
staticusPluginCopy ext = StaticusPlugin "copy by extension" id runIO
where runIO m = do
let tst x=or $ map ($x) (map isSuffixOf ext)
dl <- filter tst <$> listDirectory (par "path" m)
mapM_ (\x->copyFile (par "path" m++"/"++x) (par "outdir" m++"/"++x)) dl
return m
-- |extracts config lines (###>>>) from 'index.md'
staticusPluginCfg::StaticusPlugin
staticusPluginCfg = StaticusPlugin "extract config lines" run return
where run m = M.union (M.fromList (("index.md",indexmd):conf)) m
where indexmd=unlines . filter (not.isPrefixOf "###>>>") . lines $ par "index.md" m
conf= map (first head.second (unwords.tail).dupe.words) . filter (isPrefixOf "###>>>") . lines $ par "index.md" m
-- |pipes 'index.md' value through pandoc and saves in 'content'
staticusPluginPandoc::StaticusPlugin
staticusPluginPandoc = StaticusPlugin "pandoc" run return
where run m = let f = runPure $ do doc <- readMarkdown def{readerExtensions=(enableExtension Ext_raw_html pandocExtensions )} $ T.pack (par "index.md" m)
writeHtml5String def doc
in M.union (M.fromList [("content",T.unpack (fromRight (T.pack "err") f))]) m
-- |Plugin for filling the 'template.html' value with 'content', 'menu',
-- etc and storing in 'final'
staticusPluginFill::StaticusPlugin
staticusPluginFill = StaticusPlugin "fill template" run return
where run m = M.union (M.fromList [("final",
replace "###BREADCRUMBS###" (par "breadcrumbs" m) $
replace "###SUBMENU###" (par "submenu" m) $
replace "###MENU###" (par "menutop" m) $
replace "###CONTENT###" (par "content" m) $
replace "###ROOT###" (par "html_root" m) $
replace "###TITLE###" (t (par' "###>>>TITLE" m,par "title" m)) $
replace "###DESCRIPTION###" (par' "###>>>DSC" m) $
replace "###KEYWORDS###" (par' "###>>>KWD" m) $
(par "template.html" m))]) m
t (a,b) = if a=="" then b else a
-- |write final index.html file
staticusPluginWrite::StaticusPlugin
staticusPluginWrite = StaticusPlugin "writer" id runIO
where runIO m = do
writeFile ((par "outdir" m)++"/index.html") (par "final" m)
return m
-- |simple bootstrap cards
staticusPluginCards::StaticusPlugin
staticusPluginCards = StaticusPlugin "bootstrap cards" run return
where run m = M.union (M.fromList[("index.md",makeCards $ par "index.md" m)]) m
makeCards x = concat $ evr2 $ splitRegex (mkRegex "^\\{BEGIN:CARD\\}.*$|^\\{END:CARD\\}.*$") x
evr2 (x:y:xs) = x:createCard y:evr2 xs
evr2 x = x
createCard v = let (_:x:y:z:_:xs)=lines v in replace "###IMG###" x
$ replace "###TITLE###" y
$ replace "###FOOTER###" z -- (z++"
"++a)
$ replace "###TEXT###" (unlines $ map spans xs) tmpl
tmpl =""
++"
"
++"

"
++"
"
++"
###TITLE###
"
++"
"
++"###TEXT###"
++"
"
++"
"
++""
++"
"
spans ('-':vv)=let (x:xs)=words vv in ""++unwords xs++""
spans xx = xx