Skip to content

Commit

Permalink
Remove LANGUAGE pragrams implied by Haskell2010
Browse files Browse the repository at this point in the history
Haskell2010 implies (at least) EmptyDataDecls, ForeignFunctionInterface,
PatternGuards, DoAndIfThenElse, and RelaxedPolyRec.

This is a follow-up to dd92e21

Signed-off-by: Herbert Valerio Riedel <[email protected]>
  • Loading branch information
hvr committed May 14, 2014
1 parent dd92e21 commit 88c0870
Show file tree
Hide file tree
Showing 11 changed files with 7 additions and 16 deletions.
2 changes: 1 addition & 1 deletion compiler/cmm/Hoopl/Dataflow.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 #-}

Expand Down
2 changes: 1 addition & 1 deletion distrib/compare/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
GHC = ghc

compare: *.hs
"$(GHC)" -O --make -Wall -Werror $@
"$(GHC)" -O -XHaskell2010 --make -Wall -Werror $@

.PHONY: clean
clean:
Expand Down
2 changes: 0 additions & 2 deletions distrib/compare/compare.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE PatternGuards #-}

module Main (main) where

import Control.Monad.State
Expand Down
1 change: 0 additions & 1 deletion ghc/Main.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
{-# LANGUAGE ForeignFunctionInterface #-}

-----------------------------------------------------------------------------
--
Expand Down
3 changes: 1 addition & 2 deletions libraries/integer-simple/GHC/Integer/Type.hs
Original file line number Diff line number Diff line change
@@ -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:
Expand Down
2 changes: 1 addition & 1 deletion utils/checkUniques/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -13,4 +13,4 @@ check: checkUniques
./checkUniques mkPreludeMiscIdUnique $(PREL_NAMES) $(DS_META)

checkUniques: checkUniques.hs
$(GHC) --make $@
$(GHC) -O -XHaskell2010 --make $@
2 changes: 0 additions & 2 deletions utils/checkUniques/checkUniques.hs
Original file line number Diff line number Diff line change
@@ -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
Expand Down
3 changes: 0 additions & 3 deletions utils/dll-split/Main.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,3 @@

{-# LANGUAGE PatternGuards #-}

module Main (main) where

import Control.Monad
Expand Down
2 changes: 1 addition & 1 deletion utils/ghc-pkg/Main.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE PatternGuards, CPP, ForeignFunctionInterface #-}
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
--
-- (c) The University of Glasgow 2004-2009.
Expand Down
2 changes: 1 addition & 1 deletion utils/ghctags/Main.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE PatternGuards, ScopedTypeVariables #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main where

import Prelude hiding ( mod, id, mapM )
Expand Down
2 changes: 1 addition & 1 deletion utils/runghc/runghc.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
{-# LANGUAGE CPP #-}
#include "ghcconfig.h"
-----------------------------------------------------------------------------
--
Expand Down

0 comments on commit 88c0870

Please sign in to comment.