
Given: data D a = A a | B Int Char dmapNoCoerce :: (a -> b) -> D a -> D b dmapNoCoerce f (A a) = A (f a) dmapNoCoerce _ (B i c) = B i c I have to reconstruct a B change it from D a to D b. But at the lower level, couldn't this be implemented as a type cast? What prevents such an optimization? I can write this as dmapCoerce :: (a -> b) -> D a -> D b dmapCoerce f (A a) = A (f a) dmapCoerce _ b@(B {}) = Unsafe.Coerce.unsafeCoerce b
From the core, it looks like dmapCoerce indeed has a cast with no allocation, while dmapNoCoerce allocates a new B.
It seems to work, but is it safe? Is there a more principled way to do it? I can't convince Data.Coerce to cooperate, presumably because 'a' and 'b' are not coercible themselves, and it doesn't believe me if I try to tell it the type role is phantom.

Hi, Am Mittwoch, den 13.12.2017, 21:34 -0800 schrieb Evan Laforge:
Given:
data D a = A a | B Int Char
dmapNoCoerce :: (a -> b) -> D a -> D b dmapNoCoerce f (A a) = A (f a) dmapNoCoerce _ (B i c) = B i c
I have to reconstruct a B change it from D a to D b. But at the lower level, couldn't this be implemented as a type cast? What prevents such an optimization?
I can write this as
dmapCoerce :: (a -> b) -> D a -> D b dmapCoerce f (A a) = A (f a) dmapCoerce _ b@(B {}) = Unsafe.Coerce.unsafeCoerce b
From the core, it looks like dmapCoerce indeed has a cast with no allocation, while dmapNoCoerce allocates a new B.
It seems to work, but is it safe? Is there a more principled way to do it? I can't convince Data.Coerce to cooperate, presumably because 'a' and 'b' are not coercible themselves, and it doesn't believe me if I try to tell it the type role is phantom.
this coercion is not possible in Core, because Core’s type system is not expressive enough (at least now…). But luckily, at the STG level this optimization is possible, see https://git.haskell.org/ghc.git/commitdiff/19d5c7312bf0ad9ae764168132aecf369... This is probably in 8.2. Joachim -- Joachim Breitner mail@joachim-breitner.de http://www.joachim-breitner.de/

Nice, it looks like "Note [Case 2: CSEing case binders]" applies to
what I was talking about.
I assume once I can upgrade to 8.2 (or 8.4 more likely) then both my
examples should wind up looking different at the core level, but then
both be a coerce in STG? Well, I guess implicitly a coerce since STG
doesn't have types like that.
On Thu, Dec 14, 2017 at 7:16 AM, Joachim Breitner
Hi,
Am Mittwoch, den 13.12.2017, 21:34 -0800 schrieb Evan Laforge:
Given:
data D a = A a | B Int Char
dmapNoCoerce :: (a -> b) -> D a -> D b dmapNoCoerce f (A a) = A (f a) dmapNoCoerce _ (B i c) = B i c
I have to reconstruct a B change it from D a to D b. But at the lower level, couldn't this be implemented as a type cast? What prevents such an optimization?
I can write this as
dmapCoerce :: (a -> b) -> D a -> D b dmapCoerce f (A a) = A (f a) dmapCoerce _ b@(B {}) = Unsafe.Coerce.unsafeCoerce b
From the core, it looks like dmapCoerce indeed has a cast with no allocation, while dmapNoCoerce allocates a new B.
It seems to work, but is it safe? Is there a more principled way to do it? I can't convince Data.Coerce to cooperate, presumably because 'a' and 'b' are not coercible themselves, and it doesn't believe me if I try to tell it the type role is phantom.
this coercion is not possible in Core, because Core’s type system is not expressive enough (at least now…). But luckily, at the STG level this optimization is possible, see https://git.haskell.org/ghc.git/commitdiff/19d5c7312bf0ad9ae764168132aecf369...
This is probably in 8.2.
Joachim
-- Joachim Breitner mail@joachim-breitner.de http://www.joachim-breitner.de/
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi, Am Donnerstag, den 14.12.2017, 16:53 -0800 schrieb Evan Laforge:
Nice, it looks like "Note [Case 2: CSEing case binders]" applies to what I was talking about.
I assume once I can upgrade to 8.2 (or 8.4 more likely) then both my examples should wind up looking different at the core level, but then both be a coerce in STG? Well, I guess implicitly a coerce since STG doesn't have types like that.
precisely:
$ ghc-8.2 -O -ddump-stg test.hs
[1 of 1] Compiling Foo ( test.hs, test.o )
…
==================== STG syntax: ====================
Foo.dmapNoCoerce :: forall a b. (a -> b) -> Foo.D a -> Foo.D b
[GblId,
Arity=2,
Caf=NoCafRefs,
Str=,
Unf=OtherCon []] =
\r [f_s15C ds_s15D]
case ds_s15D of {
Foo.A a1_s15F [Occ=Once] ->
let {
sat_s15G [Occ=Once] :: b_aTu
[LclId] =
\u [] f_s15C a1_s15F;
} in Foo.A [sat_s15G];
Foo.B i_s15H [Occ=Once] c_s15I [Occ=Once] -> wild_s15E;
};
…
The pretty-printing is actually a bit broken, but the wild_s15E is the
case-binder of the "case ds_s15D" construct.
Joachim
--
Joachim Breitner
mail@joachim-breitner.de
http://www.joachim-breitner.de/

Joachim, in the commit message you remark that
This CSE pass only targets data constructor applications. This is probably the best we can do, as function calls and primitive operations might have side-effects.
While it's true that function calls may have side effects, I imagine
you can probably
dig up the has_side_effects values for primops and use those.
On Thu, Dec 14, 2017 at 10:16 AM, Joachim Breitner
Hi,
Am Mittwoch, den 13.12.2017, 21:34 -0800 schrieb Evan Laforge:
Given:
data D a = A a | B Int Char
dmapNoCoerce :: (a -> b) -> D a -> D b dmapNoCoerce f (A a) = A (f a) dmapNoCoerce _ (B i c) = B i c
I have to reconstruct a B change it from D a to D b. But at the lower level, couldn't this be implemented as a type cast? What prevents such an optimization?
I can write this as
dmapCoerce :: (a -> b) -> D a -> D b dmapCoerce f (A a) = A (f a) dmapCoerce _ b@(B {}) = Unsafe.Coerce.unsafeCoerce b
From the core, it looks like dmapCoerce indeed has a cast with no allocation, while dmapNoCoerce allocates a new B.
It seems to work, but is it safe? Is there a more principled way to do it? I can't convince Data.Coerce to cooperate, presumably because 'a' and 'b' are not coercible themselves, and it doesn't believe me if I try to tell it the type role is phantom.
this coercion is not possible in Core, because Core’s type system is not expressive enough (at least now…). But luckily, at the STG level this optimization is possible, see https://git.haskell.org/ghc.git/commitdiff/19d5c7312bf0ad9ae764168132aecf369...
This is probably in 8.2.
Joachim
-- Joachim Breitner mail@joachim-breitner.de http://www.joachim-breitner.de/
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (3)
-
David Feuer
-
Evan Laforge
-
Joachim Breitner