Hi,

Am Samstag, den 13.09.2014, 00:01 -0400 schrieb David Feuer:
> On Sep 12, 2014 2:35 PM, "Joachim Breitner" <[email protected]>
> wrote:
> > Interesting. I assumed that some wrap.unwrap=id law would hold, or
> at
> > least some moral approximation (e.g. disregarding bottoms in an
> > acceptable manner). But if the wrappers have to do arbitrary stuff
> that
> > can arbitrarily interact with how the producer calls them, this
> becomes
> > a bit less appealing.
> 
> No, nothing pleasant like that, I'm afraid. isoSimple is like that of
> course, but once it gets to foldl, the fusion rule is handing the
> builder a wrap/unwrap pair that isn't even close to that.

and parametricity doesn’t help here? Note that due to the forall in the
type of buildW, you can probably reason about what kind of values buildW
can produce, as it can only use whatever the consumer handed to it.
Maybe there is an invariant for that type, and the worker/wrapper pair
is the identity for values that fulfill that invariant.

> > > Do you have any ideas?
> >
> > Directly related to foldrW, no.
> >
> > About list fusion and foldl in general, some half-baked.
> >
> > I once experimented with a magic "oneShot :: (a -> b) -> (a -> b)"
> > function, semantically the identity, but tell the compiler not to share
> > the result of the computation. Using that in the definition of
> > foldl-as-foldr, one can get the same effect as Call Arity, but a bit
> > more reliable. I need to investigate if that solves the sumConcatInits
> > problem.
> 
> How does that work exactly? Where do you stick the oneShot/

Quite simple, see the attached patch. I think I lost the corresponding
patch to base due to the merge, but all it did was to write

        foldl k z xs = foldr (\v fn -> oneShot (\ z -> fn ( k z v ))) id xs z

also see http://www.joachim-breitner.de/publications/CallArity-TFP.pdf
§6.2.

> why is it valid?

Because the type of build allows the builder to use each result of the
„constructor“ to be used once, and the whole result is called once, by
foldl, with z as the argument.

... at least if the list is finite. If build re-uses a result, then
because it builds an infinite list (e.g. in
        repeat x = build $ \c _ -> let r = x `c` r in r
) and I’m not quite sure if that is a problem. Probably not here,
because foldl applied to an infinite list is is ⊥ anyways. But with
others (e.g. scanl) I might be wrong and the oneShot trick might not
work there.


> > Another idea, probably with the same effect: What happens if we extend
> >         build :: (forall b. (a -> b -> b) -> b -> b) -> [a]
> > to
> >         buildI :: (forall b. (a -> b -> b) -> b -> (b -> b) -> b) -> [a]
> > where the extra argument is the identity, but magically „improves values
> > of type b“. So with
> >
> >         enum = buildI $ \c n imp -> go 0
> >           where go i = imp $ case i of 100 -> n ; _ -> i `c` go (i+1)
> >
> > and
> >
> >    foldl f a0 = foldrI (\x k a -> k (f x a)) id (\k a -> k a) a0
> >
> > we might get good code (but this is half-baked and written as I go).
> 
> It sounds a lot like the foldrW/buildW thing again, but maybe you can
> do better with it.

Yes, it is very much inspired by it, but possibly simpler, and much
weaker: It doesn’t try to undo the continuation style of foldl, but only
helps the compiler a bit. I don’t like it a lot, though.

Gruß,
Joachim

-- 
Joachim Breitner
  e-Mail: [email protected]
  Homepage: http://www.joachim-breitner.de
  Jabber-ID: [email protected]

commit f70ff9094bb89d2711ddccd92251dcfa74f86002
Author: Joachim Breitner <[email protected]>
Date:   Sun Jan 26 11:36:23 2014 +0000

    Add GHC.Prim.oneShot

diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs
index 604163f..c6fcbae 100644
--- a/compiler/basicTypes/MkId.lhs
+++ b/compiler/basicTypes/MkId.lhs
@@ -141,7 +141,8 @@ ghcPrimIds
     seqId,
     magicDictId,
     coerceId,
