[GHC] #13002: :set -O does not work in .ghci file
GHC
ghc-devs at haskell.org
Wed Sep 20 00:01:11 UTC 2017
#13002: :set -O does not work in .ghci file
-------------------------------------+-------------------------------------
Reporter: George | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.4.1
Component: GHCi | Version: 8.0.1
Resolution: | Keywords:
| RecompilationCheck
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by George:
Old description:
> {{{#!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.
New description:
{{{#!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; it 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#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list