[commit: nofib] master: Move required language extensions into pragmas for shootout. (c985746)

git at git.haskell.org git at git.haskell.org
Tue Jan 1 17:38:19 UTC 2019


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

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

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

commit c985746f0bfe32cb08b9dcd057ada2e90fe77f4d
Author: klebinger.andreas at gmx.at <klebinger.andreas at gmx.at>
Date:   Sun Dec 30 12:52:51 2018 -0500

    Move required language extensions into pragmas for shootout.
    
    Summary: That way they are easier to compile with plain calls to ghc.
    
    Test Plan: make clean && make boot && make
    
    Reviewers: O26 nofib, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: bgamari
    
    Differential Revision: https://phabricator.haskell.org/D5437


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

c985746f0bfe32cb08b9dcd057ada2e90fe77f4d
 shootout/binary-trees/Main.hs        | 1 +
 shootout/binary-trees/Makefile       | 2 +-
 shootout/fannkuch-redux/Main.hs      | 1 +
 shootout/fannkuch-redux/Makefile     | 4 +---
 shootout/fasta/Main.hs               | 1 +
 shootout/fasta/Makefile              | 2 +-
 shootout/k-nucleotide/Main.hs        | 1 +
 shootout/k-nucleotide/Makefile       | 2 +-
 shootout/n-body/Main.hs              | 1 +
 shootout/n-body/Makefile             | 2 +-
 shootout/pidigits/Main.hs            | 1 +
 shootout/reverse-complement/Main.hs  | 1 +
 shootout/reverse-complement/Makefile | 3 +--
 shootout/spectral-norm/Main.hs       | 1 +
 shootout/spectral-norm/Makefile      | 2 +-
 15 files changed, 15 insertions(+), 10 deletions(-)

diff --git a/shootout/binary-trees/Main.hs b/shootout/binary-trees/Main.hs
index 8258c71..9c596d9 100644
--- a/shootout/binary-trees/Main.hs
+++ b/shootout/binary-trees/Main.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE BangPatterns #-}
 --
 -- The Computer Language Benchmarks Game
 -- http://benchmarksgame.alioth.debian.org/
diff --git a/shootout/binary-trees/Makefile b/shootout/binary-trees/Makefile
index 2d2d321..7731758 100644
--- a/shootout/binary-trees/Makefile
+++ b/shootout/binary-trees/Makefile
@@ -8,5 +8,5 @@ SLOW_OPTS = 20  # official shootout setting
 
 # The benchmark game also uses -fllvm, which we can't since it might
 # not be available on the developer's machine.
-HC_OPTS += -XBangPatterns -funbox-strict-fields
+HC_OPTS += -funbox-strict-fields
 SRC_RUNTEST_OPTS += +RTS -K128M -H200m -RTS
diff --git a/shootout/fannkuch-redux/Main.hs b/shootout/fannkuch-redux/Main.hs
index 157c05d..9b9e817 100644
--- a/shootout/fannkuch-redux/Main.hs
+++ b/shootout/fannkuch-redux/Main.hs
@@ -7,6 +7,7 @@
     and run with:
     	+RTS -N<number of cores> -RTS <input>
 -}
+{-# LANGUAGE BangPatterns #-}
 
 import Control.Concurrent
 import Control.Monad
diff --git a/shootout/fannkuch-redux/Makefile b/shootout/fannkuch-redux/Makefile
index 729955f..b87fdd2 100644
--- a/shootout/fannkuch-redux/Makefile
+++ b/shootout/fannkuch-redux/Makefile
@@ -6,7 +6,5 @@ FAST_OPTS = 10
 NORM_OPTS = 11
 SLOW_OPTS = 12  # official shootout setting
 
-# The benchmark game also uses -fllvm, which we can't since it might
+# The benchmark game uses -fllvm, which we can't since it might
 # not be available on the developer's machine.
-HC_OPTS += -XBangPatterns
-
diff --git a/shootout/fasta/Main.hs b/shootout/fasta/Main.hs
index 070a3f0..3b10ccc 100644
--- a/shootout/fasta/Main.hs
+++ b/shootout/fasta/Main.hs
@@ -4,6 +4,7 @@
 
     contributed by Bryan O'Sullivan
 -}
