module Hakyll.Shortcode.Service (
Shortcode(..),
ShortcodeTag(ShortcodeTag),
ShortcodeAttribute(YesNo, OneOf, Valid),
expandShortcodes,
missingError
) where
import Hakyll.Shortcode.Validate
import Hakyll.Shortcode.Parser
import Hakyll.Shortcode.Types.YesNo
import Control.Monad (foldM)
import Data.List (intercalate)
import Data.List.Utils (replace)
import Text.ParserCombinators.Parsec
import Text.Regex.Posix
class Shortcode t where
tag :: ShortcodeTag t
attributes :: [ShortcodeAttribute t]
emptycode :: t
embedcode :: t -> String
data ShortcodeTag a = ShortcodeTag
{ unTag :: String
} deriving Show
data ShortcodeAttribute t where
YesNo :: String -> (YesNo -> t -> t) -> ShortcodeAttribute t
OneOf :: String -> [(String, t -> t)] -> ShortcodeAttribute t
Valid :: (Validate a) => String -> (a -> t -> t) -> ShortcodeAttribute t
update :: (Shortcode t) => t -> (String, String) -> Either String t
update x kv = foldM (processKeyVal kv) x attributes
where
processKeyVal :: forall t. (Shortcode t)
=> (String, String) -> t -> ShortcodeAttribute t -> Either String t
processKeyVal (k,v) x (YesNo key f)
| key /= k = Right x
| otherwise = case v of
"yes" -> Right $ f Yes x
"no" -> Right $ f No x
_ -> Left $ typeError (unTag theTag) key v ["\"yes\"", "\"no\""]
where
theTag :: ShortcodeTag t
theTag = tag
processKeyVal (k,v) x (OneOf key cases)
| key /= k = Right x
| otherwise = foo cases
where
foo [] = Left $ typeError (unTag theTag) key v $ map (show . fst) cases
foo ((val,f):cs) = if val /= v
then foo cs
else Right $ f x
theTag :: ShortcodeTag t
theTag = tag
processKeyVal (k,v) x (Valid key f)
| key /= k = Right x
| otherwise = case validate v of
Right z -> return $ f z x
Left er -> Left $ validateError (unTag theTag) k v er
where
theTag :: ShortcodeTag t
theTag = tag
expandShortcodes :: (Shortcode t) => t -> String -> String
expandShortcodes x text = foldr (expandOne x) text matches
where
matches :: [String]
matches = getAllTextMatches $ text =~ (shortcodeRegex x)
expandOne :: (Shortcode t) => t -> String -> String -> String
expandOne x code text = replace code (getReplacement x code) text
shortcodeRegex :: forall t. (Shortcode t) => t -> String
shortcodeRegex x = "<p>\\[[[:blank:]]*" ++ (unTag theTag) ++ "[^]]*]</p>"
where
theTag :: ShortcodeTag t
theTag = tag
getReplacement :: forall t. (Shortcode t) => t -> String -> String
getReplacement x text = case runParser p () "" text of
Left err -> parseError (unTag theTag) $ show err
Right atts -> case foldM update init atts of
Left err -> err
Right result -> embedcode result
where
p :: Parser [(String, String)]
p = shortcodeParser (unTag theTag)
init :: t
init = emptycode
theTag :: ShortcodeTag t
theTag = tag
validateError :: String -> String -> String -> String -> String
validateError tag key badval expect = concat
[ "(Nb. there is an error in this '" ++ tag ++ "' shortcode; "
, "the value '" ++ badval ++ "' for key '" ++ key ++ "' is invalid. "
, expect ++ ")"
]
typeError :: String -> String -> String -> [String] -> String
typeError tag key badval expects = concat
[ "(Nb. there is an error in this '" ++ tag ++ "' shortcode; "
, "the value '" ++ badval ++ "' for key '" ++ key ++ "' was not expected. "
, "Possible values: " ++ (intercalate " " expects) ++ ".)"
]
parseError :: String -> String -> String
parseError tag err = concat
[ "(Nb. there was an error while parsing this '" ++ tag ++ "' tag. "
, err ++ ".)"
]
missingError :: String -> String -> String
missingError tag key = concat
[ "(Nb. there is an error in this '" ++ tag ++ "' shortcode; "
, "you must provide a value for the '" ++ key ++ "' key.)"
]