Desugaring overloaded functions

Bas van Dijk basvandijk at home.nl
Mon Nov 6 15:37:59 EST 2006


Dear GHC Hackers,

I'm using the GHC API for a project of mine. I have a question about the way 
GHC 'desugars' the following overloaded function:

incL :: (Num a) => [a] -> [a]
incL []       = []
incL (x : xs) = (1 + x) : (incL xs)

After calling 'Desugar.deSugar' on this function I get the following Core 
representation:

Test.incL =
   \ (@ a_ag0) ($dNum_al8 :: {GHC.Num.Num a_ag0}) ->
     __letrec {

       incL_afU :: [a_ag0] -> [a_ag0]
       incL_afU =
         \ (ds_dlZ :: [a_ag0]) ->
           case ds_dlZ of wild_B1 {
             []             -> __letrec { } in  GHC.Base.[] @ a_ag0;
             : x_adm xs_adn ->
               __letrec { } in  GHC.Base.: @ a_ag0 (+_al3 lit_al2 x_adm) 
(incL_afU xs_adn)
           };
       $dNum_alp :: {GHC.Num.Num a_ag0}
       $dNum_alp = $dNum_al8;

       fromInteger_alm :: GHC.Num.Integer -> a_ag0
       fromInteger_alm = GHC.Num.fromInteger @ a_ag0 $dNum_alp;

       lit_al2 :: a_ag0
       lit_al2 = fromInteger_alm (GHC.Num.S# 1);

       +_al3 :: a_ag0 -> a_ag0 -> a_ag0
       +_al3 = GHC.Num.+ @ a_ag0 $dNum_al8;

     } in  incL_afU;

This is great! However, I don't understand why:
'incL_afU', 
'$dNum_alp', 
'fromInteger_alm',
'lit_al2' and 
'+_al3' are all listed under the same letrec?

What I expect is that a dependency analysis is also applied to this letrec 
resulting in something like:

Test.incL =
   \ (@ a_ag0) ($dNum_al8 :: {GHC.Num.Num a_ag0}) ->
       let $dNum_alp :: {GHC.Num.Num a_ag0}
           $dNum_alp = $dNum_al8;
       in ( let +_al3 :: a_ag0 -> a_ag0 -> a_ag0
                +_al3 = GHC.Num.+ @ a_ag0 $dNum_al8;
            in ( let fromInteger_alm :: GHC.Num.Integer -> a_ag0
                     fromInteger_alm = GHC.Num.fromInteger @ a_ag0 $dNum_alp;
                 in ( let lit_al2 :: a_ag0
                          lit_al2 = fromInteger_alm (GHC.Num.S# 1);
                      in ( __letrec { incL_afU :: [a_ag0] -> [a_ag0]
                                      incL_afU = \ (ds_dlZ :: [a_ag0]) ->
                                                 case ds_dlZ of wild_B1 
                                                 { []             -> __letrec 
{ } in GHC.Base.[] @ a_ag0;
                                                   : x_adm xs_adn -> __letrec 
{ } in GHC.Base.: @ a_ag0 (+_al3 lit_al2 x_adm) 
                                                                                                        
(incL_afU xs_adn)
                                                 };
                                    } in  incL_afU;
                         )
                    )
               )
          )

I would really like the output of 'Desugar.deSugar' to be like the latter. 
Because than I can apply some beta-reductions to get rid of the non-recursive 
lets and use that as input for the rest of my project...

So, why isn't a dependency analysis applied to the letrec? And is it possible 
to manually apply a dependency analysis? If so, where can I find such a 
function?

Many thanks in advance,

Bas van Dijk


P.S.
I know that applying 'SimplCore.core2core' will result in something that I 
almost want:

[Test.incL :: forall a_ad8. (GHC.Num.Num a_ad8) => [a_ad8] -> [a_ad8]
 Test.incL =
   \ (@ a_akG) ($dNum_akS :: {GHC.Num.Num a_akG}) ->
     let {
       lit_akM :: a_akG
       lit_akM =
         case $dNum_akS
         of tpl_Xb { GHC.Num.:DNum tpl_B2 tpl_B3 tpl_B4 tpl_B5 tpl_B6 tpl_B7 
tpl_B8 tpl_B9 tpl_Ba ->
         tpl_Ba (GHC.Num.S# 1)
         } } in
     __letrec {
       incL_akH [LoopBreaker Nothing] :: [a_akG] -> [a_akG]
       incL_akH =
         \ (ds_dle :: [a_akG]) ->
           case ds_dle of wild_B1 {
             [] -> GHC.Base.[] @ a_akG;
             : x_adb xs_adc ->
               GHC.Base.:
                 @ a_akG
                 (case $dNum_akS
                  of tpl_X9 { GHC.Num.:DNum tpl_B2 tpl_B3 tpl_B4 tpl_B5 tpl_B6 
tpl_B7 tpl_B8 tpl_B9 tpl_Ba ->
                  tpl_B4 lit_akM x_adb
                  })
                 (incL_akH xs_adc)
           };
     } in  incL_akH]

However the rest of my project has trouble with the way 'fromInteger_alm' 
and '+_al3' are optimzed to case-expressions. So I would rather not 
use 'core2core'.


More information about the Glasgow-haskell-users mailing list