+{-# LANGUAGE BangPatterns, OverloadedStrings #-}
 
 import Control.Monad
 import Data.ByteString.Unsafe
diff --git a/shootout/fasta/Makefile b/shootout/fasta/Makefile
index 14ecb61..19fa17b 100644
--- a/shootout/fasta/Makefile
+++ b/shootout/fasta/Makefile
@@ -13,7 +13,7 @@ SLOW_OPTS = 25000000  # official shootout setting
 
 # The benchmark game also uses -fllvm, which we can't since it might
 # not be available on the developer's machine.
-HC_OPTS += -XBangPatterns -XOverloadedStrings -package bytestring
+HC_OPTS += -package bytestring
 
 #------------------------------------------------------------------
 # Create output to validate against
diff --git a/shootout/k-nucleotide/Main.hs b/shootout/k-nucleotide/Main.hs
index 6963a4d..6783f0b 100644
--- a/shootout/k-nucleotide/Main.hs
+++ b/shootout/k-nucleotide/Main.hs
@@ -4,6 +4,7 @@
 --
 -- contributed by Stephen Blackheath (with some bits taken from Don Stewart's
 --     version), v1.2
+{-# LANGUAGE BangPatterns #-}
 
 import Text.Printf
 import Data.ByteString.Internal
diff --git a/shootout/k-nucleotide/Makefile b/shootout/k-nucleotide/Makefile
index 56870ff..6cff15d 100644
--- a/shootout/k-nucleotide/Makefile
+++ b/shootout/k-nucleotide/Makefile
@@ -11,7 +11,7 @@ CLEAN_FILES += fasta-c k-nucleotide.*stdin
 
 # The benchmark game also uses -fllvm, which we can't since it might
 # not be available on the developer's machine.
-HC_OPTS += -XBangPatterns -package bytestring
+HC_OPTS += -package bytestring
 
 #------------------------------------------------------------------
 # Create input
diff --git a/shootout/n-body/Main.hs b/shootout/n-body/Main.hs
index d22ddb0..5391020 100644
--- a/shootout/n-body/Main.hs
+++ b/shootout/n-body/Main.hs
@@ -10,6 +10,7 @@
 --
 -- Don't enable -optc-mfpmath=sse -optc-msse2, this triggers a gcc bug on x86
 --
+{-# LANGUAGE BangPatterns #-}
 
 import Foreign (Ptr, Storable(..), plusPtr, mallocBytes)
 import Foreign.Storable
diff --git a/shootout/n-body/Makefile b/shootout/n-body/Makefile
index 2290826..0de067a 100644
--- a/shootout/n-body/Makefile
+++ b/shootout/n-body/Makefile
@@ -8,4 +8,4 @@ SLOW_OPTS = 50000000  # official shootout setting
 
 # The benchmark game also uses -fllvm, which we can't since it might
 # not be available on the developer's machine.
-HC_OPTS += -XBangPatterns -fexcess-precision
+HC_OPTS += -fexcess-precision
diff --git a/shootout/pidigits/Main.hs b/shootout/pidigits/Main.hs
index 665641f..137e23a 100644
--- a/shootout/pidigits/Main.hs
+++ b/shootout/pidigits/Main.hs
@@ -4,6 +4,7 @@
 -- modified by Eugene Kirpichov: pidgits only generates
 -- the result string instead of printing it. For some
 -- reason, this gives a speedup.
+{-# LANGUAGE BangPatterns #-}
 
 import System.Environment
 
diff --git a/shootout/reverse-complement/Main.hs b/shootout/reverse-complement/Main.hs
index 7f3bdf9..e329dc8 100644
--- a/shootout/reverse-complement/Main.hs
+++ b/shootout/reverse-complement/Main.hs
@@ -4,6 +4,7 @@ http://benchmarksgame.alioth.debian.org/
 
 contributed by Louis Wasserman
 -}
+{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-}
 
 import Control.Monad
 import Foreign
diff --git a/shootout/reverse-complement/Makefile b/shootout/reverse-complement/Makefile
index e3b72b7..306bab4 100644
--- a/shootout/reverse-complement/Makefile
+++ b/shootout/reverse-complement/Makefile
@@ -15,8 +15,7 @@ SLOW_OPTS = 25000000  # official shootout setting
 
 # The benchmark game also uses -fllvm, which we can't since it might
 # not be available on the developer's machine.
-HC_OPTS += -XBangPatterns -funfolding-use-threshold=32 -XMagicHash \
-	-XUnboxedTuples
+HC_OPTS += -funfolding-use-threshold=32
 
 #------------------------------------------------------------------
 # Create input
diff --git a/shootout/spectral-norm/Main.hs b/shootout/spectral-norm/Main.hs
index 3a52736..4e83277 100644
--- a/shootout/spectral-norm/Main.hs
+++ b/shootout/spectral-norm/Main.hs
@@ -13,6 +13,7 @@
 -- 	-fexcess-precision -optc-ffast-math
 -- Should be run with:
 -- 	+RTS -N<number of cores>
+{-# LANGUAGE BangPatterns, MagicHash #-}
 
 import System.Environment
 import Foreign.Marshal.Array
diff --git a/shootout/spectral-norm/Makefile b/shootout/spectral-norm/Makefile
index a0728d9..15cae66 100644
--- a/shootout/spectral-norm/Makefile
+++ b/shootout/spectral-norm/Makefile
@@ -8,4 +8,4 @@ SLOW_OPTS = 5500  # official shootout setting
 
 # The benchmark game also uses -fllvm, which we can't since it might
 # not be available on the developer's machine.
-HC_OPTS += -XBangPatterns -XMagicHash -fexcess-precision
+HC_OPTS += -fexcess-precision



More information about the ghc-commits mailing list