behaviour of {-# NOINLINE #-} in where clauses

Duncan Coutts duncan.coutts at worc.ox.ac.uk
Mon Aug 14 13:52:38 EDT 2006


On Mon, 2006-08-14 at 10:12 +0100, Simon Peyton-Jones wrote:
> [Narrowing to ghc users only]
> 
> That's odd.  I tried it (the HEAD) and it worked fine.  Input and output
> below
> 
> You'll notice that the binding for 'realloc' got floated into the branch
> of the case (that's FloatIn), but it is never inlined.

Ok, I'll try with the latest head.

In my code the realloc name has disappeared in the -ddump-simpl and the
only remaining 'let' expressions are for other things (for allocating
prim byte arrays and ForeignPtrContents).

> | Even so, I kind of wish there were a stage between STG and CMM that
> | showed the imperative model of STG with linear layout, control flow
> and
> | notes to indicate thunk/closure allocations. I expect most of my
> problem
> | is that I do not understand the STG evaluation model sufficiently well
> | to see how it maps to basic blocks, jumps/calls etc.
> 
> Try -ddump-prep.  It's essentially STG with a bit less clutter.

Right'o. Thanks.

> ======= Input =========
> 
> {-# OPTIONS -fglasgow-exts #-}
> 
> module Foo7 where
> 
> data Thing = One Thing | The Bool
> 
> loop xs ys =
>   case xs of
>     One thing -> loop thing ys
>     The other -> case realloc of
> 		    True -> False
> 		    False -> True
> 
> 
>   where
>     {-# NOINLINE realloc #-}
>     realloc = case ys of
> 		One thing -> True
> 		The other -> False
> 
> 
> ======= Output =========
> 
> Rec {
> Foo7.loop :: Foo7.Thing -> Foo7.Thing -> GHC.Base.Bool
> [GlobalId]
> [Arity 2
>  NoCafRefs
>  Str: DmdType SS]
> Foo7.loop =
>   \ (xs_add :: Foo7.Thing) (ys_ade :: Foo7.Thing) ->
>     case xs_add of wild_B1 {
>       Foo7.One thing_adv -> Foo7.loop thing_adv ys_ade;
>       Foo7.The other_adz ->
> 	let {
> 	  realloc_seH :: GHC.Base.Bool
> 	  [Str: DmdType]
> 	  realloc_seH =
> 	    case ys_ade of wild1_Xc {
> 	      Foo7.One thing_adn -> GHC.Base.True; Foo7.The other1_adr
> -> GHC.Base.False
> 	    }
> 	} in 
> 	  case realloc_seH of wild1_Xe {
> 	    GHC.Base.False -> GHC.Base.True; GHC.Base.True ->
> GHC.Base.False
> 	  }
>     }
> end Rec }

Yes, that looks more like what I want, I think.

Duncan



More information about the Glasgow-haskell-users mailing list