Skip to content

Commit

Permalink
Fix build on Windows (#2457)
Browse files Browse the repository at this point in the history
  • Loading branch information
Blaisorblade committed Aug 12, 2016
1 parent 81105cd commit ae88be8
Show file tree
Hide file tree
Showing 4 changed files with 33 additions and 10 deletions.
13 changes: 13 additions & 0 deletions src/test/Stack/Ghci/PortableFakePaths.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}

-- | Helpers for writing fake paths for test suite for the GhciScript DSL.
-- This must be a separate module because it is used in Teplate Haskell splices.
module Stack.Ghci.PortableFakePaths where

defaultDrive :: FilePath
#ifdef WINDOWS
defaultDrive = "C:\\"
#else
defaultDrive = "/"
#endif
18 changes: 12 additions & 6 deletions src/test/Stack/Ghci/ScriptSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,10 @@ import Data.Monoid
import qualified Data.Set as S
import Distribution.ModuleName
import Test.Hspec
import qualified System.FilePath as FP
import Stack.Ghci.PortableFakePaths
import Path
import Path.Extra (pathToLazyByteString)

import Stack.Ghci.Script

Expand All @@ -20,10 +23,11 @@ spec = do

describe "script" $ do
it "should seperate commands with a newline" $ do
let script = cmdCdGhc $(mkAbsDir "/src/package-a")
let dir = $(mkAbsDir $ defaultDrive FP.</> "src" FP.</> "package-a")
script = cmdCdGhc dir
<> cmdAdd [fromString "Lib.A"]
scriptToLazyByteString script `shouldBe`
":cd-ghc /src/package-a/\n:add Lib.A\n"
":cd-ghc " <> pathToLazyByteString dir <> "\n:add Lib.A\n"

describe ":add" $ do
it "should not render empty add commands" $ do
Expand All @@ -36,15 +40,17 @@ spec = do

describe ":add (by file)" $ do
it "should render a full file path" $ do
let script = cmdAddFile $(mkAbsFile "/Users/someone/src/project/package-a/src/Main.hs")
let file = $(mkAbsFile $ defaultDrive FP.</> "Users" FP.</> "someone" FP.</> "src" FP.</> "project" FP.</> "package-a" FP.</> "src" FP.</> "Main.hs")
script = cmdAddFile file
scriptToLazyByteString script `shouldBe`
":add /Users/someone/src/project/package-a/src/Main.hs\n"
":add " <> pathToLazyByteString file <> "\n"

describe ":cd-ghc" $ do
it "should render a full absolute path" $ do
let script = cmdCdGhc $(mkAbsDir "/Users/someone/src/project/package-a")
let dir = $(mkAbsDir $ defaultDrive FP.</> "Users" FP.</> "someone" FP.</> "src" FP.</> "project" FP.</> "package-a")
script = cmdCdGhc dir
scriptToLazyByteString script `shouldBe`
":cd-ghc /Users/someone/src/project/package-a/\n"
":cd-ghc " <> pathToLazyByteString dir <> "\n"

describe ":module" $ do
it "should render empty module as ':module +'" $ do
Expand Down
11 changes: 7 additions & 4 deletions src/test/Stack/GhciSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,19 +18,22 @@ import Test.Hspec
import NeatInterpolation
import Path
import Path.Extra (pathToText)
import qualified System.FilePath as FP

import Stack.Ghci
import Stack.Ghci.Script (scriptToLazyByteString)
import Stack.Ghci.PortableFakePaths

textToLazy :: Text -> LBS.ByteString
textToLazy = LBS.fromStrict . T.encodeUtf8

projDirA, projDirB :: Path Abs Dir
projDirA = $(mkAbsDir "/Users/someone/src/project-a")
projDirB = $(mkAbsDir "/Users/someone/src/project-b")
baseProjDir, projDirA, projDirB :: Path Abs Dir
baseProjDir = $(mkAbsDir $ defaultDrive FP.</> "Users" FP.</> "someone" FP.</> "src")
projDirA = baseProjDir </> $(mkRelDir "project-a")
projDirB = baseProjDir </> $(mkRelDir "project-b")

relFile :: Path Rel File
relFile = $(mkRelFile "exe/Main.hs")
relFile = $(mkRelFile $ "exe" FP.</> "Main.hs")

absFile :: Path Abs File
absFile = projDirA </> relFile
Expand Down
1 change: 1 addition & 0 deletions stack.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -300,6 +300,7 @@ test-suite stack-test
, Stack.DotSpec
, Stack.GhciSpec
, Stack.Ghci.ScriptSpec
, Stack.Ghci.PortableFakePaths
, Stack.PackageDumpSpec
, Stack.ArgsSpec
, Stack.NixSpec
Expand Down

0 comments on commit ae88be8

Please sign in to comment.