
In the following code, function fmap does not compile because variable 'y' on line marked <***> has type (Expr a) where an (Expr b) is expected. The code can be fixed simply by returning (Val x) on the rhs of the function but then we are allocating a new object for something we could potentially reuse since (Val n) has the same runtime representation in (Expr a) and (Expr b) (it has no dependence on the type variable). I was reading about coerce (Data.Coerce) recently and thought this could be a place it could be used but simply replacing the 'y' on the rhs with 'coerce y' does not compile (error message below). Is it possible to use coerce in this context? Thanks for any help, Brent ======================================= data Expr a = Var a | Val Int | Add (Expr a) (Expr a) deriving Show instance Functor Expr where fmap :: (a -> b) -> Expr a -> Expr b fmap f (Var a) = Var (f a) fmap f (Add e0 e1) = Add (fmap f e0) (fmap f e1) fmap _ y@(Val x) = y -- <***> ======================================= /dev/proj/src/Ex12.hs:69:22: error: • Couldn't match representation of type ‘a’ with that of ‘b’ arising from a use of ‘coerce’ ‘a’ is a rigid type variable bound by the type signature for: fmap :: forall a b. (a -> b) -> Expr a -> Expr b at /dev/proj/src/Ex12.hs:66:11-38 ‘b’ is a rigid type variable bound by the type signature for: fmap :: forall a b. (a -> b) -> Expr a -> Expr b at /dev/proj/src/Ex12.hs:66:11-38 • In the expression: coerce y In an equation for ‘fmap’: fmap _ y@(Val _) = coerce y In the instance declaration for ‘Functor Expr’ • Relevant bindings include y :: Expr a (bound at /dev/proj/src/Ex12.hs:69:10) fmap :: (a -> b) -> Expr a -> Expr b (bound at /dev/proj/src/Ex12.hs:67:3) | 69 | fmap _ y@(Val _) = coerce y | ^^^^^^^^ =======================================

You could use unsafeCoerce, but I don't think it's worth the risk. With the
plain code, GHC will *try* to recover sharing in cases like this late in
compilation, after the types are erased.
On Wed, Dec 2, 2020, 10:12 AM Brent Walker
In the following code, function fmap does not compile because variable 'y' on line marked <***> has type (Expr a) where an (Expr b) is expected. The code can be fixed simply by returning (Val x) on the rhs of the function but then we are allocating a new object for something we could potentially reuse since (Val n) has the same runtime representation in (Expr a) and (Expr b) (it has no dependence on the type variable).
I was reading about coerce (Data.Coerce) recently and thought this could be a place it could be used but simply replacing the 'y' on the rhs with 'coerce y' does not compile (error message below).
Is it possible to use coerce in this context?
Thanks for any help, Brent
======================================= data Expr a = Var a | Val Int | Add (Expr a) (Expr a) deriving Show
instance Functor Expr where fmap :: (a -> b) -> Expr a -> Expr b fmap f (Var a) = Var (f a) fmap f (Add e0 e1) = Add (fmap f e0) (fmap f e1) fmap _ y@(Val x) = y -- <***>
======================================= /dev/proj/src/Ex12.hs:69:22: error: • Couldn't match representation of type ‘a’ with that of ‘b’ arising from a use of ‘coerce’ ‘a’ is a rigid type variable bound by the type signature for: fmap :: forall a b. (a -> b) -> Expr a -> Expr b at /dev/proj/src/Ex12.hs:66:11-38 ‘b’ is a rigid type variable bound by the type signature for: fmap :: forall a b. (a -> b) -> Expr a -> Expr b at /dev/proj/src/Ex12.hs:66:11-38 • In the expression: coerce y In an equation for ‘fmap’: fmap _ y@(Val _) = coerce y In the instance declaration for ‘Functor Expr’ • Relevant bindings include y :: Expr a (bound at /dev/proj/src/Ex12.hs:69:10) fmap :: (a -> b) -> Expr a -> Expr b (bound at /dev/proj/src/Ex12.hs:67:3) | 69 | fmap _ y@(Val _) = coerce y | ^^^^^^^^ ======================================= _______________________________________________ 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.

Oops! I was very confused! Sorry, ignore that. I think ghc doesn't "know" which case you're in (after the pattern match) to allow the coercal. ======= Georgi

