Skip to content
Snippets Groups Projects
Commit 58edf9f5 authored by Yuji Yamamoto's avatar Yuji Yamamoto Committed by Alex Biehl
Browse files

Fix test failures on Windows (#564)

* Ignore .stack-work

* Fix for windows: use nul instead of /dev/null

* Fix for windows: canonicalize line separator

* Also normalize osx line endings
parent a330da52
No related branches found
No related tags found
5 merge requests!38Make --no-tmp-comp-dir the default,!37Adapt to latest xhtml version, various optimizations,!31Support HsToken in DataDecl and ClassDecl,!12Drop orphan instance when defined upstream.,!10Haddock interfaces produced from `.hi` files
......@@ -21,3 +21,5 @@ TAGS
.cabal-sandbox
cabal.sandbox.config
.stack-work/
......@@ -21,8 +21,8 @@ library
exposed-modules:
Test.Haddock
Test.Haddock.Config
Test.Haddock.Utils
Test.Haddock.Xhtml
other-modules:
Test.Haddock.Process
Test.Haddock.Utils
......@@ -193,7 +193,7 @@ loadConfig ccfg dcfg flags files = do
, baseDependencies ghcPath
]
let cfgHaddockStdOut = fromMaybe "/dev/null" (flagsHaddockStdOut flags)
let cfgHaddockStdOut = fromMaybe defaultStdOut (flagsHaddockStdOut flags)
cfgDiffTool <- if FlagNoDiff `elem` flags
then pure Nothing
......@@ -256,6 +256,14 @@ defaultDiffTool =
isAvailable = liftM isJust . findProgramLocation silent
defaultStdOut :: FilePath
#ifdef mingw32_HOST_OS
defaultStdOut = "nul"
#else
defaultStdOut = "/dev/null"
#endif
processFileArgs :: DirConfig -> [String] -> IO [TestPackage]
processFileArgs dcfg [] =
processFileArgs' dcfg . filter isValidEntry =<< getDirectoryContents srcDir
......
......@@ -48,3 +48,10 @@ copyFile' :: FilePath -> FilePath -> IO ()
copyFile' old new = do
createDirectoryIfMissing True $ takeDirectory new
copyFile old new
crlfToLf :: String -> String
crlfToLf "" = ""
crlfToLf ('\r' : '\n' : rest) = '\n' : crlfToLf rest
crlfToLf ('\r' : rest) = '\n' : crlfToLf rest
crlfToLf (other : rest) = other : crlfToLf rest
{-# LANGUAGE CPP #-}
import Data.Function
import System.Environment
import System.FilePath
import Test.Haddock
import Test.Haddock.Utils
checkConfig :: CheckConfig String
......@@ -12,7 +14,7 @@ checkConfig = CheckConfig
{ ccfgRead = Just
, ccfgClean = \_ -> id
, ccfgDump = id
, ccfgEqual = (==)
, ccfgEqual = (==) `on` crlfToLf
}
......
{-# LANGUAGE CPP #-}
import Data.Function
import System.Environment
import System.FilePath
import Test.Haddock
import Test.Haddock.Utils
checkConfig :: CheckConfig String
......@@ -12,7 +14,7 @@ checkConfig = CheckConfig
{ ccfgRead = Just
, ccfgClean = \_ -> id
, ccfgDump = id
, ccfgEqual = (==)
, ccfgEqual = (==) `on` crlfToLf
}
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment