Skip to content

Commit

Permalink
Use normalized filepaths in tests
Browse files Browse the repository at this point in the history
  • Loading branch information
mmhat committed Jun 5, 2024
1 parent af350b1 commit 9aa1a9a
Show file tree
Hide file tree
Showing 11 changed files with 16 additions and 27 deletions.
2 changes: 0 additions & 2 deletions dhall/tests/Dhall/Test/Diff.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,7 @@
module Dhall.Test.Diff where

import Data.Text (Text)
import Prelude hiding (FilePath)
import Test.Tasty (TestTree)
import Turtle (FilePath)

import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
Expand Down
2 changes: 0 additions & 2 deletions dhall/tests/Dhall/Test/Freeze.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,7 @@ module Dhall.Test.Freeze where

import Data.Text (Text)
import Dhall.Freeze (Intent (..), Scope (..))
import Prelude hiding (FilePath)
import Test.Tasty (TestTree)
import Turtle (FilePath)

import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
Expand Down
4 changes: 2 additions & 2 deletions dhall/tests/Dhall/Test/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ getTests = do
successTests <- Test.Util.discover (Turtle.chars <* "A.dhall") successTest (do
path <- Turtle.lstree (importDirectory </> "success")

Monad.guard (path `notElem` flakyTests)
Monad.guard (path `Test.Util.pathNotElem` flakyTests)

return path )

Expand All @@ -96,7 +96,7 @@ getTests = do
#endif
]

_ <- Monad.guard (path `notElem` expectedSuccesses)
_ <- Monad.guard (path `Test.Util.pathNotElem` expectedSuccesses)
_ <- Monad.guard (not ("ENV.dhall" `isSuffixOf` Text.pack path))
return path )

Expand Down
2 changes: 0 additions & 2 deletions dhall/tests/Dhall/Test/Lint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,7 @@ module Dhall.Test.Lint where

import Data.Text (Text)
import Dhall.Parser (Header (..))
import Prelude hiding (FilePath)
import Test.Tasty (TestTree)
import Turtle (FilePath)

import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
Expand Down
3 changes: 1 addition & 2 deletions dhall/tests/Dhall/Test/Normalization.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,8 @@ module Dhall.Test.Normalization where
import Data.Text (Text)
import Data.Void (Void)
import Dhall.Core (Expr (..), Var (..), throws)
import Prelude hiding (FilePath)
import System.FilePath ((</>))
import Test.Tasty (TestTree)
import Turtle (FilePath, (</>))

import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
Expand Down
3 changes: 1 addition & 2 deletions dhall/tests/Dhall/Test/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,8 @@ module Dhall.Test.Parser where
import Data.Text (Text)
import Data.Void (Void)
import Dhall.Core (Binding (..), Expr (..), Import, Var (..))
import Prelude hiding (FilePath)
import System.FilePath ((</>))
import Test.Tasty (TestTree)
import Turtle (FilePath, (</>))

import qualified Control.Monad as Monad
import qualified Data.Bifunctor as Bifunctor
Expand Down
2 changes: 0 additions & 2 deletions dhall/tests/Dhall/Test/Schemas.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,7 @@ module Dhall.Test.Schemas where

import Data.Text (Text)
import Dhall.Parser (Header (..))
import Prelude hiding (FilePath)
import Test.Tasty (TestTree)
import Turtle (FilePath)

import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
Expand Down
2 changes: 0 additions & 2 deletions dhall/tests/Dhall/Test/SemanticHash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,7 @@
module Dhall.Test.SemanticHash where

import Data.Text (Text)
import Prelude hiding (FilePath)
import Test.Tasty (TestTree)
import Turtle (FilePath)

import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
Expand Down
7 changes: 3 additions & 4 deletions dhall/tests/Dhall/Test/Tags.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,8 @@ module Dhall.Test.Tags where

import Data.Text (Text)
import Dhall.Util (Input (..))
import Prelude hiding (FilePath)
import System.FilePath ((</>))
import Test.Tasty (TestTree)
import Turtle (FilePath)

import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
Expand All @@ -30,7 +29,7 @@ getTests = do
tagsTest :: Text -> TestTree
tagsTest prefix =
Tasty.HUnit.testCase (Text.unpack prefix) $ do
let inputFile = Text.unpack (prefix <> ".dhall")
let inputFile = Text.unpack (Test.Util.toDhallPath prefix <> ".dhall")
let outputFile = Text.unpack (prefix <> ".tags")

actualTags <- fixPathSeparators <$> Tags.generate (InputFile inputFile) Nothing False
Expand All @@ -44,7 +43,7 @@ tagsTest prefix =
tagsDirTest :: TestTree
tagsDirTest =
Tasty.HUnit.testCase "all" $ do
let outputFile = Text.unpack . Turtle.format Turtle.fp $ tagsDirectory Turtle.</> "all.tags"
let outputFile = Text.unpack . Turtle.format Turtle.fp $ tagsDirectory </> "all.tags"

actualTags <- fmap fixPathSeparators
(Tags.generate
Expand Down
3 changes: 1 addition & 2 deletions dhall/tests/Dhall/Test/TypeInference.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,8 @@ module Dhall.Test.TypeInference where

import Control.Exception (SomeException (..))
import Data.Text (Text)
import Prelude hiding (FilePath)
import System.FilePath ((</>))
import Test.Tasty (TestTree)
import Turtle (FilePath, (</>))

import qualified Control.Exception as Exception
import qualified Control.Monad as Monad
Expand Down
13 changes: 8 additions & 5 deletions dhall/tests/Dhall/Test/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ module Dhall.Test.Util
, assertDoesntTypeCheck
, discover
, Dhall.Test.Util.testCase
, pathNotElem
, toDhallPath
, managedTestEnvironment
) where
Expand All @@ -41,11 +42,10 @@ import Dhall.Core
)
import Dhall.Import (SemanticCacheMode (..), Status (..))
import Dhall.Parser (Src)
import Prelude hiding (FilePath)
import System.IO.Error (isDoesNotExistError)
import Test.Tasty (TestTree)
import Test.Tasty.HUnit
import Turtle (FilePath, Pattern, Shell, fp)
import Turtle (Pattern, Shell, fp)

import qualified Control.Exception
import qualified Control.Foldl as Foldl
Expand Down Expand Up @@ -289,7 +289,7 @@ discover pattern buildTest paths = do
let shell = do
path_ <- paths

let pathText = Turtle.format fp path_
let pathText = Turtle.format fp (FilePath.normalise path_)

prefix : _ <- return (Turtle.match pattern pathText)

Expand All @@ -301,15 +301,18 @@ discover pattern buildTest paths = do

testCase :: Text -> [ FilePath ] -> Assertion -> TestTree
testCase prefix expectedFailures assertion =
if prefix `elem` map (Turtle.format fp) expectedFailures
if prefix `elem` map (Turtle.format fp . FilePath.normalise) expectedFailures
then Tasty.ExpectedFailure.expectFail test
else test
where
test = Test.Tasty.HUnit.testCase (Text.unpack prefix) assertion

pathNotElem :: FilePath -> [FilePath] -> Bool
pathNotElem this = not . any (FilePath.equalFilePath this)

{-| Path names on Windows are not valid Dhall paths due to using backslashes
instead of forwardslashes to separate path components. This utility fixes
them if necessary
-}
toDhallPath :: Text -> Text
toDhallPath = Text.replace "\\" "/"
toDhallPath = ("./" <>) . Text.replace "\\" "/"

0 comments on commit 9aa1a9a

Please sign in to comment.