{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE StrictData #-}
module Headroom.Template
(
Template(..)
, emptyTemplate
, TemplateError(..)
)
where
import Data.String.Interpolate ( iii )
import Headroom.Types ( fromHeadroomError
, toHeadroomError
)
import Headroom.Variables.Types ( Variables(..) )
import RIO
import qualified RIO.Text as T
class Template a where
templateExtensions :: NonEmpty Text
parseTemplate :: MonadThrow m
=> Maybe Text
-> Text
-> m a
renderTemplate :: MonadThrow m
=> Variables
-> a
-> m Text
rawTemplate :: a
-> Text
emptyTemplate :: (MonadThrow m, Template a) => m a
emptyTemplate :: m a
emptyTemplate = Maybe Text -> Text -> m a
forall a (m :: * -> *).
(Template a, MonadThrow m) =>
Maybe Text -> Text -> m a
parseTemplate Maybe Text
forall a. Maybe a
Nothing Text
T.empty
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' = \case
MissingVariables Text
name [Text]
variables -> [iii|
Missing variables for #{name}: #{variables}
|]
ParseError Text
msg -> [iii|
Error parsing template: #{msg}
|]