Re: finally part run twice on Ctrl-C

2009-02-27 Thread Philip K.F. Hölzenspies
 I've got the following code:

 import Control.Exception
 import System.Cmd
 main = system sleep 1m `finally` putStrLn goodbye

 When compiled with GHC 6.10.1.20090225, if I hit Ctrl-C during the
 sleep, I get the goodbye printed twice. If I leave evaluation to
 finish normally I get goodbye once. Is this a bug?

Dear Neil, et al.

Just to let you know; I tried it on the release version of 6.10.1 and it 
worked as expected (first run, I waited; second I pressed Ctrl-C):

*Test main
goodbye
ExitSuccess
*Test main
goodbye
ExitFailure 2
*Test

If not coming from system differences, the bug should sit in recent code.

Regards,
Philip
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: finally part run twice on Ctrl-C

2009-02-27 Thread Neil Mitchell
Hi Philip,

 Just to let you know; I tried it on the release version of 6.10.1 and it
 worked as expected (first run, I waited; second I pressed Ctrl-C):

 *Test main
 goodbye
 ExitSuccess
 *Test main
 goodbye
 ExitFailure 2
 *Test

It looks like you are running in GHCi, which I think works. It's only
when the program is compiled and run from the command line (Cygwin or
DOS) that I get the above problem.

Thanks

Neil;
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: finally part run twice on Ctrl-C

2009-02-27 Thread Philip K.F. Hölzenspies
On Friday 27 February 2009 09:39:14 Neil Mitchell wrote:
 It looks like you are running in GHCi, which I think works. It's only
 when the program is compiled and run from the command line (Cygwin or
 DOS) that I get the above problem.

Dear Neil,

You were right. When I do compile it, though, I get the same (correct) 
behaviour (now I pressed Ctrl-C the first run and let it be for the second):

holze...@ewi1043:~/tmp ghc Test.hs
holze...@ewi1043:~/tmp ./a.out
goodbye
holze...@ewi1043:~/tmp ./a.out
goodbye
holze...@ewi1043:~/tmp  

This is on Linux, though, so it may also be OS-dependent.

Regards,
Philip
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Suggestion for bang patterns documentation

2009-02-27 Thread Simon Peyton-Jones
good idea. done

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Brian Bloniarz
| Sent: 27 February 2009 03:56
| To: glasgow-haskell-users@haskell.org
| Subject: Suggestion for bang patterns documentation
|
|
| I got confused by the GHC documentation recently, I was wondering how
| it could be improved. From:
| http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html
|
|  A bang only really has an effect if it precedes a variable or wild-card 
pattern:
|  f3 !(x,y) = [x,y]
|  f4 (x,y)  = [x,y]
|  Here, f3 and f4 are identical; putting a bang before a pattern that
|  forces evaluation anyway does nothing.
|
| The first sentence is true, but only in settings where the pattern is being
| evaluated eagerly -- the bang in:
|  f3 a = let !(x,y) = a in [1,x,y]
|  f4 a = let (x,y) = a in [1,x,y]
| has an effect.
|
| The first time I read this, I took the first sentence to be a unqualified 
truth
| and ended up thinking that !(x,y) was equivalent to (x,y) everywhere. Stuff
| that comes later actually clarifies this, but I missed it.
|
| What about making the distinction clear upfront? Something like:
|  A bang in an eager pattern match only really has an effect if it precedes a
| variable
|  or wild-card pattern:
|  f3 !(x,y) = [x,y]
|  f4 (x,y)  = [x,y]
|  Because f4 _|_ will force the evaluation of the pattern match anyway, f3 
and f4
|  are identical; the bang does nothing.
|
| It also might be a good idea to immediately follow this with the let/where 
usage:
|
|  A bang can also preceed a let/where binding to make the pattern match 
strict. For
| example:
|  let ![x,y] = e in b
|  is a strict pattern...
| (in the existing docs, let comes a bit later):
|
| Just a thought. Hopefully someone can come up with a better way of
| wording what I'm getting at.
|
| Thanks,
| -Brian
|
| _
| Windows Live(tm) Hotmail(r)...more than just e-mail.
| 
http://windowslive.com/howitworks?ocid=TXT_TAGLM_WL_t2_hm_justgotbetter_howitworks_0
| 22009___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Suggestion for bang patterns documentation

2009-02-27 Thread Christian Maeder
Brian Bloniarz wrote:
 I got confused by the GHC documentation recently, I was wondering how
 it could be improved. From:
 http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html

Seeing the rule
 pat ::= !pat

