Commit 33dcfcc9 authored by Andrew Gibiansky's avatar Andrew Gibiansky

Make test suite not use system-filepath

parent 36de4c2b
{-# LANGUAGE QuasiQuotes, OverloadedStrings, ExtendedDefaultRules, CPP #-} {-# LANGUAGE QuasiQuotes, OverloadedStrings, ExtendedDefaultRules, CPP #-}
-- Keep all the language pragmas here so it can be compiled separately. -- Keep all the language pragmas here so it can be compiled separately.
module Main where module Main where
import Prelude import Prelude
import GHC hiding (Qualified) import GHC hiding (Qualified)
import GHC.Paths import GHC.Paths
import Data.IORef import Data.IORef
import Control.Monad import Control.Monad
import Control.Monad.IO.Class ( MonadIO, liftIO ) import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.List import Data.List
import System.Directory import System.Directory
import Shelly (Sh, shelly, cmd, (</>), toTextIgnore, cd, withTmpDir, mkdir_p, import Shelly (Sh, shelly, cmd, (</>), toTextIgnore, cd, withTmpDir, mkdir_p, touchfile,
touchfile) fromText)
import qualified Data.Text as T
import qualified Shelly import qualified Shelly
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import Filesystem.Path.CurrentOS (encodeString) import System.SetEnv (setEnv)
import System.SetEnv (setEnv) import Data.String.Here
import Data.String.Here import Data.String.Utils (strip, replace)
import Data.String.Utils (strip, replace) import Data.Monoid
import Data.Monoid
import IHaskell.Eval.Parser
import IHaskell.Eval.Parser import IHaskell.Types
import IHaskell.Types import IHaskell.IPython
import IHaskell.IPython import IHaskell.Eval.Evaluate as Eval hiding (liftIO)
import IHaskell.Eval.Evaluate as Eval hiding (liftIO)
import qualified IHaskell.Eval.Evaluate as Eval (liftIO) import qualified IHaskell.Eval.Evaluate as Eval (liftIO)
import IHaskell.Eval.Completion import IHaskell.Eval.Completion
import IHaskell.Eval.ParseShell import IHaskell.Eval.ParseShell
import Debug.Trace import Debug.Trace
import Test.Hspec import Test.Hspec
import Test.Hspec.HUnit import Test.Hspec.HUnit
import Test.HUnit (assertBool, assertFailure) import Test.HUnit (assertBool, assertFailure)
traceShowId x = traceShow x x traceShowId x = traceShow x x
...@@ -166,7 +166,7 @@ inDirectory dirs files action = shelly $ withTmpDir $ \dirPath -> ...@@ -166,7 +166,7 @@ inDirectory dirs files action = shelly $ withTmpDir $ \dirPath ->
do cd dirPath do cd dirPath
mapM_ mkdir_p dirs mapM_ mkdir_p dirs
mapM_ touchfile files mapM_ touchfile files
liftIO $ doGhc $ wrap (encodeString dirPath) (action dirPath) liftIO $ doGhc $ wrap (T.unpack $ toTextIgnore dirPath) (action dirPath)
where cdEvent path = liftIO $ setCurrentDirectory path --Eval.evaluate defaultKernelState (":! cd " ++ path) noPublish where cdEvent path = liftIO $ setCurrentDirectory path --Eval.evaluate defaultKernelState (":! cd " ++ path) noPublish
wrap :: FilePath -> Interpreter a -> Interpreter a wrap :: FilePath -> Interpreter a -> Interpreter a
wrap path action = wrap path action =
...@@ -241,8 +241,8 @@ completionTests = do ...@@ -241,8 +241,8 @@ completionTests = do
"import Prel*" `completionHas` ["Prelude"] "import Prel*" `completionHas` ["Prelude"]
it "properly completes haskell file paths on :load directive" $ it "properly completes haskell file paths on :load directive" $
let loading xs = ":load " ++ encodeString xs let loading xs = ":load " ++ T.unpack (toTextIgnore xs)
paths = map encodeString paths = map (T.unpack . toTextIgnore)
in do in do
loading ("dir" </> "file*") `shouldHaveCompletionsInDirectory` paths ["dir" </> "file2.hs", loading ("dir" </> "file*") `shouldHaveCompletionsInDirectory` paths ["dir" </> "file2.hs",
"dir" </> "file2.lhs"] "dir" </> "file2.lhs"]
...@@ -258,7 +258,7 @@ completionTests = do ...@@ -258,7 +258,7 @@ completionTests = do
, "./" </> "file1.lhs"] , "./" </> "file1.lhs"]
it "provides path completions on empty shell cmds " $ it "provides path completions on empty shell cmds " $
":! cd *" `shouldHaveCompletionsInDirectory` map encodeString ["" </> "dir/" ":! cd *" `shouldHaveCompletionsInDirectory` map (T.unpack . toTextIgnore) ["" </> "dir/"
, "" </> "file1.hs" , "" </> "file1.hs"
, "" </> "file1.lhs"] , "" </> "file1.lhs"]
...@@ -268,7 +268,7 @@ completionTests = do ...@@ -268,7 +268,7 @@ completionTests = do
result <- action result <- action
setHomeEvent $ Shelly.fromText home setHomeEvent $ Shelly.fromText home
return result return result
setHomeEvent path = liftIO $ setEnv "HOME" (encodeString path) setHomeEvent path = liftIO $ setEnv "HOME" (T.unpack $ toTextIgnore path)
it "correctly interprets ~ as the environment HOME variable" $ it "correctly interprets ~ as the environment HOME variable" $
let shouldHaveCompletions :: String -> [String] -> IO () let shouldHaveCompletions :: String -> [String] -> IO ()
...@@ -289,7 +289,7 @@ completionTests = do ...@@ -289,7 +289,7 @@ completionTests = do
matchText <- withHsHome $ fst <$> uncurry complete (readCompletePrompt string) matchText <- withHsHome $ fst <$> uncurry complete (readCompletePrompt string)
matchText `shouldBe` expected matchText `shouldBe` expected
setHomeEvent path = liftIO $ setEnv "HOME" (encodeString path) setHomeEvent path = liftIO $ setEnv "HOME" (T.unpack $ toTextIgnore path)
it "generates the correct matchingText on `:! cd ~/*` " $ it "generates the correct matchingText on `:! cd ~/*` " $
do ":! cd ~/*" `shouldHaveMatchingText` ("~/" :: String) do ":! cd ~/*" `shouldHaveMatchingText` ("~/" :: String)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment