Simon,

On Thu, 2006-11-30 at 02:13 +0000, Simon Peyton-Jones wrote:
> | A related problem is
> |
> | foo :: Int -> Int -> Int
> | foo 0 n = 0
> | foo m n = foo (m-n) n
> | Here, n isn't getting unboxed although it could be if m is not 0 in the 
> first iteration. Perhaps unrolling
> | the loop once could help here.
> 
> I'm not sure when I fixed this, but it's working fine now.  Try it!

Not quite. For:

------
module Foo where

data a :*: b = !a :*: !b

infixl 7 :*:

foo :: Int -> Int :*: Int -> Int
foo 0 _ = 0
foo i (m :*: n) | even i    = foo (i-m) (m :*: n)
                | otherwise = foo (i-n) (m :*: n)
------

I get

------
$wfoo :: Int# -> (:*:) Int Int -> Int#
$wfoo =
  \ (ww_spE :: Int#) (w_spG :: (:*:) Int Int) ->
    case ww_spE of ds_Xi7 {
      __DEFAULT ->
        case w_spG of wild_Xc { :*: m_a7E n_a7F ->
        case remInt# ds_Xi7 2 of wild1_aoo {
          __DEFAULT ->
            case n_a7F of wild11_aoS { I# y_aoU ->
            $wfoo
              (-# ds_Xi7 y_aoU)
              (case m_a7E of tpl_Xt { I# ipv_sp2 -> wild_Xc })
            };
          0 ->
            case m_a7E of wild11_aoS { I# y_aoU ->
            $wfoo
              (-# ds_Xi7 y_aoU)
              (case n_a7F of tpl_B2 { I# ipv_spb -> wild_Xc })
            }
        }
        };
      0 -> 0
    }
------

I'm not entirely sure why my original example works now. Anyway, this is
a rather minor problem, at least for me.

Roman



_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to