you'll probably want to avoid patterns like: !!pat, ! ! pat, or ~ !
~ pat.

Even the current http://www.haskell.org/onlinelibrary/exps.html#sect3.17.1

  apat - ~ apat

allows ~ ~x. (Note the space!) So maybe a separate non-terminal bpat
should be used with:

 bpat - [~|!] apat

(and bpat used within pat). You may also want to exclude v@ ~(...) in
favor of ~v@(...).

 A bang only really has an effect if it precedes a variable or wild-card 
 pattern:
 f3 !(x,y) = [x,y]
 f4 (x,y)  = [x,y]
 Here, f3 and f4 are identical; putting a bang before a pattern that
 forces evaluation anyway does nothing.

Maybe the duality (if it is one) should be added that an irrefutable
pattern above would make a difference but not within the let below.

 The first sentence is true, but only in settings where the pattern is being
 evaluated eagerly -- the bang in:
 f3 a = let !(x,y) = a in [1,x,y]
 f4 a = let (x,y) = a in [1,x,y]
 has an effect.

Cheers Christian

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Suggestion for bang patterns documentation

2009-02-27 Thread Christian Maeder
Brian Bloniarz wrote:
 I got confused by the GHC documentation recently, I was wondering how
 it could be improved. From:
 http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html

cite
The let-binding can be recursive. However, it is much more common for
the let-binding to be non-recursive, in which case the following law
holds: (let !p = rhs in body)  is equivalent to (case rhs of !p - body)
/cite

Shouldn't the bang be removed in the final case pattern?

Furthermore with existential types the let binding is not supported:

 data E = forall a . Show a = E a

 f :: E - String
 f x = case x of E a - show a

f works, but g

 g :: E - String
 g x = let !(E a) = x in show a

fails (with or without the bang):

