Cleanup errors and logging a bit

This commit is contained in:
Daniel Gröber
2015-03-04 21:48:21 +01:00
parent bc71877dcf
commit f0ea445a9b
41 changed files with 242 additions and 456 deletions

View File

@@ -1,39 +1,17 @@
{-# LANGUAGE ScopedTypeVariables #-}
module MonadSpec where
import Test.Hspec
import Dir
import TestUtils
import Control.Applicative
import Control.Exception
import Control.Monad.Error.Class
spec :: Spec
spec = do
describe "When using GhcModT in a do block" $
it "a pattern match failure causes a call to `fail` on ErrorT in the monad stack" $ do
(a, _)
(a, _h)
<- runGhcModT defaultOptions $
do
Just _ <- return Nothing
return "hello"
`catchError` (const $ fail "oh noes")
a `shouldBe` (Left $ GMEString "oh noes")
describe "runGhcModT" $
it "complains if the cabal file fails to parse while a sandbox is present" $ withDirectory_ "test/data/broken-cabal" $ do
shouldReturnError $ runD' (gmCradle <$> ask)
describe "gmsGet/Put" $
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 ""