[GHC] #13002: :set -O does not work in .ghci file
GHC
ghc-devs at haskell.org
Sun Dec 18 17:49:42 UTC 2016
#13002: :set -O does not work in .ghci file
--------------------------------------+----------------------------
Reporter: George | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 8.0.1
Keywords: | Operating System: MacOS X
Architecture: x86_64 (amd64) | Type of failure: Other
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
--------------------------------------+----------------------------
{{{#!hs
{-# OPTIONS_GHC -Wall #-}
module Foo where
testFromTo :: Int -> Int
testFromTo n = length ([0..(10^n)] :: [Int])
}}}
{{{
cat ~/.ghci
:set +s
:set -fobject-code
:set -O
bash-3.2$ touch Foo.hs
bash-3.2$ ghci
GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /Users/gcolpitts/.ghci
Prelude> :load Foo
:load Foo
[1 of 1] Compiling Foo ( Foo.hs, Foo.o )
Ok, modules loaded: Foo (Foo.o).
(0.15 secs,)
Prelude Foo> testFromTo 5
testFromTo 5
100001
(0.02 secs, 8,885,888 bytes)
Prelude Foo> :quit
:quit
Leaving GHCi.
bash-3.2$ touch Foo.hs
bash-3.2$ ghci -fobject-code -O
GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /Users/gcolpitts/.ghci
Prelude> :load Foo
:load Foo
[1 of 1] Compiling Foo ( Foo.hs, Foo.o )
Ok, modules loaded: Foo (Foo.o).
(0.15 secs,)
Prelude Foo> testFromTo 5
testFromTo 5
100001
(0.02 secs, 98,400 bytes)
}}}
While supplying -fobject-code -O as an argument to ghci seems like an easy
workaround that isn't feasible as far as I know when using emacs thus
setting priority to normal rather than low.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13002>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list