[reiner.pope@gmail.com: [Haskell-cafe] SpecConstr difficulties]

Simon Peyton-Jones simonpj at microsoft.com
Wed Jul 22 01:48:53 EDT 2009


Thanks.  You've found a bug in 6.10, which is happily fixed in the HEAD and in the upcoming 6.12. Here's the code for g2:

Test.$s$wg2 =
  \ (sc_soL :: GHC.Prim.Int#) (sc1_soM :: GHC.Prim.Int#) ->
    case GHC.Prim.># sc_soL 10 of _ {
      GHC.Bool.False ->
        case GHC.Prim.<=# sc1_soM sc_soL of _ {
          GHC.Bool.False -> Test.$s$wg2 (GHC.Prim.+# sc_soL 1) sc1_soM;
          GHC.Bool.True -> Test.$s$wg2 (GHC.Prim.+# sc_soL 1) sc_soL
        };
      GHC.Bool.True -> Test.Just @ GHC.Types.Int (GHC.Types.I# sc1_soM)
    }

Simon

| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-
| users-bounces at haskell.org] On Behalf Of Don Stewart
| Sent: 20 July 2009 17:38
| To: glasgow-haskell-users at haskell.org
| Subject: [reiner.pope at gmail.com: [Haskell-cafe] SpecConstr difficulties]
| 
| Something for SimonPJ
| 
| ----- Forwarded message from Reiner Pope <reiner.pope at gmail.com> -----
| 
| Date: Mon, 20 Jul 2009 22:09:09 +0930
| From: Reiner Pope <reiner.pope at gmail.com>
| To: Haskell Cafe mailing list <haskell-cafe at haskell.org>
| Subject: [Haskell-cafe] SpecConstr difficulties
| 
| Hi everyone,
| 
| I've been having some trouble getting SpecConstr to work as I want it
| to. The following example (see end of email) came up in some code I
| was playing around with. The loops g1 and g2 both compute the same
| thing: the maximum element of the "list" (which has been fused away)
| of numbers from 1 to 10.
| 
| Since 'maximum' is a foldl1 not a foldl, I use a strict Maybe type as
| an accumulator. The Maybe gets filled after the first element is seen,
| so the Maybe is a Just for almost the entire running of the loop.
| 
| It would be good to have this recognised by SpecConstr, to create an
| optimised loop for the Just case. This does indeed happen for g1, but
| not for g2.
| 
| My difficulty is that I am only able to produce code similar to g2,
| i.e. where the pattern matching is in a separate function, 'expose',
| because the 'expose' function is implemented in a type-class, like in
| stream-fusion. Is there some way to keep the SpecConstr while leaving
| the 'expose' as a separate function?
| 
| Here is the code:
| 
| > {-# LANGUAGE BangPatterns #-}
| >
| > module Test(ans1,ans2) where
| >
| > import Prelude hiding(Maybe(..))
| >
| > data Maybe a = Just !a | Nothing
| >
| > Nothing `mapp` Just b = Just b
| > Just a `mapp` Just b = Just (max a b)
| >
| > ans1 = g1 Nothing (0::Int)
| >
| > g1 m !n = case m of
| >            Nothing -> if n > 10 then m else g1 (m `mapp` Just n) (n+1)
| >            Just x -> if n > 10 then m else g1 (m `mapp` Just n) (n+1)
| >
| > ans2 = g2 Nothing (0::Int)
| >
| > g2 m !n = expose m (if n > 10 then m else g2 (m `mapp` Just n) (n+1))
| > expose Nothing  b = b
| > expose (Just a) b = a `seq` b
| 
| On a similar note, when I was having difficulties with this problem, I
| started to wonder if it would be possible to come up with a more
| direct way to tell GHC, "do SpecConstr on this variable". From reading
| the source code of the stream-fusion package, it seems that the
| current way of doing this is with 'expose' functions like I wrote
| below. Could we instead have a {-# SPECCONSTR #-} pragma, to be used
| on function arguments, like:
| 
| foo {-# SPECCONSTR #-} x y {-# SPECCONSTR #-} z = ...
| 
| This pragma should say to the GHC something like "ignore conditions
| H2, H5 and H6 of the SpecConstr paper, for this function and this
| argument".
| 
| Cheers,
| Reiner
| _______________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
| 
| ----- End forwarded message -----
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



More information about the Glasgow-haskell-users mailing list