{-| An example of using project-forge on a single .mustache file. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module SingleFile.Example where import Control.Exception import Data.Aeson import ProjectForge import Test.Tasty import Test.Tasty.HUnit exampleTemplate :: (MonadLogger m, MonadIO m ) => m FileTemplate exampleTemplate = getFileTemplateFromFile "examples/SingleFile/{{name}}-report.md" varsComplete :: Value varsComplete = object [ "name" .= String "Chris" , "value" .= Number 10000 , "taxed_value" .= Number 6000.0 , "in_ca" .= True ] varsIncomplete :: Value varsIncomplete = object [ "name" .= String "Chris" , "value" .= Number 10000 , "in_ca" .= True ] runExample1 :: Value -> IO (FilePath, Text) runExample1 v = runSimpleLoggingT (exampleTemplate >>= (\x -> renderFileTemplate (MkRenderTemplateOpts WarningAsError) x v)) runExample2 :: Value -> IO (FilePath, Text) runExample2 v = runSimpleLoggingT (exampleTemplate >>= (\x -> renderFileTemplate (MkRenderTemplateOpts Ignore) x v)) catchRunExample :: Value -> IO (Maybe (FilePath, Text)) catchRunExample v = do catch ( Just <$> runSimpleLoggingT (exampleTemplate >>= (\x -> renderFileTemplate (MkRenderTemplateOpts WarningAsError) x v))) (\(e :: SomeException) -> pure Nothing ) exampleSuccess1 :: IO TestTree exampleSuccess1 = testCase "Render should succeed with complete variables" <$> (assertEqual "results should be equal" <$> runExample1 varsComplete <*> pure ( "examples/SingleFile/Chris-report.md" , "Hello Chris\nYou have just won 10000 dollars!\nWell, 6000 dollars, after taxes.\n")) exampleSuccess2 :: IO TestTree exampleSuccess2 = testCase "Render should succeed with incomplete variables when ignoring errors" <$> (assertEqual "results should be equal" <$> runExample2 varsIncomplete <*> pure ( "examples/SingleFile/Chris-report.md" , "Hello Chris\nYou have just won 10000 dollars!\nWell, dollars, after taxes.\n")) exampleFailed :: IO TestTree exampleFailed = testCase "Render should fail with incomplete variables" <$> (do results <- catchRunExample varsIncomplete case results of Nothing -> pure $ assertBool "Successfully failed" True Just _ -> assertFailure "This test *should* fail" ) examples :: IO TestTree examples = testGroup "SimpleFile examples" <$> sequenceA [exampleSuccess1, exampleSuccess2, exampleFailed]