-    proxyHashId
+    proxyHashId,
+    oneShotId
     ]
 \end{code}
 
@@ -1040,7 +1041,7 @@ another gun with which to shoot yourself in the foot.
 \begin{code}
 lazyIdName, unsafeCoerceName, nullAddrName, seqName,
    realWorldName, voidPrimIdName, coercionTokenName,
-   magicDictName, coerceName, proxyName :: Name
+   magicDictName, coerceName, proxyName, oneShotName :: Name
 unsafeCoerceName  = mkWiredInIdName gHC_PRIM (fsLit "unsafeCoerce#") unsafeCoerceIdKey  unsafeCoerceId
 nullAddrName      = mkWiredInIdName gHC_PRIM (fsLit "nullAddr#")     nullAddrIdKey      nullAddrId
 seqName           = mkWiredInIdName gHC_PRIM (fsLit "seq")           seqIdKey           seqId
@@ -1051,6 +1052,7 @@ coercionTokenName = mkWiredInIdName gHC_PRIM (fsLit "coercionToken#") coercionTo
 magicDictName     = mkWiredInIdName gHC_PRIM (fsLit "magicDict")     magicDictKey magicDictId
 coerceName        = mkWiredInIdName gHC_PRIM (fsLit "coerce")        coerceKey          coerceId
 proxyName         = mkWiredInIdName gHC_PRIM (fsLit "proxy#")        proxyHashKey       proxyHashId
+oneShotName       = mkWiredInIdName gHC_MAGIC (fsLit "oneShot")       oneShotKey         oneShotId
 \end{code}
 
 \begin{code}
@@ -1131,6 +1133,17 @@ lazyId = pcMiscPrelId lazyIdName ty info
     info = noCafIdInfo
     ty  = mkForAllTys [alphaTyVar] (mkFunTy alphaTy alphaTy)
 
+oneShotId :: Id
+oneShotId = pcMiscPrelId oneShotName ty info
+  where
+    info = noCafIdInfo `setInlinePragInfo` (alwaysInlinePragma `setInlinePragmaActivation` ActiveAfter 0)
+                       `setUnfoldingInfo`  mkCompulsoryUnfolding rhs
+    ty  = mkForAllTys [alphaTyVar, betaTyVar] (mkFunTy fun_ty fun_ty)
+    fun_ty = mkFunTy alphaTy betaTy
+    [body, x] = mkTemplateLocals [fun_ty, alphaTy]
+    x' = setOneShotLambda x
+    rhs = mkLams [alphaTyVar, betaTyVar, body, x'] $ Var body `App` Var x
+
 
 --------------------------------------------------------------------------------
 magicDictId :: Id  -- See Note [magicDictId magic]
diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs
index 3f00c62..524912e 100644
--- a/compiler/prelude/PrelNames.lhs
+++ b/compiler/prelude/PrelNames.lhs
@@ -1684,10 +1684,11 @@ rootMainKey, runMainKey :: Unique
 rootMainKey                   = mkPreludeMiscIdUnique 101
 runMainKey                    = mkPreludeMiscIdUnique 102
 
-thenIOIdKey, lazyIdKey, assertErrorIdKey :: Unique
+thenIOIdKey, lazyIdKey, assertErrorIdKey, oneShotKey :: Unique
 thenIOIdKey                   = mkPreludeMiscIdUnique 103
 lazyIdKey                     = mkPreludeMiscIdUnique 104
 assertErrorIdKey              = mkPreludeMiscIdUnique 105
+oneShotKey                    = mkPreludeMiscIdUnique 106
 
 breakpointIdKey, breakpointCondIdKey, breakpointAutoIdKey,
     breakpointJumpIdKey, breakpointCondJumpIdKey,

Attachment: signature.asc
Description: This is a digitally signed message part

_______________________________________________
ghc-devs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/ghc-devs

Reply via email to