[commit: ghc] master: fixup! Turn on MonadFail desugaring by default (e55d471)

git at git.haskell.org git at git.haskell.org
Tue Aug 7 19:55:42 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/e55d47128b3f0303d4468c879727683ec29fd02c/ghc

>---------------------------------------------------------------

commit e55d47128b3f0303d4468c879727683ec29fd02c
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Aug 7 15:54:10 2018 -0400

    fixup! Turn on MonadFail desugaring by default


>---------------------------------------------------------------

e55d47128b3f0303d4468c879727683ec29fd02c
 testsuite/tests/annotations/should_run/annrun01.hs | 3 ++-
 1 file changed, 2 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/annotations/should_run/annrun01.hs b/testsuite/tests/annotations/should_run/annrun01.hs
index 0dbd44d..9030a39 100644
--- a/testsuite/tests/annotations/should_run/annrun01.hs
+++ b/testsuite/tests/annotations/should_run/annrun01.hs
@@ -4,6 +4,7 @@ module Main where
 
 import GHC
 import MonadUtils  ( liftIO )
+import Data.Maybe
 import DynFlags    ( defaultFatalMessager, defaultFlushOut )
 import Annotations ( AnnTarget(..), CoreAnnTarget )
 import GHC.Serialized  ( deserializeWithData )
@@ -34,7 +35,7 @@ main = defaultErrorHandler defaultFatalMessager defaultFlushOut
     liftIO $ putStrLn "Finding Module"
     mod <- findModule mod_nm Nothing
     liftIO $ putStrLn "Getting Module Info"
-    Just mod_info <- getModuleInfo mod
+    mod_info <- fromJust <$> getModuleInfo mod
 
     liftIO $ putStrLn "Showing Details For Module"
     showTargetAnns (ModuleTarget mod)



More information about the ghc-commits mailing list