At least up to the core representation (generated with -O2) the
optimization you suggest has not happened (see the marked line below).
Does it happen further down the pipeline? Is there some flag I can use to
get some lower level representation to see that it actually does happen?
How does one get the final STG representation?
P.$fFunctorExpr_$cfmap
= \ (@ a_a5Tu)
(@ b_a5Tv)
(f_a5Sb :: a_a5Tu -> b_a5Tv)
(ds_d5Vm :: Expr a_a5Tu) ->
case ds_d5Vm of {
Var a1_a5Sc -> P.Var @ b_a5Tv (f_a5Sb a1_a5Sc);
Val x_a5Sg -> P.Val @ b_a5Tv x_a5Sg; <--
*****************************************
Add e0_a5Se e1_a5Sf ->
P.Add
@ b_a5Tv
(P.$fFunctorExpr_$cfmap @ a_a5Tu @ b_a5Tv f_a5Sb e0_a5Se)
(P.$fFunctorExpr_$cfmap @ a_a5Tu @ b_a5Tv f_a5Sb e1_a5Sf)
}
On Wed, Dec 2, 2020 at 5:22 PM David Feuer
You could use unsafeCoerce, but I don't think it's worth the risk. With the plain code, GHC will *try* to recover sharing in cases like this late in compilation, after the types are erased.
On Wed, Dec 2, 2020, 10:12 AM Brent Walker
wrote: In the following code, function fmap does not compile because variable 'y' on line marked <***> has type (Expr a) where an (Expr b) is expected. The code can be fixed simply by returning (Val x) on the rhs of the function but then we are allocating a new object for something we could potentially reuse since (Val n) has the same runtime representation in (Expr a) and (Expr b) (it has no dependence on the type variable).
I was reading about coerce (Data.Coerce) recently and thought this could be a place it could be used but simply replacing the 'y' on the rhs with 'coerce y' does not compile (error message below).
Is it possible to use coerce in this context?
Thanks for any help, Brent
======================================= data Expr a = Var a | Val Int | Add (Expr a) (Expr a) deriving Show
instance Functor Expr where fmap :: (a -> b) -> Expr a -> Expr b fmap f (Var a) = Var (f a) fmap f (Add e0 e1) = Add (fmap f e0) (fmap f e1) fmap _ y@(Val x) = y -- <***>
======================================= /dev/proj/src/Ex12.hs:69:22: error: • Couldn't match representation of type ‘a’ with that of ‘b’ arising from a use of ‘coerce’ ‘a’ is a rigid type variable bound by the type signature for: fmap :: forall a b. (a -> b) -> Expr a -> Expr b at /dev/proj/src/Ex12.hs:66:11-38 ‘b’ is a rigid type variable bound by the type signature for: fmap :: forall a b. (a -> b) -> Expr a -> Expr b at /dev/proj/src/Ex12.hs:66:11-38 • In the expression: coerce y In an equation for ‘fmap’: fmap _ y@(Val _) = coerce y In the instance declaration for ‘Functor Expr’ • Relevant bindings include y :: Expr a (bound at /dev/proj/src/Ex12.hs:69:10) fmap :: (a -> b) -> Expr a -> Expr b (bound at /dev/proj/src/Ex12.hs:67:3) | 69 | fmap _ y@(Val _) = coerce y | ^^^^^^^^ ======================================= _______________________________________________ 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.

This optimization happens after Core. Core is typed, and this optimization only makes sense after type erasure.
On Dec 2, 2020, at 9:16 AM, Brent Walker
wrote: At least up to the core representation (generated with -O2) the optimization you suggest has not happened (see the marked line below). Does it happen further down the pipeline?

You can only coerce between types that guaranteedly have the same runtime representation (newtypes), and "structures of them". Look up Coercible for more information. In this case, there is no way to know that two arbitrary types a and b have the same representation, so you can't coerce between them. ======= Georgi

Would it be possible to extend Coercible? I have also always wanted a coercible between the fixed point of the F-algebra and a recursive data type, e.g.: newtype Fix f = Fix (f (Fix f)) data List a = Nil | Cons a (List a) data ListF a f = NilF | ConsF a f deriving Functor type List' a = Fix (ListF a) I would like Coercible (List a) (Fix (ListF a)), then you don't have to manually write a conversion function when using a general catamorphism: cata :: (Functor f, Coercible a (Fix f)) => (f b -> b) -> (a -> b) I have already tried this with unsafeCoerce and that works, much to my surprise. It would be even nicer if GHC provided a built-in F-algebras, so that I wouldn't even need to define ListF manually. (I know that these F-algebras can be generated automatically with Template Haskell, but that is too heavyweight for most of my use cases) On 12/2/20 4:24 PM, Georgi Lyubenov wrote:
You can only coerce between types that guaranteedly have the same runtime representation (newtypes), and "structures of them". Look up Coercible for more information.
In this case, there is no way to know that two arbitrary types a and b have the same representation, so you can't coerce between them.
======= Georgi
_______________________________________________ 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.

On Wed, 2 Dec 2020, Brent Walker wrote:
In the following code, function fmap does not compile because variable 'y' on line marked <***> has type (Expr a) where an (Expr b) is expected. The code can be fixed simply by returning (Val x) on the rhs of the function but then we are allocating a new object for something we could potentially reuse since (Val n) has the same runtime representation in (Expr a) and (Expr b) (it has no dependence on the type variable).
Is it worth the trouble? It is only a leaf of the tree.

