{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
module Headroom.Template
( Template(..)
, TemplateError(..)
)
where
import Headroom.Types ( fromHeadroomError
, toHeadroomError
)
import Headroom.Variables.Types ( Variables(..) )
import RIO
import qualified RIO.Text as T
class Template t where
templateExtensions :: NonEmpty Text
parseTemplate :: MonadThrow m
=> Maybe Text
-> Text
-> m t
renderTemplate :: MonadThrow m
=> Variables
-> t
-> m Text
rawTemplate :: t
-> Text
data TemplateError
= MissingVariables Text [Text]
| ParseError Text
deriving (TemplateError -> TemplateError -> Bool
(TemplateError -> TemplateError -> Bool)
-> (TemplateError -> TemplateError -> Bool) -> Eq TemplateError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemplateError -> TemplateError -> Bool
$c/= :: TemplateError -> TemplateError -> Bool
== :: TemplateError -> TemplateError -> Bool
$c== :: TemplateError -> TemplateError -> Bool
Eq, Int -> TemplateError -> ShowS
[TemplateError] -> ShowS
TemplateError -> String
(Int -> TemplateError -> ShowS)
-> (TemplateError -> String)
-> ([TemplateError] -> ShowS)
-> Show TemplateError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TemplateError] -> ShowS
$cshowList :: [TemplateError] -> ShowS
show :: TemplateError -> String
$cshow :: TemplateError -> String
showsPrec :: Int -> TemplateError -> ShowS
$cshowsPrec :: Int -> TemplateError -> ShowS
Show, Typeable)
instance Exception TemplateError where
displayException :: TemplateError -> String
displayException = TemplateError -> String
displayException'
toException :: TemplateError -> SomeException
toException = TemplateError -> SomeException
forall e. Exception e => e -> SomeException
toHeadroomError
fromException :: SomeException -> Maybe TemplateError
fromException = SomeException -> Maybe TemplateError
forall e. Exception e => SomeException -> Maybe e
fromHeadroomError
displayException' :: TemplateError -> String
displayException' :: TemplateError -> String
displayException' = Text -> String
T.unpack (Text -> String)
-> (TemplateError -> Text) -> TemplateError -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
MissingVariables Text
name [Text]
variables -> Text -> [Text] -> Text
forall a. Show a => Text -> a -> Text
missingVariables Text
name [Text]
variables
ParseError Text
msg -> Text -> Text
forall a. (Semigroup a, IsString a) => a -> a
parseError Text
msg
where
missingVariables :: Text -> a -> Text
missingVariables Text
name a
variables =
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
"Missing variables for '", Text
name, Text
"': ", String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ a -> String
forall a. Show a => a -> String
show a
variables]
parseError :: a -> a
parseError a
msg = a
"Error parsing template: " a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
msg