{-|
An example of using project-forge on a git repo

-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}

module GitRepo.Example where

import           Control.Exception
import           Data.Aeson
import           ProjectForge
import           System.FilePath
import           Test.Tasty
import           Test.Tasty.HUnit

exampleTemplate :: (MonadLogger m, MonadIO m ) => m ProjectTemplate
exampleTemplate =
  getProjectTemplateFromGit
    Nothing
    "https://test:hLdWVML8yDFyNiN4KaPN@gitlab.com/TargetRWE/epistats/nsstat/project-forge-example.git"
    Nothing

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"
  ]

-- remove directory for these test since the directory is temporary
fn :: (FilePath, b) -> (FilePath, b)
fn (x, y) = (takeFileName x, y)

runExample1 :: Value -> IO [(FilePath, Text)]
runExample1 v =
   fmap fn <$>
   runSimpleLoggingT
   ( exampleTemplate >>= (\x -> renderProjectTemplate (MkRenderTemplateOpts WarningAsError) x v))


runExample2 :: Value -> IO [(FilePath, Text)]
runExample2 v =
  fmap fn <$>
  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"
    [ (".gitignore","# your basic .gitignore\n\n.RData")
    , ("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")
    , ("no-template-variables.R","# An example of a file without template variables\n\n\"this file is copied as-is\"")
    , ("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"
     [ (".gitignore","# your basic .gitignore\n\n.RData")
     , ("README.md","# This is the Some Project project\n\nHere you can read more about it: \n\n\n")
     , ("no-template-variables.R","# An example of a file without template variables\n\n\"this file is copied as-is\"")
     , ("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]