{-# LANGUAGE TemplateHaskell #-}

module Data.OpenApi.Compare.Report.Html.Template
  ( template,
  )
where

import Control.Monad.Identity
import Data.ByteString (ByteString)
import Data.FileEmbed
import Data.Text (Text)
import qualified Data.Text.Encoding as T
import Text.DocTemplates

template :: Template Text
template :: Template Text
template =
  ([Char] -> Template Text)
-> (Template Text -> Template Text)
-> Either [Char] (Template Text)
-> Template Text
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either [Char] -> Template Text
forall a. HasCallStack => [Char] -> a
error Template Text -> Template Text
forall a. a -> a
id (Either [Char] (Template Text) -> Template Text)
-> (Text -> Either [Char] (Template Text)) -> Text -> Template Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity (Either [Char] (Template Text))
-> Either [Char] (Template Text)
forall a. Identity a -> a
runIdentity (Identity (Either [Char] (Template Text))
 -> Either [Char] (Template Text))
-> (Text -> Identity (Either [Char] (Template Text)))
-> Text
-> Either [Char] (Template Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text -> Identity (Either [Char] (Template Text))
forall (m :: * -> *) a.
(TemplateMonad m, TemplateTarget a) =>
[Char] -> Text -> m (Either [Char] (Template a))
compileTemplate [Char]
"" (Text -> Template Text) -> Text -> Template Text
forall a b. (a -> b) -> a -> b
$
    Text
"<!doctype html>\
    \<html lang=\"en\">\
    \<head>\
    \<style>"
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ByteString -> Text
T.decodeUtf8 ByteString
awsmCss
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</style>\
         \<meta charset=\"utf-8\">\
         \<title></title>\
         \<meta name=\"description\" content=\"\">\
         \<meta name=\"generator\" content=\"CompaREST\" />\
         \<meta name=\"viewport\" content=\"width=device-width, initial-scale=1.0, user-scalable=yes\" />\
         \</head>\
         \<body>\
         \<header><h1>CompaREST</h1></header>\
         \<main>\
         \$body$\
         \</main>\
         \</body>\
         \</html>"

awsmCss :: ByteString
awsmCss :: ByteString
awsmCss = $(makeRelativeToProject "awsm-css/dist/awsm.min.css" >>= embedFile)