My question was on how to use coerce -- not whether this is worth doing or not. If we were discussing that, then I would say it's not 'just a leaf' -- it's ALL the leaves of the tree -- and for a tree of depth n, there are 2^n of them so depending on what 'n' is, it could potentially be something to worry about. On Wed, Dec 2, 2020 at 6:00 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 2 Dec 2020, Brent Walker wrote:
In the following code, function fmap does not compile because variable 'y' on line marked <***> has type (Expr a) where an (Expr b) is expected. The code can be fixed simply by returning (Val x) on the rhs of the function but then we are allocating a new object for something we could potentially reuse since (Val n) has the same runtime representation in (Expr a) and (Expr b) (it has no dependence on the type variable).
Is it worth the trouble? It is only a leaf of the tree.

coerce works when one type is a newtype wrapper for another, not when two
types happen to share the same runtime representation. I don't think ghc
can currently prove the latter except in the case of newtypes, especially
in the presence of optimizations.
On Wed, Dec 2, 2020 at 11:33 AM Brent Walker
My question was on how to use coerce -- not whether this is worth doing or not. If we were discussing that, then I would say it's not 'just a leaf' -- it's ALL the leaves of the tree -- and for a tree of depth n, there are 2^n of them so depending on what 'n' is, it could potentially be something to worry about.
On Wed, Dec 2, 2020 at 6:00 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 2 Dec 2020, Brent Walker wrote:
In the following code, function fmap does not compile because variable 'y' on line marked <***> has type (Expr a) where an (Expr b) is expected. The code can be fixed simply by returning (Val x) on the rhs of the function but then we are allocating a new object for something we could potentially reuse since (Val n) has the same runtime representation in (Expr a) and (Expr b) (it has no dependence on the type variable).
Is it worth the trouble? It is only a leaf of the tree.
_______________________________________________ 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.
-- brandon s allbery kf8nh allbery.b@gmail.com

Optimizations don't seem to make the problem much *harder* (Generics manage
to work out "decided strictness", including unpacking), but they do make it
less stable: whether two things have the same representation in memory may
depend on optimization flags.
On Wed, Dec 2, 2020, 12:19 PM Brandon Allbery
coerce works when one type is a newtype wrapper for another, not when two types happen to share the same runtime representation. I don't think ghc can currently prove the latter except in the case of newtypes, especially in the presence of optimizations.
On Wed, Dec 2, 2020 at 11:33 AM Brent Walker
wrote: My question was on how to use coerce -- not whether this is worth doing or not. If we were discussing that, then I would say it's not 'just a leaf' -- it's ALL the leaves of the tree -- and for a tree of depth n, there are 2^n of them so depending on what 'n' is, it could potentially be something to worry about.
On Wed, Dec 2, 2020 at 6:00 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 2 Dec 2020, Brent Walker wrote:
In the following code, function fmap does not compile because variable 'y' on line marked <***> has type (Expr a) where an (Expr b) is expected. The code can be fixed simply by returning (Val x) on the rhs of the function but then we are allocating a new object for something we could potentially reuse since (Val n) has the same runtime representation in (Expr a) and (Expr b) (it has no dependence on the type variable).
Is it worth the trouble? It is only a leaf of the tree.
_______________________________________________ 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.
-- brandon s allbery kf8nh allbery.b@gmail.com _______________________________________________ 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.

Coincidentally, I've been thinking about (a small part of) this issue for a
day or two. I think it would probably be pretty easy to add a language
feature that basically brought what the compiler does up to the Haskell
level. Imagine a sort of *generalized* as-pattern:
f x@@(Right y) = ...
`x` here is not bound to the actual argument; instead, it is bound to
`Right y`. The type of `x` will either be inferred or given explicitly:
f (x :: ...)@@(Right y) = ...
How can this translate to Core? Roughly speaking, it would look like
f _x = case _x of
Left p -> ...
Right y ->
let x = unsafeCoerce _x
in ...
But `x` would be given the unfolding `Right y`.
For existentials and GADTs, the type checking and Core translation needs
some extras. In particular, the dictionary arguments need to be included to
ensure the coercion is valid. Just make sure they match. The special ~ and
Coercible constraints don't need to be included in that check, but it must
be possible to produce coercions with the appropriate types.
On Wed, Dec 2, 2020, 11:32 AM Brent Walker
My question was on how to use coerce -- not whether this is worth doing or not. If we were discussing that, then I would say it's not 'just a leaf' -- it's ALL the leaves of the tree -- and for a tree of depth n, there are 2^n of them so depending on what 'n' is, it could potentially be something to worry about.
On Wed, Dec 2, 2020 at 6:00 PM Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Wed, 2 Dec 2020, Brent Walker wrote:
In the following code, function fmap does not compile because variable 'y' on line marked <***> has type (Expr a) where an (Expr b) is expected. The code can be fixed simply by returning (Val x) on the rhs of the function but then we are allocating a new object for something we could potentially reuse since (Val n) has the same runtime representation in (Expr a) and (Expr b) (it has no dependence on the type variable).
Is it worth the trouble? It is only a leaf of the tree.
_______________________________________________ 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 (7)
-
Brandon Allbery
-
Brent Walker
-
David Feuer
-
Georgi Lyubenov
-
Henning Thielemann
-
Jaro Reinders
-
Will Yager