[commit: ghc] master: base: Drop obsolete/redundant `__GLASGOW_HASKELL__` checks (b10a7a4)

git at git.haskell.org git at git.haskell.org
Sat Sep 13 08:50:23 UTC 2014


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

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

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

commit b10a7a412738e16d332917b22ee1037383b81eb7
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Sep 13 10:44:20 2014 +0200

    base: Drop obsolete/redundant `__GLASGOW_HASKELL__` checks
    
    Since 527bcc41630918977c7 we require GHC >=7.6 for bootstrapping anyway.
    This also allows to avoid the CPP-processing overhead for these two modules.


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

b10a7a412738e16d332917b22ee1037383b81eb7
 libraries/base/Control/Category.hs |  7 ++-----
 libraries/base/Text/Printf.hs      | 22 +---------------------
 2 files changed, 3 insertions(+), 26 deletions(-)

diff --git a/libraries/base/Control/Category.hs b/libraries/base/Control/Category.hs
index 35875c9..3b8dc2b 100644
--- a/libraries/base/Control/Category.hs
+++ b/libraries/base/Control/Category.hs
@@ -1,9 +1,6 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP #-}
-
-#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706
-{-# LANGUAGE PolyKinds, GADTs #-}
-#endif
 
 -----------------------------------------------------------------------------
 -- |
diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs
index ec68edb..a92a1a4 100644
--- a/libraries/base/Text/Printf.hs
+++ b/libraries/base/Text/Printf.hs
@@ -1,8 +1,5 @@
-{-# LANGUAGE Safe #-}
-{-# LANGUAGE CPP #-}
-#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >=  700
 {-# LANGUAGE GADTs #-}
-#endif
+{-# LANGUAGE Safe #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -292,8 +289,6 @@ instance (IsChar c) => PrintfType [c] where
 -- type system won't readily let us say that without
 -- bringing the GADTs. So we go conditional for these defs.
 
-#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >=  700
-
 instance (a ~ ()) => PrintfType (IO a) where
     spr fmts args =
         putStr $ map fromChar $ uprintf fmts $ reverse args
@@ -302,21 +297,6 @@ instance (a ~ ()) => HPrintfType (IO a) where
     hspr hdl fmts args = do
         hPutStr hdl (uprintf fmts (reverse args))
 
-#else
-
-instance PrintfType (IO a) where
-    spr fmts args = do
-        putStr $ map fromChar $ uprintf fmts $ reverse args
-        return (error "PrintfType (IO a): result should not be used.")
-
-instance HPrintfType (IO a) where
-    hspr hdl fmts args = do
-        hPutStr hdl (uprintf fmts (reverse args))
-        return (error "HPrintfType (IO a): result should not be used.")
-
-#endif
-
-
 instance (PrintfArg a, PrintfType r) => PrintfType (a -> r) where
     spr fmts args = \ a -> spr fmts
                              ((parseFormat a, formatArg a) : args)



More information about the ghc-commits mailing list