My brain just exploded.
I can't handle pattern bindings for existentially-quantified
constructors.
Instead, use a case-expression, or do-notation, to unpack the
constructor.
In the binding group for
!(E a)
In a pattern binding: !(E a) = x
In the expression: let !(E a) = x in show a
In the definition of `g': g x = let !(E a) = x in show a

Cheers Christian

P.S. It should be mentioned that ~ and ! only make sense for single
variant data types (like tuples)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Suggestion for bang patterns documentation

2009-02-27 Thread Simon Peyton-Jones
| cite
| The let-binding can be recursive. However, it is much more common for
| the let-binding to be non-recursive, in which case the following law
| holds: (let !p = rhs in body)  is equivalent to (case rhs of !p - body)
| /cite
|
| Shouldn't the bang be removed in the final case pattern?

No.  If p was a simple variable, then
case rhs of x - body
is non-strict in Haskell, but should be strict here.

| P.S. It should be mentioned that ~ and ! only make sense for single
| variant data types (like tuples)

That isn't true.  Both are useful for multi-variant types

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Int vs Word performance?

2009-02-27 Thread Malcolm Wallace
Claus Reinke claus.rei...@talk21.com wrote:

 A while ago, I needed lots of fairly small positive numbers,
 together with a small number of flags for each, so I thought
 I'd switch from Int to Word, and map the flags to bits.

Since there are few guarantees about the size of a Word (or Int), surely
it would be better to choose a definitely sized basic type, e.g. Word8
or Word16?  I vaguely recall that ghc used to generate better code for
definitely sized WordN than the generic unguaranteed-size Word.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Suggestion for bang patterns documentation

2009-02-27 Thread Christian Maeder
Simon Peyton-Jones wrote:
 | cite
 | The let-binding can be recursive. However, it is much more common for
 | the let-binding to be non-recursive, in which case the following law
 | holds: (let !p = rhs in body)  is equivalent to (case rhs of !p - body)
 | /cite
 |
 | Shouldn't the bang be removed in the final case pattern?
 
 No.  If p was a simple variable, then
 case rhs of x - body
 is non-strict in Haskell, but should be strict here.

Thanks for pointing this out. But the case with a simple variable (and
no distinction) is special anyway (sort of a monomorphic let binding).

 | P.S. It should be mentioned that ~ and ! only make sense for single
 | variant data types (like tuples)
 
 That isn't true.  Both are useful for multi-variant types

Right, a non-empty list should behave like a pair as long as I don't
want to know the variant beforehand and thereby forcing evaluation anyway.

Cheers Christian

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Int vs Word performance?

2009-02-27 Thread Claus Reinke

Here is a trivial example with drastic difference between
T = Int and T = Word (~2.5x here):

   main = print $ foldl' (+) 0 [1..1::T]

..

   GHC.Prim.word2Int#
   (GHC.Prim.and#
   (GHC.Prim.int2Word# wild13_XbE)
   (GHC.Prim.int2Word# y#_a4EZ))

Is that likely to cost me a lot or are these conversions cheap?


Those guys are no-ops, and in general you should never see a performance
difference. If you do, it is a bug!  There are some known cases where
rules are missing however:


Thanks, that is one thing less to worry about. Btw, is there a guide to
reading Core somewhere, with emphasis on performance aspects (what
to look for when optimizing time or space usage, what to ignore, how to
make it more readable, etc)?

Until I stumbled over CORE annotations, I found it near impossible even
to find the pieces of interest for non-trivial programs, things like
-dsuppress-uniques help a little with diffs, some things look big but
are noops, etc. - that kind of helpful pragmatic knowledge (why does
it look as if source variable names aren't always preserved; why does
it use random uniques instead of de Bruijn-style disambiguation, which
wouldn't interfere with diffs and would have static semantic content;
why do the outputs look different for core2core vs dump-simpl, ..).


Some others I'm aware of are product/sum/maximum/minimum
on lists have specialisations for some atomic types (Int, Integer) but
not all (needs a ticket for this too).


A quick grep shows almost no specialization at all for Word, or for
IntXX/WordXX (see below). Still, none of that seems to explain the
example repeated at the top of this message.

Claus

$ find libraries/ -name _darcs -prune -o -name *hs | xargs grep SPECIAL | grep 
'\Int\|\Word'
libraries/base/Data/List.hs:{-# SPECIALISE sum :: [Int] - Int #-}
libraries/base/Data/List.hs:{-# SPECIALISE sum :: [Integer] - Integer #-}
libraries/base/Data/List.hs:{-# SPECIALISE product :: [Int] - Int #-}
libraries/base/Data/List.hs:{-# SPECIALISE product :: [Integer] - Integer #-}
libraries/base/GHC/Arr.lhs:{-# SPECIALISE instance Ix (Int,Int) #-}
libraries/base/GHC/Arr.lhs:{-# SPECIALISE instance Ix (Int,Int,Int) #-}
libraries/base/GHC/Float.lhs:{-# SPECIALIZE properFraction :: Float - 
(Int, Float) #-}
libraries/base/GHC/Float.lhs:{-# SPECIALIZE round:: Float - Int #-}
libraries/base/GHC/Float.lhs:{-# SPECIALIZE properFraction :: Float  - 
(Integer, Float) #-}
libraries/base/GHC/Float.lhs:{-# SPECIALIZE round:: Float - Integer #-}
libraries/base/GHC/Float.lhs:{-# SPECIALIZE properFraction :: Double - 
(Int, Double) #-}
libraries/base/GHC/Float.lhs:{-# SPECIALIZE round:: Double - Int #-}
libraries/base/GHC/Float.lhs:{-# SPECIALIZE properFraction :: Double - 
(Integer, Double) #-}
libraries/base/GHC/Float.lhs:{-# SPECIALIZE round:: Double - Integer 
#-}
libraries/base/GHC/Real.lhs:{-# SPECIALISE (%) :: Integer - Integer - 
Rational #-}
libraries/base/GHC/Real.lhs:{-# SPECIALISE reduce :: Integer - Integer - 
Rational #-}
libraries/base/GHC/Real.lhs:{-# SPECIALISE lcm :: Int - Int - Int #-}
libraries/bytestring/Data/ByteString/Internal.hs:{-# SPECIALIZE unpackWith :: (Word8 - Char) - 
ByteString - [Char] #-}
libraries/bytestring/Data/ByteString/Internal.hs:{-# SPECIALIZE packWith :: (Char - Word8) - 
[Char] - ByteString #-}
libraries/bytestring/Data/ByteString/Lazy.hs:{-# SPECIALIZE packWith :: (Char - Word8) - [Char] - 
ByteString #-}
libraries/bytestring/Data/ByteString/Lazy.hs:{-# SPECIALIZE unpackWith :: (Word8 - Char) - 
ByteString - [Char] #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE lookupTree :: Int - FingerTree (Elem a) - 
Place (Elem a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE lookupTree :: Int - FingerTree (Node a) - 
Place (Node a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE lookupNode :: Int - Node (Elem a) - Place 
(Elem a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE lookupNode :: Int - Node (Node a) - Place 
(Node a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE lookupDigit :: Int - Digit (Elem a) - Place 
(Elem a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE lookupDigit :: Int - Digit (Node a) - Place 
(Node a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE adjustTree :: (Int - Elem a - Elem a) - 
Int - FingerTree (Elem a) - FingerTree (Elem a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE adjustTree :: (Int - Node a - Node a) - 
Int - FingerTree (Node a) - FingerTree (Node a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE adjustNode :: (Int - Elem a - Elem a) - 
Int - Node (Elem a) - Node (Elem a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE adjustNode :: (Int - Node a - Node a) - 
Int- Node (Node a) - Node (Node a) #-}
libraries/containers/Data/Sequence.hs:{-# SPECIALIZE adjustDigit :: (Int - Elem a - Elem a) - 
Int - Digit (Elem a) - Digit (Elem a) #-}

Re: Int vs Word performance?

2009-02-27 Thread Claus Reinke

A while ago, I needed lots of fairly small positive numbers,
together with a small number of flags for each, so I thought
I'd switch from Int to Word, and map the flags to bits.


Since there are few guarantees about the size of a Word (or Int), surely
it would be better to choose a definitely sized basic type, e.g. Word8
or Word16?  


Good point in principle, and I would indeed prefer a specific size.
Unfortunately, I found just the opposite of this


I vaguely recall that ghc used to generate better code for
definitely sized WordN than the generic unguaranteed-size Word.


to be true (although I don't recall whether I checked with IntN or
WordN, and I don't have a small example for this issue): Even
just replacing Int with Int32 on a system where that should be
the same was liable to reduce performance..

Given Don's point about SPECIALI[ZS]E, and the lack of
specialisations for IntN/WordN, that might explain it?

Claus

PS. perhaps on newer 64 bit machines, explicitly selecting
   32 bits can offer savings? I'd certainly expect selecting
   64 bits on a 32 bit machine to lead to slowdowns.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


ghc crashes on strange foreign import

2009-02-27 Thread Ben Franksen
This is the code:

{-# OPTIONS -fglasgow-exts #-}
import Foreign
type X u = Ptr ()
foreign import ccall bla :: (forall u. X u) - IO ()

I know of course that I must not use fancy types in foreign imports. I
forgot for a moment and instead of an error message got:

b...@sarun ghci Bug3
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( Bug3.hs, interpreted )
ghc: panic! (the 'impossible' happened)
  (GHC version 6.10.1 for i386-unknown-linux):
unboxArg: 
Bug3.hs:4:0-51 forall u{tv aht} [tv].
   main:Main.X{tc rhp} u{tv aht} [tv]

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

Cheers
Ben

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Int vs Word performance?

2009-02-27 Thread Simon Marlow

Claus Reinke wrote:

Here is a trivial example with drastic difference between
T = Int and T = Word (~2.5x here):

   main = print $ foldl' (+) 0 [1..1::T]

..



A quick grep shows almost no specialization at all for Word, or for
IntXX/WordXX (see below). Still, none of that seems to explain the
example repeated at the top of this message.


The Enum instance for Int uses specialised implementations of enumFromTo 
and friends, whereas the Word version uses the generic integralEnumFromTo.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Int vs Word performance?

2009-02-27 Thread Simon Peyton-Jones
| Until I stumbled over CORE annotations, I found it near impossible even
| to find the pieces of interest for non-trivial programs, things like
| -dsuppress-uniques help a little with diffs, some things look big but
| are noops, etc. - that kind of helpful pragmatic knowledge (why does
| it look as if source variable names aren't always preserved; why does
| it use random uniques instead of de Bruijn-style disambiguation, which
| wouldn't interfere with diffs and would have static semantic content;
| why do the outputs look different for core2core vs dump-simpl, ..).

Many of these things might be fixable if someone thought about the 
specification carefully.  The current core pretty-printer was initially 
designed only for GHC internals hackers, rather than Joe User.

A first step might be for a posse of Joe Users to specify what they want, as 
precisely as possible.  Then this same posse might even write a Core 
pretty-printer to achieve it. I am happy to advise.  Then we could substitute 
new for old.

| A quick grep shows almost no specialization at all for Word, or for
| IntXX/WordXX (see below). Still, none of that seems to explain the
| example repeated at the top of this message.

We'd be delighted to apply suitable library patches.

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Int vs Word performance?

2009-02-27 Thread Simon Peyton-Jones
| | A quick grep shows almost no specialization at all for Word, or for
| | IntXX/WordXX (see below). Still, none of that seems to explain the
| | example repeated at the top of this message.
|
| We'd be delighted to apply suitable library patches.

PS: in the case that no one gets around to creating such a patch, creating a 
ticket that documents the problem and points to the needed specialisations 
would be a start
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Int vs Word performance?

2009-02-27 Thread Simon Marlow

Claus Reinke wrote:

PS. perhaps on newer 64 bit machines, explicitly selecting
   32 bits can offer savings? I'd certainly expect selecting
   64 bits on a 32 bit machine to lead to slowdowns.


Unlikely, I'd have thought.  We implement all the explicitly sized integral 
types by zero-extending or sign-extending to the size of an Int/Word. 
That's why there are no primitive types or operations for Word8#, Word16#, etc.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Int vs Word performance?

2009-02-27 Thread Don Stewart
claus.reinke:
 Here is a trivial example with drastic difference between
 T = Int and T = Word (~2.5x here):

main = print $ foldl' (+) 0 [1..1::T]
 ..
GHC.Prim.word2Int#
(GHC.Prim.and#
(GHC.Prim.int2Word# wild13_XbE)
(GHC.Prim.int2Word# y#_a4EZ))

 Is that likely to cost me a lot or are these conversions cheap?

 Those guys are no-ops, and in general you should never see a performance
 difference. If you do, it is a bug!  There are some known cases where
 rules are missing however:

 Thanks, that is one thing less to worry about. Btw, is there a guide to
 reading Core somewhere, with emphasis on performance aspects (what
 to look for when optimizing time or space usage, what to ignore, how to
 make it more readable, etc)?

 Until I stumbled over CORE annotations, I found it near impossible even
 to find the pieces of interest for non-trivial programs, things like
 -dsuppress-uniques help a little with diffs, some things look big but
 are noops, etc. - that kind of helpful pragmatic knowledge (why does
 it look as if source variable names aren't always preserved; why does
 it use random uniques instead of de Bruijn-style disambiguation, which
 wouldn't interfere with diffs and would have static semantic content;
 why do the outputs look different for core2core vs dump-simpl, ..).

 Some others I'm aware of are product/sum/maximum/minimum
 on lists have specialisations for some atomic types (Int, Integer) but
 not all (needs a ticket for this too).

 A quick grep shows almost no specialization at all for Word, or for
 IntXX/WordXX (see below). Still, none of that seems to explain the
 example repeated at the top of this message.

We do need to decide on if we want to add specializations for all atomic
types in general, and if so, then let'd do that intentionally.

Does anyone see a reason not to do it in the libraries, via rules?
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Int vs Word performance?

2009-02-27 Thread Don Stewart
marlowsd:
 Claus Reinke wrote:
 Here is a trivial example with drastic difference between
 T = Int and T = Word (~2.5x here):

main = print $ foldl' (+) 0 [1..1::T]
 ..

 A quick grep shows almost no specialization at all for Word, or for
 IntXX/WordXX (see below). Still, none of that seems to explain the
 example repeated at the top of this message.

 The Enum instance for Int uses specialised implementations of enumFromTo  
 and friends, whereas the Word version uses the generic 
 integralEnumFromTo.

Another good reason to use uvector,

import Data.Array.Vector
import Data.Word

main = print $ foldlU (+) (0::T) (enumFromToU 1 (1::T))

type T = Word


$wfold :: Word# - Word# - Word#

$wfold =
  \ (ww_s1cg :: Word#) (ww1_s1ck :: Word#) -
case gtWord# ww1_s1ck __word 1 of wild_a19p {
  False -
$wfold
  (plusWord# ww_s1cg ww1_s1ck)
  (plusWord# ww1_s1ck __word 1);
  True - ww_s1cg

Yields:

Main_zdwfold_info:
.Lc1e1:
  cmpq $1,%rdi
  ja .Lc1e4
  leaq 1(%rdi),%rax
  addq %rdi,%rsi
  movq %rax,%rdi
  jmp Main_zdwfold_info

While at 

type T = Int

We get:

$wfold :: Int# - Int# - Int#

$wfold =
  \ (ww_s144 :: Int#) (ww1_s148 :: Int#) -
case # ww1_s148 1 of wild_a11q {
  False -
$wfold
  (+# ww_s144 ww1_s148) (+# ww1_s148 1);
  True - ww_s144

And *identical assembly*

Main_zdwfold_info:
.Lc15E:
  cmpq $1,%rdi
  jg .Lc15H
  leaq 1(%rdi),%rax
  addq %rdi,%rsi
  movq %rax,%rdi
  jmp Main_zdwfold_info

-- Don
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users