From 88c0870b44a3854bc6608055e7ef84da17324830 Mon Sep 17 00:00:00 2001 From: Herbert Valerio Riedel Date: Wed, 14 May 2014 09:31:57 +0200 Subject: [PATCH] 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 --- 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 78b930a20f7e..7105195d3ce7 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 f65c0419eb77..49645783e20b 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 81055c2826d9..8653e3f6aa2d 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 d056bf97c49b..fcb9bd15a112 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 5deecd29bb2c..cd39b7d6bd24 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 a7b2df17e2de..b017473da323 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 d8858dee261b..2eda188e3c76 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 c0e370641c56..c3f5a15a4a31 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 30acbe2eb811..6bac88b379a6 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 a67891e16a2c..815cc7ca1854 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 5280cb3344d2..47a6bc57d57b 100644 --- a/utils/runghc/runghc.hs +++ b/utils/runghc/runghc.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, ForeignFunctionInterface #-} +{-# LANGUAGE CPP #-} #include "ghcconfig.h" ----------------------------------------------------------------------------- --