{- Do not edit! Created from test/TestTemplate.hs -}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
module TestResult (results) where

import qualified System.Path.Generic as Path
import qualified System.Path.Posix as Posix
import qualified System.Path.Windows as Windows
import System.Path.Generic ((</>), (<.>), relFile, relDir, absFile, absDir)
import Data.Char (toLower)


results ::
  (Path.AbsRelClass ar) => Char -> Posix.FilePath ar -> [(String, Bool)]
results a x =
  {-# LINE 353 "src/System/Path/Internal.hs" #-}
  ("Path.pathMap (map toLower) (absDir \"/tmp/Reports/SpreadSheets\") == Posix.absDir \"/tmp/reports/spreadsheets\"",
      Path.pathMap (map toLower) (absDir "/tmp/Reports/SpreadSheets") == Posix.absDir "/tmp/reports/spreadsheets") :
  {-# LINE 490 "src/System/Path/Internal.hs" #-}
  ("show (Posix.rootDir </> relDir \"bla\" </> relFile \"blub\") == \"rootDir </> relPath \\\"bla\\\" </> relPath \\\"blub\\\"\"",
      show (Posix.rootDir </> relDir "bla" </> relFile "blub") == "rootDir </> relPath \"bla\" </> relPath \"blub\"") :
  {-# LINE 491 "src/System/Path/Internal.hs" #-}
  ("show (Just (Posix.rootDir </> relDir \"bla\" </> relFile \"blub\")) == \"Just (rootDir </> relPath \\\"bla\\\" </> relPath \\\"blub\\\")\"",
      show (Just (Posix.rootDir </> relDir "bla" </> relFile "blub")) == "Just (rootDir </> relPath \"bla\" </> relPath \"blub\")") :
  {-# LINE 492 "src/System/Path/Internal.hs" #-}
  ("show (Posix.currentDir </> relDir \"bla\" </> relFile \"blub\") == \"currentDir </> relPath \\\"bla\\\" </> relPath \\\"blub\\\"\"",
      show (Posix.currentDir </> relDir "bla" </> relFile "blub") == "currentDir </> relPath \"bla\" </> relPath \"blub\"") :
  {-# LINE 493 "src/System/Path/Internal.hs" #-}
  ("show (Just (Posix.currentDir </> relDir \"bla\" </> relFile \"blub\")) == \"Just (currentDir </> relPath \\\"bla\\\" </> relPath \\\"blub\\\")\"",
      show (Just (Posix.currentDir </> relDir "bla" </> relFile "blub")) == "Just (currentDir </> relPath \"bla\" </> relPath \"blub\")") :
  {-# LINE 494 "src/System/Path/Internal.hs" #-}
  ("show (Windows.absDir \"c:\" </> relDir \"bla\" </> relFile \"blub\") == \"absDir \\\"c:\\\" </> relPath \\\"bla\\\" </> relPath \\\"blub\\\"\"",
      show (Windows.absDir "c:" </> relDir "bla" </> relFile "blub") == "absDir \"c:\" </> relPath \"bla\" </> relPath \"blub\"") :
  {-# LINE 495 "src/System/Path/Internal.hs" #-}
  ("show (Just (Windows.absDir \"c:\\\\\" </> relDir \"bla\" </> relFile \"blub\")) == \"Just (absDir \\\"c:\\\\\\\\\\\" </> relPath \\\"bla\\\" </> relPath \\\"blub\\\")\"",
      show (Just (Windows.absDir "c:\\" </> relDir "bla" </> relFile "blub")) == "Just (absDir \"c:\\\\\" </> relPath \"bla\" </> relPath \"blub\")") :
  {-# LINE 527 "src/System/Path/Internal.hs" #-}
  ("read \"rootDir\" == Posix.rootDir",
      read "rootDir" == Posix.rootDir) :
  {-# LINE 528 "src/System/Path/Internal.hs" #-}
  ("read \"rootDir\" == Windows.rootDir",
      read "rootDir" == Windows.rootDir) :
  {-# LINE 529 "src/System/Path/Internal.hs" #-}
  ("read \"currentDir\" == Posix.currentDir",
      read "currentDir" == Posix.currentDir) :
  {-# LINE 530 "src/System/Path/Internal.hs" #-}
  ("read \"currentDir\" == Windows.currentDir",
      read "currentDir" == Windows.currentDir) :
  {-# LINE 531 "src/System/Path/Internal.hs" #-}
  ("let path = Posix.rootDir </> relDir \"bla\" </> relFile \"blub\" in read (show path) == path",
      let path = Posix.rootDir </> relDir "bla" </> relFile "blub" in read (show path) == path) :
  {-# LINE 532 "src/System/Path/Internal.hs" #-}
  ("let path = Just (Posix.rootDir </> relDir \"bla\" </> relFile \"blub\") in read (show path) == path",
      let path = Just (Posix.rootDir </> relDir "bla" </> relFile "blub") in read (show path) == path) :
  {-# LINE 533 "src/System/Path/Internal.hs" #-}
  ("let path = Posix.currentDir </> relDir \"bla\" </> relFile \"blub\" in read (show path) == path",
      let path = Posix.currentDir </> relDir "bla" </> relFile "blub" in read (show path) == path) :
  {-# LINE 534 "src/System/Path/Internal.hs" #-}
  ("let path = Just (Posix.currentDir </> relDir \"bla\" </> relFile \"blub\") in read (show path) == path",
      let path = Just (Posix.currentDir </> relDir "bla" </> relFile "blub") in read (show path) == path) :
  {-# LINE 535 "src/System/Path/Internal.hs" #-}
  ("let path = Windows.rootDir </> relDir \"bla\" </> relFile \"blub\" in read (show path) == path",
      let path = Windows.rootDir </> relDir "bla" </> relFile "blub" in read (show path) == path) :
  {-# LINE 536 "src/System/Path/Internal.hs" #-}
  ("let path = Just (Windows.rootDir </> relDir \"bla\" </> relFile \"blub\") in read (show path) == path",
      let path = Just (Windows.rootDir </> relDir "bla" </> relFile "blub") in read (show path) == path) :
  {-# LINE 537 "src/System/Path/Internal.hs" #-}
  ("let path = Windows.absDir \"c:\" </> relDir \"bla\" </> relFile \"blub\" in read (show path) == path",
      let path = Windows.absDir "c:" </> relDir "bla" </> relFile "blub" in read (show path) == path) :
  {-# LINE 632 "src/System/Path/Internal.hs" #-}
  ("Posix.toString Path.rootDir == \"/\"",
      Posix.toString Path.rootDir == "/") :
  {-# LINE 633 "src/System/Path/Internal.hs" #-}
  ("Windows.toString Path.rootDir == \"\\\\\"",
      Windows.toString Path.rootDir == "\\") :
  {-# LINE 643 "src/System/Path/Internal.hs" #-}
  ("Posix.toString Path.currentDir == \".\"",
      Posix.toString Path.currentDir == ".") :
  {-# LINE 644 "src/System/Path/Internal.hs" #-}
  ("Windows.toString Path.currentDir == \".\"",
      Windows.toString Path.currentDir == ".") :
  {-# LINE 683 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/\" :: Maybe Posix.AbsDir) == Just \"/\"",
      fmap Posix.toString (Posix.maybePath "/" :: Maybe Posix.AbsDir) == Just "/") :
  {-# LINE 684 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/\" :: Maybe Posix.AbsFile) == Nothing",
      fmap Posix.toString (Posix.maybePath "/" :: Maybe Posix.AbsFile) == Nothing) :
  {-# LINE 685 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/\" :: Maybe Posix.RelDir) == Nothing",
      fmap Posix.toString (Posix.maybePath "/" :: Maybe Posix.RelDir) == Nothing) :
  {-# LINE 686 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/\" :: Maybe Posix.RelFile) == Nothing",
      fmap Posix.toString (Posix.maybePath "/" :: Maybe Posix.RelFile) == Nothing) :
  {-# LINE 687 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp\" :: Maybe Posix.AbsDir) == Just \"/tmp\"",
      fmap Posix.toString (Posix.maybePath "/tmp" :: Maybe Posix.AbsDir) == Just "/tmp") :
  {-# LINE 688 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp\" :: Maybe Posix.AbsFile) == Just \"/tmp\"",
      fmap Posix.toString (Posix.maybePath "/tmp" :: Maybe Posix.AbsFile) == Just "/tmp") :
  {-# LINE 689 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp\" :: Maybe Posix.RelDir) == Nothing",
      fmap Posix.toString (Posix.maybePath "/tmp" :: Maybe Posix.RelDir) == Nothing) :
  {-# LINE 690 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp\" :: Maybe Posix.RelFile) == Nothing",
      fmap Posix.toString (Posix.maybePath "/tmp" :: Maybe Posix.RelFile) == Nothing) :
  {-# LINE 691 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp/\" :: Maybe Posix.AbsDir) == Just \"/tmp\"",
      fmap Posix.toString (Posix.maybePath "/tmp/" :: Maybe Posix.AbsDir) == Just "/tmp") :
  {-# LINE 692 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp/\" :: Maybe Posix.AbsFile) == Nothing",
      fmap Posix.toString (Posix.maybePath "/tmp/" :: Maybe Posix.AbsFile) == Nothing) :
  {-# LINE 693 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp/\" :: Maybe Posix.RelDir) == Nothing",
      fmap Posix.toString (Posix.maybePath "/tmp/" :: Maybe Posix.RelDir) == Nothing) :
  {-# LINE 694 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp/\" :: Maybe Posix.RelFile) == Nothing",
      fmap Posix.toString (Posix.maybePath "/tmp/" :: Maybe Posix.RelFile) == Nothing) :
  {-# LINE 695 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp\" :: Maybe Posix.AbsOrRelFileOrDir) == Just \"/tmp\"",
      fmap Posix.toString (Posix.maybePath "/tmp" :: Maybe Posix.AbsOrRelFileOrDir) == Just "/tmp") :
  {-# LINE 696 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"/tmp/\" :: Maybe Posix.AbsOrRelFileOrDir) == Just \"/tmp\"",
      fmap Posix.toString (Posix.maybePath "/tmp/" :: Maybe Posix.AbsOrRelFileOrDir) == Just "/tmp") :
  {-# LINE 697 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"file.txt\" :: Maybe Posix.RelFile) == Just \"file.txt\"",
      fmap Posix.toString (Posix.maybePath "file.txt" :: Maybe Posix.RelFile) == Just "file.txt") :
  {-# LINE 698 "src/System/Path/Internal.hs" #-}
  ("fmap Posix.toString (Posix.maybePath \"file.txt\" :: Maybe Posix.AbsFile) == Nothing",
      fmap Posix.toString (Posix.maybePath "file.txt" :: Maybe Posix.AbsFile) == Nothing) :
  {-# LINE 699 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"\\\\tmp\" :: Maybe Windows.AbsDir) == Just \"\\\\tmp\"",
      fmap Windows.toString (Windows.maybePath "\\tmp" :: Maybe Windows.AbsDir) == Just "\\tmp") :
  {-# LINE 700 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"a:\\\\tmp\" :: Maybe Windows.AbsDir) == Just \"a:\\\\tmp\"",
      fmap Windows.toString (Windows.maybePath "a:\\tmp" :: Maybe Windows.AbsDir) == Just "a:\\tmp") :
  {-# LINE 701 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"a:tmp\" :: Maybe Windows.AbsDir) == Just \"a:tmp\"",
      fmap Windows.toString (Windows.maybePath "a:tmp" :: Maybe Windows.AbsDir) == Just "a:tmp") :
  {-# LINE 702 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"a:\\\\\" :: Maybe Windows.AbsDir) == Just \"a:\\\\\"",
      fmap Windows.toString (Windows.maybePath "a:\\" :: Maybe Windows.AbsDir) == Just "a:\\") :
  {-# LINE 703 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"a:\" :: Maybe Windows.AbsDir) == Just \"a:\"",
      fmap Windows.toString (Windows.maybePath "a:" :: Maybe Windows.AbsDir) == Just "a:") :
  {-# LINE 704 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"tmp\" :: Maybe Windows.RelDir) == Just \"tmp\"",
      fmap Windows.toString (Windows.maybePath "tmp" :: Maybe Windows.RelDir) == Just "tmp") :
  {-# LINE 705 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"\\\\tmp\" :: Maybe Windows.RelDir) == Nothing",
      fmap Windows.toString (Windows.maybePath "\\tmp" :: Maybe Windows.RelDir) == Nothing) :
  {-# LINE 706 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"a:\\\\tmp\" :: Maybe Windows.RelDir) == Nothing",
      fmap Windows.toString (Windows.maybePath "a:\\tmp" :: Maybe Windows.RelDir) == Nothing) :
  {-# LINE 707 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"a:tmp\" :: Maybe Windows.RelDir) == Nothing",
      fmap Windows.toString (Windows.maybePath "a:tmp" :: Maybe Windows.RelDir) == Nothing) :
  {-# LINE 708 "src/System/Path/Internal.hs" #-}
  ("fmap Windows.toString (Windows.maybePath \"tmp\" :: Maybe Windows.AbsDir) == Nothing",
      fmap Windows.toString (Windows.maybePath "tmp" :: Maybe Windows.AbsDir) == Nothing) :
  {-# LINE 757 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.relFile \"file.txt\") == \"file.txt\"",
      Posix.toString (Posix.relFile "file.txt") == "file.txt") :
  {-# LINE 758 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.relFile \"tmp\") == \"tmp\"",
      Posix.toString (Posix.relFile "tmp") == "tmp") :
  {-# LINE 764 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.relDir \".\") == \".\"",
      Posix.toString (Posix.relDir ".") == ".") :
  {-# LINE 765 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.relDir \"file.txt\") == \"file.txt\"",
      Posix.toString (Posix.relDir "file.txt") == "file.txt") :
  {-# LINE 766 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.relDir \"tmp\") == \"tmp\"",
      Posix.toString (Posix.relDir "tmp") == "tmp") :
  {-# LINE 772 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.absFile \"/file.txt\") == \"/file.txt\"",
      Posix.toString (Posix.absFile "/file.txt") == "/file.txt") :
  {-# LINE 773 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.absFile \"/tmp\") == \"/tmp\"",
      Posix.toString (Posix.absFile "/tmp") == "/tmp") :
  {-# LINE 779 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.absDir \"/file.txt\") == \"/file.txt\"",
      Posix.toString (Posix.absDir "/file.txt") == "/file.txt") :
  {-# LINE 780 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.absDir \"/tmp\") == \"/tmp\"",
      Posix.toString (Posix.absDir "/tmp") == "/tmp") :
  {-# LINE 845 "src/System/Path/Internal.hs" #-}
  ("Posix.asPath \"/tmp\" == Posix.absDir \"/tmp\"",
      Posix.asPath "/tmp" == Posix.absDir "/tmp") :
  {-# LINE 846 "src/System/Path/Internal.hs" #-}
  ("Posix.asPath \"file.txt\" == Posix.relFile \"file.txt\"",
      Posix.asPath "file.txt" == Posix.relFile "file.txt") :
  {-# LINE 847 "src/System/Path/Internal.hs" #-}
  ("Path.isAbsolute (Posix.asAbsDir \"/tmp\")",
      Path.isAbsolute (Posix.asAbsDir "/tmp")) :
  {-# LINE 848 "src/System/Path/Internal.hs" #-}
  ("Path.isRelative (Posix.asRelDir \"/tmp\")",
      Path.isRelative (Posix.asRelDir "/tmp")) :
  {-# LINE 849 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asPath \"/tmp\" :: Posix.AbsDir) == \"/tmp\"",
      Posix.toString (Posix.asPath "/tmp" :: Posix.AbsDir) == "/tmp") :
  {-# LINE 850 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asPath \"/tmp\" :: Posix.RelDir) == \"tmp\"",
      Posix.toString (Posix.asPath "/tmp" :: Posix.RelDir) == "tmp") :
  {-# LINE 851 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.asPath \"\\\\tmp\" :: Windows.AbsDir) == \"\\\\tmp\"",
      Windows.toString (Windows.asPath "\\tmp" :: Windows.AbsDir) == "\\tmp") :
  {-# LINE 852 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.asPath \"a:\\\\tmp\" :: Windows.AbsDir) == \"a:\\\\tmp\"",
      Windows.toString (Windows.asPath "a:\\tmp" :: Windows.AbsDir) == "a:\\tmp") :
  {-# LINE 853 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.asPath \"a:tmp\" :: Windows.AbsDir) == \"a:tmp\"",
      Windows.toString (Windows.asPath "a:tmp" :: Windows.AbsDir) == "a:tmp") :
  {-# LINE 854 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.asPath \"tmp\" :: Windows.RelDir) == \"tmp\"",
      Windows.toString (Windows.asPath "tmp" :: Windows.RelDir) == "tmp") :
  {-# LINE 862 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelFile \"file.txt\") == \"file.txt\"",
      Posix.toString (Posix.asRelFile "file.txt") == "file.txt") :
  {-# LINE 863 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelFile \"/file.txt\") == \"file.txt\"",
      Posix.toString (Posix.asRelFile "/file.txt") == "file.txt") :
  {-# LINE 864 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelFile \"tmp\") == \"tmp\"",
      Posix.toString (Posix.asRelFile "tmp") == "tmp") :
  {-# LINE 865 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelFile \"/tmp\") == \"tmp\"",
      Posix.toString (Posix.asRelFile "/tmp") == "tmp") :
  {-# LINE 871 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelDir \".\") == \".\"",
      Posix.toString (Posix.asRelDir ".") == ".") :
  {-# LINE 872 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelDir \"file.txt\") == \"file.txt\"",
      Posix.toString (Posix.asRelDir "file.txt") == "file.txt") :
  {-# LINE 873 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelDir \"/file.txt\") == \"file.txt\"",
      Posix.toString (Posix.asRelDir "/file.txt") == "file.txt") :
  {-# LINE 874 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelDir \"tmp\") == \"tmp\"",
      Posix.toString (Posix.asRelDir "tmp") == "tmp") :
  {-# LINE 875 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asRelDir \"/tmp\") == \"tmp\"",
      Posix.toString (Posix.asRelDir "/tmp") == "tmp") :
  {-# LINE 881 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asAbsFile \"/file.txt\") == \"/file.txt\"",
      Posix.toString (Posix.asAbsFile "/file.txt") == "/file.txt") :
  {-# LINE 882 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asAbsFile \"/tmp\") == \"/tmp\"",
      Posix.toString (Posix.asAbsFile "/tmp") == "/tmp") :
  {-# LINE 888 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asAbsDir \"/file.txt\") == \"/file.txt\"",
      Posix.toString (Posix.asAbsDir "/file.txt") == "/file.txt") :
  {-# LINE 889 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.asAbsDir \"/tmp\") == \"/tmp\"",
      Posix.toString (Posix.asAbsDir "/tmp") == "/tmp") :
  {-# LINE 926 "src/System/Path/Internal.hs" #-}
  ("Path.mkPathAbsOrRel \"/tmp\" == Left (Posix.absDir \"/tmp\")",
      Path.mkPathAbsOrRel "/tmp" == Left (Posix.absDir "/tmp")) :
  {-# LINE 927 "src/System/Path/Internal.hs" #-}
  ("Path.mkPathAbsOrRel  \"tmp\" == Right (Posix.relDir \"tmp\")",
      Path.mkPathAbsOrRel  "tmp" == Right (Posix.relDir "tmp")) :
  {-# LINE 928 "src/System/Path/Internal.hs" #-}
  ("Path.mkPathAbsOrRel \"\\\\tmp\" == Left (Windows.absDir \"\\\\tmp\")",
      Path.mkPathAbsOrRel "\\tmp" == Left (Windows.absDir "\\tmp")) :
  {-# LINE 929 "src/System/Path/Internal.hs" #-}
  ("Path.mkPathAbsOrRel \"d:\\\\tmp\" == Left (Windows.absDir \"d:\\\\tmp\")",
      Path.mkPathAbsOrRel "d:\\tmp" == Left (Windows.absDir "d:\\tmp")) :
  {-# LINE 930 "src/System/Path/Internal.hs" #-}
  ("Path.mkPathAbsOrRel \"d:tmp\" == Left (Windows.absDir \"d:tmp\")",
      Path.mkPathAbsOrRel "d:tmp" == Left (Windows.absDir "d:tmp")) :
  {-# LINE 931 "src/System/Path/Internal.hs" #-}
  ("Path.mkPathAbsOrRel \"tmp\" == Right (Windows.relDir \"tmp\")",
      Path.mkPathAbsOrRel "tmp" == Right (Windows.relDir "tmp")) :
  {-# LINE 961 "src/System/Path/Internal.hs" #-}
  ("Path.mkAbsPath (absDir \"/tmp\") \"foo.txt\" == Posix.absFile \"/tmp/foo.txt\"",
      Path.mkAbsPath (absDir "/tmp") "foo.txt" == Posix.absFile "/tmp/foo.txt") :
  {-# LINE 962 "src/System/Path/Internal.hs" #-}
  ("Path.mkAbsPath (absDir \"/tmp\") \"/etc/foo.txt\" == Posix.absFile \"/etc/foo.txt\"",
      Path.mkAbsPath (absDir "/tmp") "/etc/foo.txt" == Posix.absFile "/etc/foo.txt") :
  {-# LINE 1099 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.absDir \"/tmp\" </> Posix.relFile \"file.txt\") == \"/tmp/file.txt\"",
      Posix.toString (Posix.absDir "/tmp" </> Posix.relFile "file.txt") == "/tmp/file.txt") :
  {-# LINE 1100 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.absDir \"/tmp\" </> Posix.relDir \"dir\" </> Posix.relFile \"file.txt\") == \"/tmp/dir/file.txt\"",
      Posix.toString (Posix.absDir "/tmp" </> Posix.relDir "dir" </> Posix.relFile "file.txt") == "/tmp/dir/file.txt") :
  {-# LINE 1101 "src/System/Path/Internal.hs" #-}
  ("Posix.toString (Posix.relDir \"dir\" </> Posix.relFile \"file.txt\") == \"dir/file.txt\"",
      Posix.toString (Posix.relDir "dir" </> Posix.relFile "file.txt") == "dir/file.txt") :
  {-# LINE 1102 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.absDir \"\\\\tmp\" </> Windows.relFile \"file.txt\") == \"\\\\tmp\\\\file.txt\"",
      Windows.toString (Windows.absDir "\\tmp" </> Windows.relFile "file.txt") == "\\tmp\\file.txt") :
  {-# LINE 1103 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.absDir \"c:\\\\tmp\" </> Windows.relFile \"file.txt\") == \"c:\\\\tmp\\\\file.txt\"",
      Windows.toString (Windows.absDir "c:\\tmp" </> Windows.relFile "file.txt") == "c:\\tmp\\file.txt") :
  {-# LINE 1104 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.absDir \"c:tmp\" </> Windows.relFile \"file.txt\") == \"c:tmp\\\\file.txt\"",
      Windows.toString (Windows.absDir "c:tmp" </> Windows.relFile "file.txt") == "c:tmp\\file.txt") :
  {-# LINE 1105 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.absDir \"c:\\\\\" </> Windows.relDir \"tmp\" </> Windows.relFile \"file.txt\") == \"c:\\\\tmp\\\\file.txt\"",
      Windows.toString (Windows.absDir "c:\\" </> Windows.relDir "tmp" </> Windows.relFile "file.txt") == "c:\\tmp\\file.txt") :
  {-# LINE 1106 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.absDir \"c:\" </> Windows.relDir \"tmp\" </> Windows.relFile \"file.txt\") == \"c:tmp\\\\file.txt\"",
      Windows.toString (Windows.absDir "c:" </> Windows.relDir "tmp" </> Windows.relFile "file.txt") == "c:tmp\\file.txt") :
  {-# LINE 1107 "src/System/Path/Internal.hs" #-}
  ("Windows.toString (Windows.relDir \"dir\" </> Windows.relFile \"file.txt\") == \"dir\\\\file.txt\"",
      Windows.toString (Windows.relDir "dir" </> Windows.relFile "file.txt") == "dir\\file.txt") :
  {-# LINE 1134 "src/System/Path/Internal.hs" #-}
  ("Path.addExtension (relFile \"file.txt\") \"bib\" == Posix.relFile \"file.txt.bib\"",
      Path.addExtension (relFile "file.txt") "bib" == Posix.relFile "file.txt.bib") :
  {-# LINE 1135 "src/System/Path/Internal.hs" #-}
  ("Path.addExtension (relFile \"file.\") \".bib\" == Posix.relFile \"file..bib\"",
      Path.addExtension (relFile "file.") ".bib" == Posix.relFile "file..bib") :
  {-# LINE 1136 "src/System/Path/Internal.hs" #-}
  ("Path.addExtension (relFile \"file\") \".bib\" == Posix.relFile \"file.bib\"",
      Path.addExtension (relFile "file") ".bib" == Posix.relFile "file.bib") :
  {-# LINE 1137 "src/System/Path/Internal.hs" #-}
  ("Path.addExtension Path.emptyFile \"bib\" == Posix.relFile \".bib\"",
      Path.addExtension Path.emptyFile "bib" == Posix.relFile ".bib") :
  {-# LINE 1138 "src/System/Path/Internal.hs" #-}
  ("Path.addExtension Path.emptyFile \".bib\" == Posix.relFile \".bib\"",
      Path.addExtension Path.emptyFile ".bib" == Posix.relFile ".bib") :
  {-# LINE 1139 "src/System/Path/Internal.hs" #-}
  ("Path.takeFileName (Path.addExtension Path.emptyFile \"ext\") == Posix.relFile \".ext\"",
      Path.takeFileName (Path.addExtension Path.emptyFile "ext") == Posix.relFile ".ext") :
  {-# LINE 1154 "src/System/Path/Internal.hs" #-}
  ("Path.dropExtension x == fst (Path.splitExtension x)",
      Path.dropExtension x == fst (Path.splitExtension x)) :
  {-# LINE 1160 "src/System/Path/Internal.hs" #-}
  ("not $ Path.hasAnExtension (Path.dropExtensions x)",
      not $ Path.hasAnExtension (Path.dropExtensions x)) :
  {-# LINE 1171 "src/System/Path/Internal.hs" #-}
  ("Path.replaceExtension (relFile \"file.txt\") \".bob\" == Posix.relFile \"file.bob\"",
      Path.replaceExtension (relFile "file.txt") ".bob" == Posix.relFile "file.bob") :
  {-# LINE 1172 "src/System/Path/Internal.hs" #-}
  ("Path.replaceExtension (relFile \"file.txt\") \"bob\" == Posix.relFile \"file.bob\"",
      Path.replaceExtension (relFile "file.txt") "bob" == Posix.relFile "file.bob") :
  {-# LINE 1173 "src/System/Path/Internal.hs" #-}
  ("Path.replaceExtension (relFile \"file\") \".bob\" == Posix.relFile \"file.bob\"",
      Path.replaceExtension (relFile "file") ".bob" == Posix.relFile "file.bob") :
  {-# LINE 1174 "src/System/Path/Internal.hs" #-}
  ("Path.replaceExtension (relFile \"file.txt\") \"\" == Posix.relFile \"file\"",
      Path.replaceExtension (relFile "file.txt") "" == Posix.relFile "file") :
  {-# LINE 1175 "src/System/Path/Internal.hs" #-}
  ("Path.replaceExtension (relFile \"file.fred.bob\") \"txt\" == Posix.relFile \"file.fred.txt\"",
      Path.replaceExtension (relFile "file.fred.bob") "txt" == Posix.relFile "file.fred.txt") :
  {-# LINE 1192 "src/System/Path/Internal.hs" #-}
  ("uncurry (<.>) (Path.splitExtension x) == x",
      uncurry (<.>) (Path.splitExtension x) == x) :
  {-# LINE 1193 "src/System/Path/Internal.hs" #-}
  ("uncurry Path.addExtension (Path.splitExtension x) == x",
      uncurry Path.addExtension (Path.splitExtension x) == x) :
  {-# LINE 1194 "src/System/Path/Internal.hs" #-}
  ("Path.splitExtension (relFile \"file.txt\") == (Posix.relFile \"file\",\".txt\")",
      Path.splitExtension (relFile "file.txt") == (Posix.relFile "file",".txt")) :
  {-# LINE 1195 "src/System/Path/Internal.hs" #-}
  ("Path.splitExtension (relFile \".bashrc\") == (Posix.emptyFile, \".bashrc\")",
      Path.splitExtension (relFile ".bashrc") == (Posix.emptyFile, ".bashrc")) :
  {-# LINE 1196 "src/System/Path/Internal.hs" #-}
  ("Path.splitExtension (relFile \"file\") == (Posix.relFile \"file\",\"\")",
      Path.splitExtension (relFile "file") == (Posix.relFile "file","")) :
  {-# LINE 1197 "src/System/Path/Internal.hs" #-}
  ("Path.splitExtension (relFile \"file/file.txt\") == (Posix.relFile \"file/file\",\".txt\")",
      Path.splitExtension (relFile "file/file.txt") == (Posix.relFile "file/file",".txt")) :
  {-# LINE 1198 "src/System/Path/Internal.hs" #-}
  ("Path.splitExtension (relFile \"file.txt/boris\") == (Posix.relFile \"file.txt/boris\",\"\")",
      Path.splitExtension (relFile "file.txt/boris") == (Posix.relFile "file.txt/boris","")) :
  {-# LINE 1199 "src/System/Path/Internal.hs" #-}
  ("Path.splitExtension (relFile \"file.txt/boris.ext\") == (Posix.relFile \"file.txt/boris\",\".ext\")",
      Path.splitExtension (relFile "file.txt/boris.ext") == (Posix.relFile "file.txt/boris",".ext")) :
  {-# LINE 1200 "src/System/Path/Internal.hs" #-}
  ("Path.splitExtension (relFile \"file/path.txt.bob.fred\") == (Posix.relFile \"file/path.txt.bob\",\".fred\")",
      Path.splitExtension (relFile "file/path.txt.bob.fred") == (Posix.relFile "file/path.txt.bob",".fred")) :
  {-# LINE 1206 "src/System/Path/Internal.hs" #-}
  ("Path.splitExtensions (relFile \"file.tar.gz\") == (Posix.relFile \"file\",\".tar.gz\")",
      Path.splitExtensions (relFile "file.tar.gz") == (Posix.relFile "file",".tar.gz")) :
  {-# LINE 1222 "src/System/Path/Internal.hs" #-}
  ("Path.takeBaseName (absFile \"/tmp/somedir/myfile.txt\") == Posix.relFile \"myfile\"",
      Path.takeBaseName (absFile "/tmp/somedir/myfile.txt") == Posix.relFile "myfile") :
  {-# LINE 1223 "src/System/Path/Internal.hs" #-}
  ("Path.takeBaseName (relFile \"./myfile.txt\") == Posix.relFile \"myfile\"",
      Path.takeBaseName (relFile "./myfile.txt") == Posix.relFile "myfile") :
  {-# LINE 1224 "src/System/Path/Internal.hs" #-}
  ("Path.takeBaseName (relFile \"myfile.txt\") == Posix.relFile \"myfile\"",
      Path.takeBaseName (relFile "myfile.txt") == Posix.relFile "myfile") :
  {-# LINE 1233 "src/System/Path/Internal.hs" #-}
  ("Path.takeExtension x == snd (Path.splitExtension x)",
      Path.takeExtension x == snd (Path.splitExtension x)) :
  {-# LINE 1234 "src/System/Path/Internal.hs" #-}
  ("Path.takeExtension (Path.addExtension x \"ext\") == \".ext\"",
      Path.takeExtension (Path.addExtension x "ext") == ".ext") :
  {-# LINE 1235 "src/System/Path/Internal.hs" #-}
  ("Path.takeExtension (Path.replaceExtension x \"ext\") == \".ext\"",
      Path.takeExtension (Path.replaceExtension x "ext") == ".ext") :
  {-# LINE 1241 "src/System/Path/Internal.hs" #-}
  ("Path.takeExtensions (Posix.relFile \"file.tar.gz\") == \".tar.gz\"",
      Path.takeExtensions (Posix.relFile "file.tar.gz") == ".tar.gz") :
  {-# LINE 1247 "src/System/Path/Internal.hs" #-}
  ("Path.takeFileName (absFile \"/tmp/somedir/myfile.txt\") == Posix.relFile \"myfile.txt\"",
      Path.takeFileName (absFile "/tmp/somedir/myfile.txt") == Posix.relFile "myfile.txt") :
  {-# LINE 1248 "src/System/Path/Internal.hs" #-}
  ("Path.takeFileName (relFile \"./myfile.txt\") == Posix.relFile \"myfile.txt\"",
      Path.takeFileName (relFile "./myfile.txt") == Posix.relFile "myfile.txt") :
  {-# LINE 1249 "src/System/Path/Internal.hs" #-}
  ("Path.takeFileName (relFile \"myfile.txt\") == Posix.relFile \"myfile.txt\"",
      Path.takeFileName (relFile "myfile.txt") == Posix.relFile "myfile.txt") :
  {-# LINE 1266 "src/System/Path/Internal.hs" #-}
  ("      Posix.equalFilePath \"abc/def\" \"abc/def\"",
            Posix.equalFilePath "abc/def" "abc/def") :
  {-# LINE 1267 "src/System/Path/Internal.hs" #-}
  ("      Posix.equalFilePath \"abc/def\" \"abc//def\"",
            Posix.equalFilePath "abc/def" "abc//def") :
  {-# LINE 1268 "src/System/Path/Internal.hs" #-}
  ("      Posix.equalFilePath \"/tmp/\" \"/tmp\"",
            Posix.equalFilePath "/tmp/" "/tmp") :
  {-# LINE 1269 "src/System/Path/Internal.hs" #-}
  ("      Posix.equalFilePath \"/tmp\" \"//tmp\"",
            Posix.equalFilePath "/tmp" "//tmp") :
  {-# LINE 1270 "src/System/Path/Internal.hs" #-}
  ("      Posix.equalFilePath \"/tmp\" \"///tmp\"",
            Posix.equalFilePath "/tmp" "///tmp") :
  {-# LINE 1271 "src/System/Path/Internal.hs" #-}
  ("not $ Posix.equalFilePath \"abc\" \"def\"",
      not $ Posix.equalFilePath "abc" "def") :
  {-# LINE 1272 "src/System/Path/Internal.hs" #-}
  ("not $ Posix.equalFilePath \"/tmp\" \"tmp\"",
      not $ Posix.equalFilePath "/tmp" "tmp") :
  {-# LINE 1273 "src/System/Path/Internal.hs" #-}
  ("      Windows.equalFilePath \"abc\\\\def\" \"abc\\\\def\"",
            Windows.equalFilePath "abc\\def" "abc\\def") :
  {-# LINE 1274 "src/System/Path/Internal.hs" #-}
  ("      Windows.equalFilePath \"abc\\\\def\" \"abc\\\\\\\\def\"",
            Windows.equalFilePath "abc\\def" "abc\\\\def") :
  {-# LINE 1275 "src/System/Path/Internal.hs" #-}
  ("      Windows.equalFilePath \"file\" \"File\"",
            Windows.equalFilePath "file" "File") :
  {-# LINE 1276 "src/System/Path/Internal.hs" #-}
  ("      Windows.equalFilePath \"\\\\file\" \"\\\\\\\\file\"",
            Windows.equalFilePath "\\file" "\\\\file") :
  {-# LINE 1277 "src/System/Path/Internal.hs" #-}
  ("      Windows.equalFilePath \"\\\\file\" \"\\\\\\\\\\\\file\"",
            Windows.equalFilePath "\\file" "\\\\\\file") :
  {-# LINE 1278 "src/System/Path/Internal.hs" #-}
  ("not $ Windows.equalFilePath \"abc\" \"def\"",
      not $ Windows.equalFilePath "abc" "def") :
  {-# LINE 1279 "src/System/Path/Internal.hs" #-}
  ("not $ Windows.equalFilePath \"file\" \"dir\"",
      not $ Windows.equalFilePath "file" "dir") :
  {-# LINE 1292 "src/System/Path/Internal.hs" #-}
  ("Path.joinPath [\"tmp\",\"someDir\",\"dir\"] == Posix.relDir \"tmp/someDir/dir\"",
      Path.joinPath ["tmp","someDir","dir"] == Posix.relDir "tmp/someDir/dir") :
  {-# LINE 1293 "src/System/Path/Internal.hs" #-}
  ("Path.joinPath [\"tmp\",\"someDir\",\"file.txt\"] == Posix.relFile \"tmp/someDir/file.txt\"",
      Path.joinPath ["tmp","someDir","file.txt"] == Posix.relFile "tmp/someDir/file.txt") :
  {-# LINE 1299 "src/System/Path/Internal.hs" #-}
  ("Path.normalise (absFile \"/tmp/fred/./jim/./file\") == Posix.absFile \"/tmp/fred/jim/file\"",
      Path.normalise (absFile "/tmp/fred/./jim/./file") == Posix.absFile "/tmp/fred/jim/file") :
  {-# LINE 1305 "src/System/Path/Internal.hs" #-}
  ("Path.splitPath (Posix.absDir \"/tmp/someDir/mydir.dir\") == (True, map relDir [\"tmp\",\"someDir\",\"mydir.dir\"], Nothing)",
      Path.splitPath (Posix.absDir "/tmp/someDir/mydir.dir") == (True, map relDir ["tmp","someDir","mydir.dir"], Nothing)) :
  {-# LINE 1306 "src/System/Path/Internal.hs" #-}
  ("Path.splitPath (Posix.absFile \"/tmp/someDir/myfile.txt\") == (True, map relDir [\"tmp\",\"someDir\"], Just $ relFile \"myfile.txt\")",
      Path.splitPath (Posix.absFile "/tmp/someDir/myfile.txt") == (True, map relDir ["tmp","someDir"], Just $ relFile "myfile.txt")) :
  {-# LINE 1325 "src/System/Path/Internal.hs" #-}
  ("Path.makeRelative (absDir \"/tmp/somedir\") (absFile \"/tmp/somedir/anotherdir/file.txt\") == Posix.relFile \"anotherdir/file.txt\"",
      Path.makeRelative (absDir "/tmp/somedir") (absFile "/tmp/somedir/anotherdir/file.txt") == Posix.relFile "anotherdir/file.txt") :
  {-# LINE 1326 "src/System/Path/Internal.hs" #-}
  ("Path.makeRelative (absDir \"/tmp/somedir\") (absDir \"/tmp/somedir/anotherdir/dir\") == Posix.relDir \"anotherdir/dir\"",
      Path.makeRelative (absDir "/tmp/somedir") (absDir "/tmp/somedir/anotherdir/dir") == Posix.relDir "anotherdir/dir") :
  {-# LINE 1327 "src/System/Path/Internal.hs" #-}
  ("Path.makeRelative (absDir \"c:\\\\tmp\\\\somedir\") (absFile \"C:\\\\Tmp\\\\SomeDir\\\\AnotherDir\\\\File.txt\") == Windows.relFile \"AnotherDir\\\\File.txt\"",
      Path.makeRelative (absDir "c:\\tmp\\somedir") (absFile "C:\\Tmp\\SomeDir\\AnotherDir\\File.txt") == Windows.relFile "AnotherDir\\File.txt") :
  {-# LINE 1328 "src/System/Path/Internal.hs" #-}
  ("Path.makeRelative (absDir \"c:\\\\tmp\\\\somedir\") (absDir \"c:\\\\tmp\\\\somedir\\\\anotherdir\\\\dir\") == Windows.relDir \"anotherdir\\\\dir\"",
      Path.makeRelative (absDir "c:\\tmp\\somedir") (absDir "c:\\tmp\\somedir\\anotherdir\\dir") == Windows.relDir "anotherdir\\dir") :
  {-# LINE 1329 "src/System/Path/Internal.hs" #-}
  ("Path.makeRelative (absDir \"c:tmp\\\\somedir\") (absDir \"c:tmp\\\\somedir\\\\anotherdir\\\\dir\") == Windows.relDir \"anotherdir\\\\dir\"",
      Path.makeRelative (absDir "c:tmp\\somedir") (absDir "c:tmp\\somedir\\anotherdir\\dir") == Windows.relDir "anotherdir\\dir") :
  {-# LINE 1340 "src/System/Path/Internal.hs" #-}
  ("Path.makeRelativeMaybe (Posix.absDir \"/tmp/somedir\") (absFile \"/tmp/anotherdir/file.txt\") == Nothing",
      Path.makeRelativeMaybe (Posix.absDir "/tmp/somedir") (absFile "/tmp/anotherdir/file.txt") == Nothing) :
  {-# LINE 1341 "src/System/Path/Internal.hs" #-}
  ("Path.makeRelativeMaybe (Posix.absDir \"/Tmp\") (absFile \"/tmp/anotherdir/file.txt\") == Nothing",
      Path.makeRelativeMaybe (Posix.absDir "/Tmp") (absFile "/tmp/anotherdir/file.txt") == Nothing) :
  {-# LINE 1342 "src/System/Path/Internal.hs" #-}
  ("Path.makeRelativeMaybe (Windows.absDir \"\\\\Tmp\") (absFile \"\\\\tmp\\\\anotherdir\\\\file.txt\") == Just (relFile \"anotherdir\\\\file.txt\")",
      Path.makeRelativeMaybe (Windows.absDir "\\Tmp") (absFile "\\tmp\\anotherdir\\file.txt") == Just (relFile "anotherdir\\file.txt")) :
  {-# LINE 1356 "src/System/Path/Internal.hs" #-}
  ("Path.makeAbsolute (absDir \"/tmp\") (relFile \"file.txt\")      == Posix.absFile \"/tmp/file.txt\"",
      Path.makeAbsolute (absDir "/tmp") (relFile "file.txt")      == Posix.absFile "/tmp/file.txt") :
  {-# LINE 1357 "src/System/Path/Internal.hs" #-}
  ("Path.makeAbsolute (absDir \"/tmp\") (relFile \"adir/file.txt\") == Posix.absFile \"/tmp/adir/file.txt\"",
      Path.makeAbsolute (absDir "/tmp") (relFile "adir/file.txt") == Posix.absFile "/tmp/adir/file.txt") :
  {-# LINE 1358 "src/System/Path/Internal.hs" #-}
  ("Path.makeAbsolute (absDir \"/tmp\") (relDir  \"adir/dir\")      == Posix.absDir \"/tmp/adir/dir\"",
      Path.makeAbsolute (absDir "/tmp") (relDir  "adir/dir")      == Posix.absDir "/tmp/adir/dir") :
  {-# LINE 1380 "src/System/Path/Internal.hs" #-}
  ("Path.genericMakeAbsolute (absDir \"/tmp\") (relFile \"file.txt\")       == Posix.absFile \"/tmp/file.txt\"",
      Path.genericMakeAbsolute (absDir "/tmp") (relFile "file.txt")       == Posix.absFile "/tmp/file.txt") :
  {-# LINE 1381 "src/System/Path/Internal.hs" #-}
  ("Path.genericMakeAbsolute (absDir \"/tmp\") (relFile \"adir/file.txt\")  == Posix.absFile \"/tmp/adir/file.txt\"",
      Path.genericMakeAbsolute (absDir "/tmp") (relFile "adir/file.txt")  == Posix.absFile "/tmp/adir/file.txt") :
  {-# LINE 1382 "src/System/Path/Internal.hs" #-}
  ("Path.genericMakeAbsolute (absDir \"/tmp\") (absFile \"/adir/file.txt\") == Posix.absFile \"/adir/file.txt\"",
      Path.genericMakeAbsolute (absDir "/tmp") (absFile "/adir/file.txt") == Posix.absFile "/adir/file.txt") :
  {-# LINE 1467 "src/System/Path/Internal.hs" #-}
  ("Path.isAbsolute (Posix.absFile \"/fred\")",
      Path.isAbsolute (Posix.absFile "/fred")) :
  {-# LINE 1468 "src/System/Path/Internal.hs" #-}
  ("Path.isAbsolute (Windows.absFile \"\\\\fred\")",
      Path.isAbsolute (Windows.absFile "\\fred")) :
  {-# LINE 1469 "src/System/Path/Internal.hs" #-}
  ("Path.isAbsolute (Windows.absFile \"c:\\\\fred\")",
      Path.isAbsolute (Windows.absFile "c:\\fred")) :
  {-# LINE 1470 "src/System/Path/Internal.hs" #-}
  ("Path.isAbsolute (Windows.absFile \"c:fred\")",
      Path.isAbsolute (Windows.absFile "c:fred")) :
  {-# LINE 1477 "src/System/Path/Internal.hs" #-}
  ("Path.isRelative (Posix.relFile \"fred\")",
      Path.isRelative (Posix.relFile "fred")) :
  {-# LINE 1478 "src/System/Path/Internal.hs" #-}
  ("Path.isRelative (Windows.relFile \"fred\")",
      Path.isRelative (Windows.relFile "fred")) :
  {-# LINE 1503 "src/System/Path/Internal.hs" #-}
  ("null (Path.takeExtension x) == not (Path.hasAnExtension x)",
      null (Path.takeExtension x) == not (Path.hasAnExtension x)) :
  {-# LINE 1509 "src/System/Path/Internal.hs" #-}
  ("Path.hasExtension \".hs\" (Posix.relFile \"MyCode.hs\")",
      Path.hasExtension ".hs" (Posix.relFile "MyCode.hs")) :
  {-# LINE 1510 "src/System/Path/Internal.hs" #-}
  ("Path.hasExtension \".hs\" (Posix.relFile \"MyCode.bak.hs\")",
      Path.hasExtension ".hs" (Posix.relFile "MyCode.bak.hs")) :
  {-# LINE 1511 "src/System/Path/Internal.hs" #-}
  ("not $ Path.hasExtension \".hs\" (Posix.relFile \"MyCode.hs.bak\")",
      not $ Path.hasExtension ".hs" (Posix.relFile "MyCode.hs.bak")) :
  {-# LINE 1521 "src/System/Path/Internal.hs" #-}
  ("Posix.extSeparator == '.'",
      Posix.extSeparator == '.') :
  {-# LINE 1532 "src/System/Path/Internal.hs" #-}
  ("Posix.isExtSeparator a == (a == Posix.extSeparator)",
      Posix.isExtSeparator a == (a == Posix.extSeparator)) :
  {-# LINE 1538 "src/System/Path/Internal.hs" #-}
  ("Posix.isSearchPathSeparator a == (a == Posix.searchPathSeparator)",
      Posix.isSearchPathSeparator a == (a == Posix.searchPathSeparator)) :
  {-# LINE 1554 "src/System/Path/Internal.hs" #-}
  ("Path.genericAddExtension (absDir \"/\") \"x\" == Posix.absDir \"/.x\"",
      Path.genericAddExtension (absDir "/") "x" == Posix.absDir "/.x") :
  {-# LINE 1555 "src/System/Path/Internal.hs" #-}
  ("Path.genericAddExtension (absDir \"/a\") \"x\" == Posix.absDir \"/a.x\"",
      Path.genericAddExtension (absDir "/a") "x" == Posix.absDir "/a.x") :
  {-# LINE 1556 "src/System/Path/Internal.hs" #-}
  ("Path.genericAddExtension Path.emptyFile \"x\" == Posix.relFile \".x\"",
      Path.genericAddExtension Path.emptyFile "x" == Posix.relFile ".x") :
  {-# LINE 1557 "src/System/Path/Internal.hs" #-}
  ("Path.genericAddExtension Path.emptyFile \"\" == Posix.emptyFile",
      Path.genericAddExtension Path.emptyFile "" == Posix.emptyFile) :
  {-# LINE 1695 "src/System/Path/Internal.hs" #-}
  ("Posix.isPathSeparator Posix.pathSeparator",
          Posix.isPathSeparator Posix.pathSeparator) :
  {-# LINE 1700 "src/System/Path/Internal.hs" #-}
  ("Posix.pathSeparator `elem` Posix.pathSeparators",
          Posix.pathSeparator `elem` Posix.pathSeparators) :
  {-# LINE 1707 "src/System/Path/Internal.hs" #-}
  ("Posix.isPathSeparator a == (a `elem` Posix.pathSeparators)",
          Posix.isPathSeparator a == (a `elem` Posix.pathSeparators)) :
  []