ghc-mod/test/MonadSpec.hs

30 lines
1015 B
Haskell
Raw Normal View History

2014-08-11 21:42:16 +00:00
{-# LANGUAGE ScopedTypeVariables #-}
module MonadSpec where
import Test.Hspec
2014-08-11 21:42:16 +00:00
import Dir
2014-08-12 16:11:32 +00:00
import TestUtils
2014-08-11 21:42:16 +00:00
import Control.Applicative
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
2014-08-20 03:14:27 +00:00
(a, _)
<- runGhcModT defaultOptions $
do
2014-08-20 03:14:27 +00:00
Just _ <- return Nothing
return "hello"
`catchError` (const $ fail "oh noes")
a `shouldBe` (Left $ GMEString "oh noes")
2014-08-11 21:42:16 +00:00
describe "runGhcModT" $
it "complains if the cabal file fails to parse while a sandbox is present" $ withDirectory_ "test/data/broken-cabal" $ do
2014-08-12 16:11:32 +00:00
shouldReturnError $ runD' (gmCradle <$> ask)
2014-08-12 16:22:28 +00:00
describe "gmsGet/Put" $
it "work" $ do
(runD $ gmsPut (GhcModState Intelligent) >> gmsGet)
`shouldReturn` (GhcModState Intelligent)