[commit: ghc] master: Remove LANGUAGE pragrams implied by Haskell2010 (88c0870)

git at git.haskell.org git at git.haskell.org
Wed May 14 09:19:12 UTC 2014


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

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

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

commit 88c0870b44a3854bc6608055e7ef84da17324830
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Wed May 14 09:31:57 2014 +0200

    Remove LANGUAGE pragrams implied by Haskell2010
    
    Haskell2010 implies (at least) EmptyDataDecls, ForeignFunctionInterface,
    PatternGuards, DoAndIfThenElse, and RelaxedPolyRec.
    
    This is a follow-up to dd92e2179e3171a0630834b773c08d416101980d
    
    Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>


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

88c0870b44a3854bc6608055e7ef84da17324830
 compiler/cmm/Hoopl/Dataflow.hs               | 2 +-
 distrib/compare/Makefile                     | 2 +-
 distrib/compare/compare.hs                   | 2 --
 ghc/Main.hs                                  | 1 -
 libraries/integer-simple/GHC/Integer/Type.hs | 3 +--
 utils/checkUniques/Makefile                  | 2 +-
 utils/checkUniques/checkUniques.hs           | 2 --
 utils/dll-split/Main.hs                      | 3 ---
 utils/ghc-pkg/Main.hs                        | 2 +-
 utils/ghctags/Main.hs                        | 2 +-
 utils/runghc/runghc.hs                       | 2 +-
 11 files changed, 7 insertions(+), 16 deletions(-)

diff --git a/compiler/cmm/Hoopl/Dataflow.hs b/compiler/cmm/Hoopl/Dataflow.hs
index 78b930a..7105195 100644
--- a/compiler/cmm/Hoopl/Dataflow.hs
+++ b/compiler/cmm/Hoopl/Dataflow.hs
@@ -9,7 +9,7 @@
 -- specialised to the UniqSM monad.
 --
 
-{-# LANGUAGE RankNTypes, ScopedTypeVariables, GADTs, EmptyDataDecls, PatternGuards, TypeFamilies, MultiParamTypeClasses #-}
+{-# LANGUAGE RankNTypes, ScopedTypeVariables, GADTs, TypeFamilies, MultiParamTypeClasses #-}
 {-# OPTIONS_GHC -fprof-auto-top #-}
 {-# LANGUAGE Trustworthy #-}
 
diff --git a/distrib/compare/Makefile b/distrib/compare/Makefile
index f65c041..4964578 100644
--- a/distrib/compare/Makefile
+++ b/distrib/compare/Makefile
@@ -2,7 +2,7 @@
 GHC = ghc
 
 compare: *.hs
-	"$(GHC)" -O --make -Wall -Werror $@
+	"$(GHC)" -O -XHaskell2010 --make -Wall -Werror $@
 
 .PHONY: clean
 clean:
diff --git a/distrib/compare/compare.hs b/distrib/compare/compare.hs
index 81055c2..8653e3f 100644
--- a/distrib/compare/compare.hs
+++ b/distrib/compare/compare.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE PatternGuards #-}
-
 module Main (main) where
 
 import Control.Monad.State
diff --git a/ghc/Main.hs b/ghc/Main.hs
index d056bf9..fcb9bd1 100644
--- a/ghc/Main.hs
+++ b/ghc/Main.hs
@@ -1,5 +1,4 @@
 {-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
-{-# LANGUAGE ForeignFunctionInterface #-}
 
 -----------------------------------------------------------------------------
 --
diff --git a/libraries/integer-simple/GHC/Integer/Type.hs b/libraries/integer-simple/GHC/Integer/Type.hs
index 5deecd2..cd39b7d 100644
--- a/libraries/integer-simple/GHC/Integer/Type.hs
+++ b/libraries/integer-simple/GHC/Integer/Type.hs
@@ -1,6 +1,5 @@
 
-{-# LANGUAGE CPP, MagicHash, ForeignFunctionInterface,
-             NoImplicitPrelude, BangPatterns, UnboxedTuples,
+{-# LANGUAGE CPP, MagicHash, NoImplicitPrelude, BangPatterns, UnboxedTuples,
              UnliftedFFITypes #-}
 
 -- Commentary of Integer library is located on the wiki:
diff --git a/utils/checkUniques/Makefile b/utils/checkUniques/Makefile
index a7b2df1..b017473 100644
--- a/utils/checkUniques/Makefile
+++ b/utils/checkUniques/Makefile
@@ -13,4 +13,4 @@ check: checkUniques
 	./checkUniques mkPreludeMiscIdUnique  $(PREL_NAMES) $(DS_META)
 
 checkUniques: checkUniques.hs
-	$(GHC) --make $@
+	$(GHC) -O -XHaskell2010 --make $@
diff --git a/utils/checkUniques/checkUniques.hs b/utils/checkUniques/checkUniques.hs
index d8858de..2eda188 100644
--- a/utils/checkUniques/checkUniques.hs
+++ b/utils/checkUniques/checkUniques.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE PatternGuards #-}
-
 -- Some things could be improved, e.g.:
 -- * Check that each file given contains at least one instance of the
 --   function
diff --git a/utils/dll-split/Main.hs b/utils/dll-split/Main.hs
index c0e3706..c3f5a15 100644
--- a/utils/dll-split/Main.hs
+++ b/utils/dll-split/Main.hs
@@ -1,6 +1,3 @@
-
-{-# LANGUAGE PatternGuards #-}
-
 module Main (main) where
 
 import Control.Monad
diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs
index 30acbe2..6bac88b 100644
--- a/utils/ghc-pkg/Main.hs
+++ b/utils/ghc-pkg/Main.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards, CPP, ForeignFunctionInterface #-}
+{-# LANGUAGE CPP #-}
 -----------------------------------------------------------------------------
 --
 -- (c) The University of Glasgow 2004-2009.
diff --git a/utils/ghctags/Main.hs b/utils/ghctags/Main.hs
index a67891e..815cc7c 100644
--- a/utils/ghctags/Main.hs
+++ b/utils/ghctags/Main.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE PatternGuards, ScopedTypeVariables #-}
+{-# LANGUAGE ScopedTypeVariables #-}
 module Main where
 
 import Prelude hiding ( mod, id, mapM )
diff --git a/utils/runghc/runghc.hs b/utils/runghc/runghc.hs
index 5280cb3..47a6bc5 100644
--- a/utils/runghc/runghc.hs
+++ b/utils/runghc/runghc.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, ForeignFunctionInterface #-}
+{-# LANGUAGE CPP #-}
 #include "ghcconfig.h"
 -----------------------------------------------------------------------------
 --



More information about the ghc-commits mailing list