module SpecUp(invokeTemplateOnSpec) where
import Data.Text (Text)
import Data.ByteString.Char8 (ByteString)
import Data.Yaml (decodeEither', ParseException, prettyPrintParseException)
import Text.Megaparsec.Error (errorBundlePretty)
import Text.Mustache (compileMustacheText, renderMustache)
import qualified Data.Text.Lazy as LazyText
import Data.Either.Extra (mapLeft)
invokeTemplateOnSpec :: Text ->
                        ByteString ->
                        Either String LazyText.Text
invokeTemplateOnSpec :: Text -> ByteString -> Either String Text
invokeTemplateOnSpec Text
templ ByteString
spec =
  Template -> Value -> Text
renderMustache (Template -> Value -> Text)
-> Either String Template -> Either String (Value -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either String Template
compiledTemplate Either String (Value -> Text)
-> Either String Value -> Either String Text
forall a b.
Either String (a -> b) -> Either String a -> Either String b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Either String Value
compiledSpec
  where compiledTemplate :: Either String Template
compiledTemplate = Either (ParseErrorBundle Text Void) Template
-> Either String Template
forall {b}.
Either (ParseErrorBundle Text Void) b -> Either String b
templateCompilationErrorHandler
                           (Either (ParseErrorBundle Text Void) Template
 -> Either String Template)
-> Either (ParseErrorBundle Text Void) Template
-> Either String Template
forall a b. (a -> b) -> a -> b
$ PName -> Text -> Either (ParseErrorBundle Text Void) Template
compileMustacheText PName
"base template" Text
templ
        compiledSpec :: Either String Value
compiledSpec = Either ParseException Value -> Either String Value
forall {b}. Either ParseException b -> Either String b
yamlDecodingErrorHandler
                       (Either ParseException Value -> Either String Value)
-> Either ParseException Value -> Either String Value
forall a b. (a -> b) -> a -> b
$ ByteString -> Either ParseException Value
forall a. FromJSON a => ByteString -> Either ParseException a
decodeEither' ByteString
spec
        yamlDecodingErrorHandler :: Either ParseException b -> Either String b
yamlDecodingErrorHandler = (ParseException -> String)
-> Either ParseException b -> Either String b
forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft
          ( (String
"yaml decoding failed with the following error: " <>)
          (String -> String)
-> (ParseException -> String) -> ParseException -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseException -> String
prettyPrintParseException
          )
        templateCompilationErrorHandler :: Either (ParseErrorBundle Text Void) b -> Either String b
templateCompilationErrorHandler = (ParseErrorBundle Text Void -> String)
-> Either (ParseErrorBundle Text Void) b -> Either String b
forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft
          ( (String
"Texplate compilation failed with the following error: " <>)
          (String -> String)
-> (ParseErrorBundle Text Void -> String)
-> ParseErrorBundle Text Void
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseErrorBundle Text Void -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty
          )