{-| An example of using project-forge on a directory. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module SingleDirectory.Example where import Control.Exception import Data.Aeson import ProjectForge import Test.Tasty import Test.Tasty.HUnit exampleTemplate :: (MonadLogger m, MonadIO m ) => m ProjectTemplate exampleTemplate = getProjectTemplateFromDir "examples/SingleDirectory/project-template/" varsComplete :: Value varsComplete = object [ "prj" .= String "Some Project" , "desc" .= String "This is a description on some project" , "srcDir" .= String "src" ] varsIncomplete :: Value varsIncomplete = object [ "prj" .= String "Some Project" ] runExample1 :: Value -> IO [(FilePath, Text)] runExample1 v = runSimpleLoggingT (exampleTemplate >>= (\x -> renderProjectTemplate (MkRenderTemplateOpts WarningAsError) x v)) runExample2 :: Value -> IO [(FilePath, Text)] runExample2 v = runSimpleLoggingT (exampleTemplate >>= (\x -> renderProjectTemplate (MkRenderTemplateOpts Ignore) x v)) catchRunExample :: Value -> IO (Maybe [(FilePath, Text)]) catchRunExample v = do catch ( Just <$> runSimpleLoggingT (exampleTemplate >>= (\x -> renderProjectTemplate (MkRenderTemplateOpts WarningAsError) x v))) (\(e :: SomeException) -> pure Nothing ) exampleSuccess1 :: IO TestTree exampleSuccess1 = testCase "Render should succeed with complete variables" . assertEqual "results should be equal" [ ("examples/SingleDirectory/project-template/.gitignore","# your basic .gitignore\n\n.RData") , ("examples/SingleDirectory/project-template/README.md", "# This is the Some Project project\n\nHere you can read more about it: \n\nThis is a description on some project\n") , ("examples/SingleDirectory/project-template/src/no-template-variables.R","# An example of a file without template variables\n\n\"this file is copied as-is\"") , ("examples/SingleDirectory/project-template/src/project.R", "# This is the source code for Some Project\n\nprint_prj <- function() {\n print(\"Some Project\")\n}") ] <$> runExample1 varsComplete exampleSuccess2 :: IO TestTree exampleSuccess2 = testCase "Render should succeed with incomplete variables when ignoring errors" . assertEqual "results should be equal" [ ("examples/SingleDirectory/project-template/.gitignore","# your basic .gitignore\n\n.RData") , ("examples/SingleDirectory/project-template/README.md","# This is the Some Project project\n\nHere you can read more about it: \n\n\n") , ("examples/SingleDirectory/project-template//no-template-variables.R","# An example of a file without template variables\n\n\"this file is copied as-is\"") , ("examples/SingleDirectory/project-template//project.R", "# This is the source code for Some Project\n\nprint_prj <- function() {\n print(\"Some Project\")\n}") ] <$> runExample2 varsIncomplete 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]