From 56aba32edf6765ea7d328dd5febd0167d926ec39 Mon Sep 17 00:00:00 2001 From: Julian Ospald <hasufell@posteo.de> Date: Sat, 27 Jan 2024 18:07:12 +0800 Subject: [PATCH] Migrate abstract-filepath-tests to tasty --- filepath.cabal | 2 + tests/abstract-filepath/OsPathSpec.hs | 409 ++++++++++--------- tests/abstract-filepath/Test.hs | 4 +- tests/filepath-equivalent-tests/Gen.hs | 4 +- tests/filepath-equivalent-tests/TestEquiv.hs | 13 - 5 files changed, 215 insertions(+), 217 deletions(-) diff --git a/filepath.cabal b/filepath.cabal index 5ba88ab..d9ff661 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -165,6 +165,8 @@ test-suite abstract-filepath , os-string >=2.0.1 , QuickCheck >=2.7 && <2.15 , quickcheck-classes-base ^>=0.6.2 + , tasty + , tasty-quickcheck benchmark bench-filepath default-language: Haskell2010 diff --git a/tests/abstract-filepath/OsPathSpec.hs b/tests/abstract-filepath/OsPathSpec.hs index 35bff2e..2b50607 100644 --- a/tests/abstract-filepath/OsPathSpec.hs +++ b/tests/abstract-filepath/OsPathSpec.hs @@ -33,6 +33,8 @@ import qualified System.OsString.Data.ByteString.Short.Word16 as BS16 import qualified System.OsString.Data.ByteString.Short as SBS import Data.Char ( ord ) import Data.Proxy ( Proxy(..) ) +import Test.Tasty +import Test.Tasty.QuickCheck import Arbitrary @@ -42,211 +44,216 @@ fromRight _ (Right b) = b fromRight b _ = b -tests :: [(String, Property)] -tests = - [ ("OSP.encodeUtf . OSP.decodeUtf == id", - property $ \(NonNullString str) -> (OSP.decodeUtf . fromJust . OSP.encodeUtf) str == Just str) +tests :: TestTree +tests = testGroup "Abstract filepath" [ + testGroup "filepaths" + [ testProperties "OSP" + [ ("pack . unpack == id", + property $ \ws@(OsString _) -> + OSP.pack (OSP.unpack ws) === ws + ), + ("encodeUtf . decodeUtf == id", + property $ \(NonNullString str) -> (OSP.decodeUtf . fromJust . OSP.encodeUtf) str == Just str) + ], + testProperties "Windows" + [ ("pack . unpack == id (Windows)", + property $ \ws@(WindowsString _) -> + Windows.pack (Windows.unpack ws) === ws + ) + , ("decodeUtf . encodeUtf == id", + property $ \(NonNullString str) -> (Windows.decodeUtf . fromJust . Windows.encodeUtf) str == Just str) + , ("encodeWith ucs2le . decodeWith ucs2le == id", + property $ \(padEven -> bs) -> (Windows.encodeWith ucs2le . (\(Right r) -> r) . Windows.decodeWith ucs2le . OS.WS . toShort) bs + === Right (OS.WS . toShort $ bs)) + , ("decodeFS . encodeFS == id (Windows)", + property $ \(NonNullString str) -> ioProperty $ do + r1 <- Windows.encodeFS str + r2 <- try @SomeException $ Windows.decodeFS r1 + r3 <- evaluate $ force $ first displayException r2 + pure (r3 === Right str) + ) + , ("fromPlatformString* functions are equivalent under ASCII", + property $ \(WindowsString . BS16.pack . map (fromIntegral . ord) . nonNullAsciiString -> str) -> ioProperty $ do + r1 <- Windows.decodeFS str + r2 <- Windows.decodeUtf str + (Right r3) <- pure $ Windows.decodeWith (mkUTF16le TransliterateCodingFailure) str + (Right r4) <- pure $ Windows.decodeWith (mkUTF16le RoundtripFailure) str + (Right r5) <- pure $ Windows.decodeWith (mkUTF16le ErrorOnCodingFailure) str + pure ( r1 === r2 + .&&. r1 === r3 + .&&. r1 === r4 + .&&. r1 === r5 + ) + ) + , ("toPlatformString* functions are equivalent under ASCII", + property $ \(NonNullAsciiString str) -> ioProperty $ do + r1 <- Windows.encodeFS str + r2 <- Windows.encodeUtf str + (Right r3) <- pure $ Windows.encodeWith (mkUTF16le TransliterateCodingFailure) str + (Right r4) <- pure $ Windows.encodeWith (mkUTF16le RoundtripFailure) str + (Right r5) <- pure $ Windows.encodeWith (mkUTF16le ErrorOnCodingFailure) str + pure ( r1 === r2 + .&&. r1 === r3 + .&&. r1 === r4 + .&&. r1 === r5 + ) + ) + , ("Unit test toPlatformString*", + property $ ioProperty $ do + let str = "ABcK_(ツ123_&**" + let expected = WindowsString $ BS16.pack [0x0041,0x0042,0x0063,0x004b,0x005f,0x0028,0x30c4,0x0031,0x0032,0x0033,0x005f,0x0026,0x002a,0x002a] + r1 <- Windows.encodeFS str + r2 <- Windows.encodeUtf str + (Right r3) <- pure $ Windows.encodeWith (mkUTF16le TransliterateCodingFailure) str + (Right r4) <- pure $ Windows.encodeWith (mkUTF16le RoundtripFailure) str + (Right r5) <- pure $ Windows.encodeWith (mkUTF16le ErrorOnCodingFailure) str + pure ( r1 === expected + .&&. r2 === expected + .&&. r3 === expected + .&&. r4 === expected + .&&. r5 === expected + ) + ) + , ("Unit test fromPlatformString*", + property $ ioProperty $ do + let bs = WindowsString $ BS16.pack [0x0041,0x0042,0x0063,0x004b,0x005f,0x0028,0x30c4,0x0031,0x0032,0x0033,0x005f,0x0026,0x002a,0x002a] + let expected = "ABcK_(ツ123_&**" + r1 <- Windows.decodeFS bs + r2 <- Windows.decodeUtf bs + (Right r3) <- pure $ Windows.decodeWith (mkUTF16le TransliterateCodingFailure) bs + (Right r4) <- pure $ Windows.decodeWith (mkUTF16le RoundtripFailure) bs + (Right r5) <- pure $ Windows.decodeWith (mkUTF16le ErrorOnCodingFailure) bs + pure ( r1 === expected + .&&. r2 === expected + .&&. r3 === expected + .&&. r4 === expected + .&&. r5 === expected + ) + ) + ] + , testProperties "Posix" + [ ("decodeUtf . encodeUtf == id", + property $ \(NonNullString str) -> (Posix.decodeUtf . fromJust . Posix.encodeUtf) str == Just str) + , ("encodeWith ucs2le . decodeWith ucs2le == id (Posix)", + property $ \(padEven -> bs) -> (Posix.encodeWith ucs2le . (\(Right r) -> r) . Posix.decodeWith ucs2le . OS.PS . toShort) bs === Right (OS.PS . toShort $ bs)) + , ("decodeFS . encodeFS == id", + property $ \(NonNullString str) -> ioProperty $ do + setFileSystemEncoding (mkUTF8 TransliterateCodingFailure) + r1 <- Posix.encodeFS str + r2 <- try @SomeException $ Posix.decodeFS r1 + r3 <- evaluate $ force $ first displayException r2 + pure (r3 === Right str) + ) + , ("fromPlatformString* functions are equivalent under ASCII", + property $ \(PosixString . SBS.toShort . C.pack . nonNullAsciiString -> str) -> ioProperty $ do + r1 <- Posix.decodeFS str + r2 <- Posix.decodeUtf str + (Right r3) <- pure $ Posix.decodeWith (mkUTF8 TransliterateCodingFailure) str + (Right r4) <- pure $ Posix.decodeWith (mkUTF8 RoundtripFailure) str + (Right r5) <- pure $ Posix.decodeWith (mkUTF8 ErrorOnCodingFailure) str + pure ( r1 === r2 + .&&. r1 === r3 + .&&. r1 === r4 + .&&. r1 === r5 + ) + ) + , ("toPlatformString* functions are equivalent under ASCII", + property $ \(NonNullAsciiString str) -> ioProperty $ do + r1 <- Posix.encodeFS str + r2 <- Posix.encodeUtf str + (Right r3) <- pure $ Posix.encodeWith (mkUTF8 TransliterateCodingFailure) str + (Right r4) <- pure $ Posix.encodeWith (mkUTF8 RoundtripFailure) str + (Right r5) <- pure $ Posix.encodeWith (mkUTF8 ErrorOnCodingFailure) str + pure ( r1 === r2 + .&&. r1 === r3 + .&&. r1 === r4 + .&&. r1 === r5 + ) + ) + , ("Unit test toPlatformString*", + property $ ioProperty $ do + let str = "ABcK_(ツ123_&**" + let expected = PosixString $ SBS.pack [0x41,0x42,0x63,0x4b,0x5f,0x28,0xe3,0x83,0x84,0x31,0x32,0x33,0x5f,0x26,0x2a,0x2a] + r1 <- Posix.encodeFS str + r2 <- Posix.encodeUtf str + (Right r3) <- pure $ Posix.encodeWith (mkUTF8 TransliterateCodingFailure) str + (Right r4) <- pure $ Posix.encodeWith (mkUTF8 RoundtripFailure) str + (Right r5) <- pure $ Posix.encodeWith (mkUTF8 ErrorOnCodingFailure) str + pure ( r1 === expected + .&&. r2 === expected + .&&. r3 === expected + .&&. r4 === expected + .&&. r5 === expected + ) + ) + , ("Unit test fromPlatformString*", + property $ ioProperty $ do + let bs = PosixString $ SBS.pack [0x41,0x42,0x63,0x4b,0x5f,0x28,0xe3,0x83,0x84,0x31,0x32,0x33,0x5f,0x26,0x2a,0x2a] + let expected = "ABcK_(ツ123_&**" + r1 <- Posix.decodeFS bs + r2 <- Posix.decodeUtf bs + (Right r3) <- pure $ Posix.decodeWith (mkUTF8 TransliterateCodingFailure) bs + (Right r4) <- pure $ Posix.decodeWith (mkUTF8 RoundtripFailure) bs + (Right r5) <- pure $ Posix.decodeWith (mkUTF8 ErrorOnCodingFailure) bs + pure ( r1 === expected + .&&. r2 === expected + .&&. r3 === expected + .&&. r4 === expected + .&&. r5 === expected + ) + ) + , ("pack . unpack == id (Posix)", + property $ \ws@(PosixString _) -> + Posix.pack (Posix.unpack ws) === ws + ) + ] + ], + testGroup "QuasiQuoter" + [ testProperties "windows" + [ ("QuasiQuoter (WindowsPath)", + property $ do + let bs = WindowsString $ BS16.pack [0x0041,0x0042,0x0063,0x004b,0x005f] + let expected = [Windows.pstr|ABcK_|] + bs === expected + ) + , ("QuasiQuoter (WindowsString)", + property $ do + let bs = WindowsString $ BS16.pack [0x0041,0x0042,0x0063,0x004b,0x005f,0x0028,0x30c4,0x0031,0x0032,0x0033,0x005f,0x0026,0x002a,0x002a] + let expected = [WindowsS.pstr|ABcK_(ツ123_&**|] + bs === expected + ) + ], + testProperties "posix" + [ ("QuasiQuoter (PosixPath)", + property $ do + let bs = PosixString $ SBS.pack [0x41,0x42,0x63,0x4b,0x5f] + let expected = [Posix.pstr|ABcK_|] + bs === expected + ) + , ("QuasiQuoter (PosixString)", + property $ do + let bs = PosixString $ SBS.pack [0x41,0x42,0x63,0x4b,0x5f,0x28,0xe3,0x83,0x84,0x31,0x32,0x33,0x5f,0x26,0x2a,0x2a] + let expected = [PosixS.pstr|ABcK_(ツ123_&**|] + bs === expected + ) + ] + ], + testProperties "Type laws" + (QC.lawsProperties (QC.ordLaws (Proxy @OsPath)) + ++ QC.lawsProperties (QC.monoidLaws (Proxy @OsPath)) - , ("decodeUtf . encodeUtf == id (Posix)", - property $ \(NonNullString str) -> (Posix.decodeUtf . fromJust . Posix.encodeUtf) str == Just str) - , ("decodeUtf . encodeUtf == id (Windows)", - property $ \(NonNullString str) -> (Windows.decodeUtf . fromJust . Windows.encodeUtf) str == Just str) + ++ QC.lawsProperties (QC.ordLaws (Proxy @OsString)) + ++ QC.lawsProperties (QC.monoidLaws (Proxy @OsString)) - , ("encodeWith ucs2le . decodeWith ucs2le == id (Posix)", - property $ \(padEven -> bs) -> (Posix.encodeWith ucs2le . (\(Right r) -> r) . Posix.decodeWith ucs2le . OS.PS . toShort) bs === Right (OS.PS . toShort $ bs)) - , ("encodeWith ucs2le . decodeWith ucs2le == id (Windows)", - property $ \(padEven -> bs) -> (Windows.encodeWith ucs2le . (\(Right r) -> r) . Windows.decodeWith ucs2le . OS.WS . toShort) bs - === Right (OS.WS . toShort $ bs)) + ++ QC.lawsProperties (QC.ordLaws (Proxy @WindowsString)) + ++ QC.lawsProperties (QC.monoidLaws (Proxy @WindowsString)) - , ("decodeFS . encodeFS == id (Posix)", - property $ \(NonNullString str) -> ioProperty $ do - setFileSystemEncoding (mkUTF8 TransliterateCodingFailure) - r1 <- Posix.encodeFS str - r2 <- try @SomeException $ Posix.decodeFS r1 - r3 <- evaluate $ force $ first displayException r2 - pure (r3 === Right str) - ) - , ("decodeFS . encodeFS == id (Windows)", - property $ \(NonNullString str) -> ioProperty $ do - r1 <- Windows.encodeFS str - r2 <- try @SomeException $ Windows.decodeFS r1 - r3 <- evaluate $ force $ first displayException r2 - pure (r3 === Right str) - ) + ++ QC.lawsProperties (QC.ordLaws (Proxy @PosixString)) + ++ QC.lawsProperties (QC.monoidLaws (Proxy @PosixString)) - , ("fromPlatformString* functions are equivalent under ASCII (Windows)", - property $ \(WindowsString . BS16.pack . map (fromIntegral . ord) . nonNullAsciiString -> str) -> ioProperty $ do - r1 <- Windows.decodeFS str - r2 <- Windows.decodeUtf str - (Right r3) <- pure $ Windows.decodeWith (mkUTF16le TransliterateCodingFailure) str - (Right r4) <- pure $ Windows.decodeWith (mkUTF16le RoundtripFailure) str - (Right r5) <- pure $ Windows.decodeWith (mkUTF16le ErrorOnCodingFailure) str - pure ( r1 === r2 - .&&. r1 === r3 - .&&. r1 === r4 - .&&. r1 === r5 - ) - ) - - , ("fromPlatformString* functions are equivalent under ASCII (Posix)", - property $ \(PosixString . SBS.toShort . C.pack . nonNullAsciiString -> str) -> ioProperty $ do - r1 <- Posix.decodeFS str - r2 <- Posix.decodeUtf str - (Right r3) <- pure $ Posix.decodeWith (mkUTF8 TransliterateCodingFailure) str - (Right r4) <- pure $ Posix.decodeWith (mkUTF8 RoundtripFailure) str - (Right r5) <- pure $ Posix.decodeWith (mkUTF8 ErrorOnCodingFailure) str - pure ( r1 === r2 - .&&. r1 === r3 - .&&. r1 === r4 - .&&. r1 === r5 - ) - ) - - , ("toPlatformString* functions are equivalent under ASCII (Windows)", - property $ \(NonNullAsciiString str) -> ioProperty $ do - r1 <- Windows.encodeFS str - r2 <- Windows.encodeUtf str - (Right r3) <- pure $ Windows.encodeWith (mkUTF16le TransliterateCodingFailure) str - (Right r4) <- pure $ Windows.encodeWith (mkUTF16le RoundtripFailure) str - (Right r5) <- pure $ Windows.encodeWith (mkUTF16le ErrorOnCodingFailure) str - pure ( r1 === r2 - .&&. r1 === r3 - .&&. r1 === r4 - .&&. r1 === r5 - ) - ) - - , ("toPlatformString* functions are equivalent under ASCII (Posix)", - property $ \(NonNullAsciiString str) -> ioProperty $ do - r1 <- Posix.encodeFS str - r2 <- Posix.encodeUtf str - (Right r3) <- pure $ Posix.encodeWith (mkUTF8 TransliterateCodingFailure) str - (Right r4) <- pure $ Posix.encodeWith (mkUTF8 RoundtripFailure) str - (Right r5) <- pure $ Posix.encodeWith (mkUTF8 ErrorOnCodingFailure) str - pure ( r1 === r2 - .&&. r1 === r3 - .&&. r1 === r4 - .&&. r1 === r5 - ) - ) - , ("Unit test toPlatformString* (Posix)", - property $ ioProperty $ do - let str = "ABcK_(ツ123_&**" - let expected = PosixString $ SBS.pack [0x41,0x42,0x63,0x4b,0x5f,0x28,0xe3,0x83,0x84,0x31,0x32,0x33,0x5f,0x26,0x2a,0x2a] - r1 <- Posix.encodeFS str - r2 <- Posix.encodeUtf str - (Right r3) <- pure $ Posix.encodeWith (mkUTF8 TransliterateCodingFailure) str - (Right r4) <- pure $ Posix.encodeWith (mkUTF8 RoundtripFailure) str - (Right r5) <- pure $ Posix.encodeWith (mkUTF8 ErrorOnCodingFailure) str - pure ( r1 === expected - .&&. r2 === expected - .&&. r3 === expected - .&&. r4 === expected - .&&. r5 === expected - ) - ) - , ("Unit test toPlatformString* (WindowsString)", - property $ ioProperty $ do - let str = "ABcK_(ツ123_&**" - let expected = WindowsString $ BS16.pack [0x0041,0x0042,0x0063,0x004b,0x005f,0x0028,0x30c4,0x0031,0x0032,0x0033,0x005f,0x0026,0x002a,0x002a] - r1 <- Windows.encodeFS str - r2 <- Windows.encodeUtf str - (Right r3) <- pure $ Windows.encodeWith (mkUTF16le TransliterateCodingFailure) str - (Right r4) <- pure $ Windows.encodeWith (mkUTF16le RoundtripFailure) str - (Right r5) <- pure $ Windows.encodeWith (mkUTF16le ErrorOnCodingFailure) str - pure ( r1 === expected - .&&. r2 === expected - .&&. r3 === expected - .&&. r4 === expected - .&&. r5 === expected - ) - ) - - , ("Unit test fromPlatformString* (Posix)", - property $ ioProperty $ do - let bs = PosixString $ SBS.pack [0x41,0x42,0x63,0x4b,0x5f,0x28,0xe3,0x83,0x84,0x31,0x32,0x33,0x5f,0x26,0x2a,0x2a] - let expected = "ABcK_(ツ123_&**" - r1 <- Posix.decodeFS bs - r2 <- Posix.decodeUtf bs - (Right r3) <- pure $ Posix.decodeWith (mkUTF8 TransliterateCodingFailure) bs - (Right r4) <- pure $ Posix.decodeWith (mkUTF8 RoundtripFailure) bs - (Right r5) <- pure $ Posix.decodeWith (mkUTF8 ErrorOnCodingFailure) bs - pure ( r1 === expected - .&&. r2 === expected - .&&. r3 === expected - .&&. r4 === expected - .&&. r5 === expected - ) - ) - , ("Unit test fromPlatformString* (WindowsString)", - property $ ioProperty $ do - let bs = WindowsString $ BS16.pack [0x0041,0x0042,0x0063,0x004b,0x005f,0x0028,0x30c4,0x0031,0x0032,0x0033,0x005f,0x0026,0x002a,0x002a] - let expected = "ABcK_(ツ123_&**" - r1 <- Windows.decodeFS bs - r2 <- Windows.decodeUtf bs - (Right r3) <- pure $ Windows.decodeWith (mkUTF16le TransliterateCodingFailure) bs - (Right r4) <- pure $ Windows.decodeWith (mkUTF16le RoundtripFailure) bs - (Right r5) <- pure $ Windows.decodeWith (mkUTF16le ErrorOnCodingFailure) bs - pure ( r1 === expected - .&&. r2 === expected - .&&. r3 === expected - .&&. r4 === expected - .&&. r5 === expected - ) - ) - , ("QuasiQuoter (WindowsString)", - property $ do - let bs = WindowsString $ BS16.pack [0x0041,0x0042,0x0063,0x004b,0x005f,0x0028,0x30c4,0x0031,0x0032,0x0033,0x005f,0x0026,0x002a,0x002a] - let expected = [WindowsS.pstr|ABcK_(ツ123_&**|] - bs === expected - ) - , ("QuasiQuoter (PosixString)", - property $ do - let bs = PosixString $ SBS.pack [0x41,0x42,0x63,0x4b,0x5f,0x28,0xe3,0x83,0x84,0x31,0x32,0x33,0x5f,0x26,0x2a,0x2a] - let expected = [PosixS.pstr|ABcK_(ツ123_&**|] - bs === expected - ) - , ("QuasiQuoter (WindowsPath)", - property $ do - let bs = WindowsString $ BS16.pack [0x0041,0x0042,0x0063,0x004b,0x005f] - let expected = [Windows.pstr|ABcK_|] - bs === expected - ) - , ("QuasiQuoter (PosixPath)", - property $ do - let bs = PosixString $ SBS.pack [0x41,0x42,0x63,0x4b,0x5f] - let expected = [Posix.pstr|ABcK_|] - bs === expected - ) - - , ("pack . unpack == id (Windows)", - property $ \ws@(WindowsString _) -> - Windows.pack (Windows.unpack ws) === ws - ) - , ("pack . unpack == id (Posix)", - property $ \ws@(PosixString _) -> - Posix.pack (Posix.unpack ws) === ws - ) - , ("pack . unpack == id (OsPath)", - property $ \ws@(OsString _) -> - OSP.pack (OSP.unpack ws) === ws - ) - - - ] ++ QC.lawsProperties (QC.ordLaws (Proxy @OsPath)) - ++ QC.lawsProperties (QC.monoidLaws (Proxy @OsPath)) - - ++ QC.lawsProperties (QC.ordLaws (Proxy @OsString)) - ++ QC.lawsProperties (QC.monoidLaws (Proxy @OsString)) - - ++ QC.lawsProperties (QC.ordLaws (Proxy @WindowsString)) - ++ QC.lawsProperties (QC.monoidLaws (Proxy @WindowsString)) - - ++ QC.lawsProperties (QC.ordLaws (Proxy @PosixString)) - ++ QC.lawsProperties (QC.monoidLaws (Proxy @PosixString)) - - ++ QC.lawsProperties (QC.ordLaws (Proxy @PlatformString)) - ++ QC.lawsProperties (QC.monoidLaws (Proxy @PlatformString)) + ++ QC.lawsProperties (QC.ordLaws (Proxy @PlatformString)) + ++ QC.lawsProperties (QC.monoidLaws (Proxy @PlatformString))) + ] padEven :: ByteString -> ByteString diff --git a/tests/abstract-filepath/Test.hs b/tests/abstract-filepath/Test.hs index 00261b0..31698b6 100644 --- a/tests/abstract-filepath/Test.hs +++ b/tests/abstract-filepath/Test.hs @@ -1,7 +1,7 @@ module Main (main) where import qualified OsPathSpec -import TestUtil +import Test.Tasty main :: IO () -main = runTests (OsPathSpec.tests) +main = defaultMain OsPathSpec.tests diff --git a/tests/filepath-equivalent-tests/Gen.hs b/tests/filepath-equivalent-tests/Gen.hs index 309ffec..97aa358 100644 --- a/tests/filepath-equivalent-tests/Gen.hs +++ b/tests/filepath-equivalent-tests/Gen.hs @@ -148,7 +148,7 @@ data RelFilePath = Rel1 (NonEmpty (NonEmptyString, NonEmpty Separator)) (Maybe F deriving Arbitrary via (GenericArbitraryRec '[2, 1] `AndShrinking` RelFilePath) instance AltShow RelFilePath where - altShow (Rel1 ns mf) = (mconcat $ NE.toList $ fmap (\(a, b) -> altShow a ++ altShow b) ns) ++ altShow mf + altShow (Rel1 ns mf) = mconcat (NE.toList $ fmap (\(a, b) -> altShow a ++ altShow b) ns) ++ altShow mf altShow (Rel2 fn) = altShow fn -- file-name = 1*pchar [ stream ] @@ -156,6 +156,8 @@ data FileName = FileName NonEmptyString (Maybe DataStream) deriving (GShow, Show, Eq, Ord, Generic) instance Arbitrary FileName where + -- make sure that half of the filenames include a dot '.' + -- so that we can deal with extensions arbitrary = do ns <- arbitrary ds <- arbitrary diff --git a/tests/filepath-equivalent-tests/TestEquiv.hs b/tests/filepath-equivalent-tests/TestEquiv.hs index 99ab99a..339ce1a 100644 --- a/tests/filepath-equivalent-tests/TestEquiv.hs +++ b/tests/filepath-equivalent-tests/TestEquiv.hs @@ -21,7 +21,6 @@ import qualified Legacy.System.FilePath.Windows as LW import qualified Legacy.System.FilePath.Posix as LP - main :: IO () main = defaultMain equivalentTests @@ -432,15 +431,3 @@ equivalentTests = testGroup "equivalence" ] ] - - - - - - - - - - - - -- GitLab