[Haskell-cafe] Re: [Haskell] Real life examples

Sven Panne Sven.Panne at aedion.de
Fri Nov 26 15:03:02 EST 2004


Keean Schupke wrote:
> If a function is exported it cannot be inlined, can it? When I edit a module
> I generally don't have to recompile my whole program even if I compile with
> -O2... After all the fuss about certain type class extensions breaking separate
> compilation it would be a bit odd if it was broken already?

Again: Haskell is not C. Exported functions are exported including their
implementation if GHC thinks that "they are worth it". What this exactly
means can be tuned by a few parameters. A simple example:

---------------------------------------------------------------------------
module Foo where

bar :: Bool -> Int
bar False = 123
bar True  = 456
---------------------------------------------------------------------------
panne at jeanluc:~> ghc -O2 -c Foo.hs
panne at jeanluc:~> ghc --show-iface Foo.hi
interface "Main" Foo 1 6030 where
export Foo bar
module dependencies:
package dependencies: base
orphans: Foreign.C.Types Foreign.Ptr GHC.Base GHC.Float GHC.Int GHC.List
	 GHC.Word
bar :: GHC.Base.Bool -> GHC.Base.Int
   {- Arity: 1 HasNoCafRefs Strictness: Sm
      Unfolding:
      (\ ds :: GHC.Base.Bool ->
       case @ GHC.Base.Int ds of wild { False -> lvl1 True -> lvl }) -}
lvl :: GHC.Base.Int
   {- HasNoCafRefs Strictness: m Unfolding:  (GHC.Base.I# 456) -}
lvl1 :: GHC.Base.Int
   {- HasNoCafRefs Strictness: m Unfolding:  (GHC.Base.I# 123) -}
---------------------------------------------------------------------------

You can see that every little detail is exported here. This is extremely
important for good performance and I happily trade separate compilation
(in the traditional sense) for this. Note that 'ghc --make' easily handles
the recompilation issue for your own programs.

Libraries where you want some kind of binary backwards compatibility are
another story. Here you have to trade (just like C!) efficiency against
flexibility, e.g. by writing some kind of facade compiled without -O.

Cheers,
    S.


More information about the Haskell-Cafe mailing list