Give readProcess' more sensible error messages.

Also a bunch of refactoring for GhcModError
This commit is contained in:
Daniel Gröber
2014-08-28 11:54:01 +02:00
parent a7f00931c5
commit a0ae09a3e6
18 changed files with 161 additions and 101 deletions

View File

@@ -2,10 +2,11 @@ module FindSpec where
import Language.Haskell.GhcMod.Find
import Test.Hspec
import TestUtils
spec :: Spec
spec = do
describe "db <- loadSymbolDb" $ do
it "lookupSymbol' db \"head\" contains at least `Data.List'" $ do
db <- loadSymbolDb
db <- runD loadSymbolDb
lookupSym "head" db `shouldContain` ["Data.List"]

View File

@@ -5,6 +5,7 @@ import Test.Hspec
import Dir
import TestUtils
import Control.Applicative
import Control.Exception
import Control.Monad.Error.Class
spec :: Spec
@@ -27,3 +28,12 @@ spec = do
it "work" $ do
(runD $ gmsPut (GhcModState Intelligent) >> gmsGet)
`shouldReturn` (GhcModState Intelligent)
describe "liftIO" $ do
it "converts user errors to GhcModError" $ do
shouldReturnError $
runD' $ liftIO $ throw (userError "hello") >> return ""
it "converts a file not found exception to GhcModError" $ do
shouldReturnError $
runD' $ liftIO $ readFile "/DOES_NOT_EXIST" >> return ""

View File

@@ -1,7 +1,7 @@
module UtilsSpec where
import Language.Haskell.GhcMod.Error
import Language.Haskell.GhcMod.Utils
import Control.Exception
import TestUtils
import Test.Hspec
@@ -15,7 +15,9 @@ spec = do
describe "liftMonadError" $ do
it "converts IOErrors to GhcModError" $ do
shouldReturnError $
runD' $ liftIOExceptions $ throw (userError "hello") >> return ""
runD' $ liftIO $ throw (userError "hello") >> return ""
shouldReturnError $
runD' $ liftIOExceptions $ readFile "/DOES_NOT_EXIST" >> return ""
runD' $ liftIO $ readFile "/DOES_NOT_EXIST" >> return ""
-- readProcessWithExitCode cmd opts ""