> Can you be a bit more precise about what you are doing? Constructing
> core like this is quite hairy.

I'm modifying TcGenGenerics to use an experimental representation type that leverages ConstraintKinds (and thus constraint tuples) in its type. The function I'm modifying is tc_mkRepTy [1], which constructs the Core Type that's used for Rep/Rep1 in derived Generic instances.

> The "tuple" part doesn't really exist in core

Sure it does! It does in this code, at least:

    data Foo c a where
      MkFoo :: c => a -> Foo c a
   
    f :: Foo (Eq a, Show a) -> String
    f (MkFoo x) = show x

According to ghci -ddump-simpl, that gives you the following (unoptimized) Core:

    f :: forall a. Foo (Eq a, Show a) a -> String
    f = \ (@ a_a2RQ)
          (ds_d2S2 :: Foo (Eq a_a2RQ, Show a_a2RQ) a_a2RQ) ->
          case ds_d2S2 of { MkFoo $d(%,%)_a2RS x_a2Ry ->
          show
            @ a_a2RQ
            (GHC.Classes.$p2(%,%) @ (Eq a_a2RQ) @ (Show a_a2RQ) $d(%,%)_a2RS)
            x_a2Ry
          }

Notice the $d(%,%)_a2RS and $p2(%,%) bits, which correspond to a constraint tuple dictionary and one of its superclass selectors, respectively.

Ryan S.
-----
[1] http://git.haskell.org/ghc.git/blob/26e9806ada8823160dd63ca2c34556e5848b2f45:/compiler/typecheck/TcGenGenerics.hs#l513


On Tue, Jun 19, 2018 at 1:09 PM Matthew Pickering <matthewtpickering@gmail.com> wrote:
Can you be a bit more precise about what you are doing? Constructing
core like this is quite hairy.

The "tuple" part doesn't really exist in core, a constraint tuple is
curried. So foo :: (C1 a, C2 a) => ... desugars to `foo = /\ a . \
$dC1 . \$dC2 -> ...`.

Cheers,

Matt



On Tue, Jun 19, 2018 at 4:48 PM, Ryan Scott <ryan.gl.scott@gmail.com> wrote:
> Unfortunately, I can't directly use tc_tuple, since I don't have access to
> the Haskell AST forms I need to make that work (I'm constructing everything
> directly in Core). On the other hand, the implementation of tc_tuple does
> have one nugget of wisdom in that it reveals how GHC creates a constraint
> tuple *type constructor*. Namely, `tcLookupTyCon (cTupleTyConName arity)`
> for some `arity`.
>
> That's still a bit inconvenient, as `tcLookupTyCon` forces me to work in a
> monadic context (whereas the code I've been working on has been pure up to
> this point). Is there not a pure way to retrieve a constraint tuple type
> constructor?
>
> Ryan S.
>
> On Tue, Jun 19, 2018 at 10:07 AM Matthew Pickering
> <matthewtpickering@gmail.com> wrote:
>>
>> How about `tc_tuple`?
>>
>> On Tue, Jun 19, 2018 at 2:53 PM, Ryan Scott <ryan.gl.scott@gmail.com>
>> wrote:
>> > I'm currently working on some code in which I need to produce a Core
>> > Type
>> > that mentions a constraint tuple. I thought that there must surely exist
>> > some way to construct a constraint tuple using the GHC API, but to my
>> > astonishment, I could not find anything. The closest thing I found was
>> > mk_tuple [1], which gives you the ability to make boxed and unboxed
>> > tuples,
>> > but not constraint tuples.
>> >
>> > I then thought to myself, "But wait, PartialTypeSignatures has to create
>> > constraint tuples, right? How does that part of the code work?" To my
>> > horror, I discovered that PartialTypeSignatures actually creates *boxed*
>> > tuples (see mk_ctuple here [2]), then hackily treats them as constraint
>> > tuples, as explained in Note [Extra-constraint holes in partial type
>> > signatures] [3]. I tried reading that Note, but I couldn't follow the
>> > details.
>> >
>> > Is there a simpler way to create a constraint tuple that I'm not aware
>> > of?
>> >
>> > Ryan S.
>> > -----
>> > [1]
>> >
>> > http://git.haskell.org/ghc.git/blob/676c5754e3f9e1beeb5f01e0265ffbdc0e6f49e9:/compiler/prelude/TysWiredIn.hs#l810
>> > [2]
>> >
>> > http://git.haskell.org/ghc.git/blob/676c5754e3f9e1beeb5f01e0265ffbdc0e6f49e9:/compiler/typecheck/TcBinds.hs#l1036
>> > [3]
>> >
>> > http://git.haskell.org/ghc.git/blob/676c5754e3f9e1beeb5f01e0265ffbdc0e6f49e9:/compiler/typecheck/TcHsType.hs#l2367
>> >
>> > _______________________________________________
>> > ghc-devs mailing list
>> > ghc-devs@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>> >