[Haskell-cafe] Question on Coerce

Brent Walker brenthwalker at gmail.com
Wed Dec 2 16:14:37 UTC 2020


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 <david.feuer at gmail.com> wrote:

> 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 <brenthwalker at gmail.com> 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.
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20201202/c2dd919d/attachment.html>


More information about the Haskell-Cafe mailing list