Skip to content

Commit

Permalink
Start evaluator tests
Browse files Browse the repository at this point in the history
  • Loading branch information
tchoutri committed Feb 4, 2025
1 parent 3dd322d commit 5fa927c
Show file tree
Hide file tree
Showing 7 changed files with 50 additions and 5 deletions.
4 changes: 3 additions & 1 deletion confer.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ extra-doc-files:
CHANGELOG.md
doc/*.md
README.md
doc/confer_example.lua
examples/confer.lua

data-files: runtime/lua/confer.lua
tested-with: GHC ==9.10.1
Expand Down Expand Up @@ -94,6 +94,7 @@ library
, selective
, text
, text-display
, text-builder-linear
, validation-selective
, vector

Expand Down Expand Up @@ -142,4 +143,5 @@ test-suite confer-test
, tasty-coverage
, tasty-hunit
, tasty-test-reporter
, vector
, temporary
File renamed without changes.
7 changes: 4 additions & 3 deletions src/Confer/Config/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,9 @@ module Confer.Config.Types
import Data.Maybe
import Data.Text (Text)
import Data.Text.Display
import Data.Text.Internal.Builder qualified as Builder
import Data.Text.Builder.Linear qualified as Builder
import Data.Vector (Vector)
import Data.String
import System.OsPath (OsPath)
import System.OsPath qualified as OsPath

Expand All @@ -28,9 +29,9 @@ instance Display Fact where
displayBuilder Fact{name, source, destination} =
Builder.fromText name
<> ": "
<> Builder.fromString (fromJust (OsPath.decodeUtf source))
<> fromString (fromJust (OsPath.decodeUtf source))
<> " ~> "
<> Builder.fromString (fromJust (OsPath.decodeUtf destination))
<> fromString (fromJust (OsPath.decodeUtf destination))

data Deployment = Deployment
{ hostname :: Maybe Text
Expand Down
36 changes: 36 additions & 0 deletions test/Confer/EvaluatorTest.hs
Original file line number Diff line number Diff line change
@@ -1 +1,37 @@
{-# LANGUAGE QuasiQuotes #-}

Check warning on line 1 in test/Confer/EvaluatorTest.hs

View workflow job for this annotation

GitHub Actions / hlint

Warning in module Confer.EvaluatorTest: Unused LANGUAGE pragma ▫︎ Found: "{-# LANGUAGE QuasiQuotes #-}"
module Confer.EvaluatorTest where

import Data.Function
import Control.Monad
import Data.Vector qualified as Vector
import Data.List.NonEmpty qualified as NE
import Effectful
import Effectful.Error.Static (Error)
import Effectful.Error.Static qualified as Error
import Effectful.FileSystem (FileSystem)

Check warning on line 11 in test/Confer/EvaluatorTest.hs

View workflow job for this annotation

GitHub Actions / hlint

Warning in module Confer.EvaluatorTest: Use fewer imports ▫︎ Found: "import Effectful.FileSystem ( FileSystem )\nimport Effectful.FileSystem qualified as FileSystem\nimport Effectful.FileSystem\n" ▫︎ Perhaps: "import Effectful.FileSystem qualified as FileSystem\nimport Effectful.FileSystem\n"
import Effectful.FileSystem qualified as FileSystem
import System.FilePath qualified as FilePath
import System.IO.Temp qualified as Temporary
import System.OsPath
import System.OsPath qualified as OsPath
import Test.Tasty (TestTree)
import Effectful.FileSystem
import Test.Tasty.HUnit ()

import Confer.Config.Evaluator
import Utils

spec :: TestEff TestTree
spec =
testThese
"Evaluator Checks"
[ testThis "Empty configuration" testEmptyConfigurationoError
]

testEmptyConfigurationoError :: TestEff ()
testEmptyConfigurationoError = do
Temporary.withSystemTempDirectory "empty-config.ext" $ \directory -> do
copyFile "./test/fixtures/empty-config.lua" (directory <> "/empty-config.lua")
filepath <- liftIO $ encodeUtf $ directory <> "/empty-config.lua"
result <- assertRight =<< loadConfiguration False filepath
assertEqual result Vector.empty
2 changes: 2 additions & 0 deletions test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ import Test.Tasty.HUnit
import Test.Tasty.Runners.Reporter qualified as Reporter

import Confer.CLI.Cmd.CheckTest qualified as CheckTest
import Confer.EvaluatorTest qualified as EvaluatorTest
import Utils (TestEff)
import Utils qualified

Expand All @@ -23,4 +24,5 @@ main = do
specs :: List (TestEff TestTree)
specs =
[ CheckTest.spec
, EvaluatorTest.spec
]
5 changes: 4 additions & 1 deletion test/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ assertIsNotSymlink (Right _) = assertFailure "Did not return Left"
assertIsNotSymlink (Left (IsNotSymlink{})) = pure ()
assertIsNotSymlink (Left e) = assertFailure $ "Returned: " <> show e

assertRight :: HasCallStack => Either a () -> TestEff ()
assertRight :: HasCallStack => Either a b -> TestEff b
assertRight (Left _a) = liftIO $ Test.assertFailure "Test return Left instead of Right"
assertRight (Right b) = pure b

Expand All @@ -67,3 +67,6 @@ testThese groupName tests = fmap (Test.testGroup groupName) newTests

assertBool :: Bool -> TestEff ()
assertBool boolean = liftIO $ Test.assertBool "" boolean

assertEqual :: (Eq a, Show a) => a -> a -> TestEff ()
assertEqual actual expected = liftIO $ Test.assertEqual "" actual expected
1 change: 1 addition & 0 deletions test/fixtures/empty-config.lua
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
return {}

0 comments on commit 5fa927c

Please sign in to comment.