{-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Type.Plugin where import Bamboo.Helper.Env hiding (body, name) import qualified Bamboo.Model.Album as Album import qualified Bamboo.Model.Video as V import qualified Bamboo.View.Atom.Album as AlbumV () import qualified Bamboo.View.Atom.Video as VV () data PluginType = PhotoAlbum | Video | None deriving (Show, Eq) data Plugin = Plugin { plugin_type :: PluginType , args :: [(String, String)] } deriving (Show, Eq) -- album-plugin -- plugin is simple inline substitution, since markdown handles html natively -- [[ -- plugin: album, -- name: first-album, -- prefix: \d{2}-\d{2}-\d{2} -- ]] plugin_expression = "\n\\[\\[((.|\n)*?)\\]\\]" plugin_id = "plugin" infix_of = flip isInfixOf optimized_match x | "[[".infix_of x = x.match plugin_expression | otherwise = Nothing -- OK.. unless I get drunk again, I won't be able to understand how this works.... parse_plugin x = x.gsub "\n" "".split "," .map (split ":") .inner_map strip .map tuple2.parse_it where parse_it xs = Plugin { plugin_type = xs.at plugin_id, args = xs.reject (fst > (is plugin_id)) } at x xs = case (xs.lookup x) >>= parse_plugin_type of Nothing -> None Just x -> x plugin_types = [PhotoAlbum, Video] parse_plugin_type x = plugin_types.label_by (show_data).lookup (x) match_result x = x.fromJust.snd.first.snd.b2u apply_plugin x = if r.isNothing then return x else sub_it where r = x.optimized_match plugin = r.match_result.parse_plugin sub_it = case plugin.plugin_type of None -> return x PhotoAlbum -> do album <- plugin.args.Album.from_list ^ render_plugin x.sub plugin_expression album .apply_plugin Video -> do video <- plugin.args.V.from_list ^ render_plugin x.sub plugin_expression video .apply_plugin render_plugin x = "\n" ++ x.render_data.show