Lifting a value into a DataKind

Is it possible to automatically lift an arbitrary value into a type? i.e. I'm after a function of type `a -> Proxy (b :: a)`. More specifically, I'm wanting to be able to write a function that can convert an Enum (e.g. Bool or Ord) into such a Proxy, so I can actually write a function that looks like: `a -> (forall b. Proxy (b :: a) -> r) -> r` and use the `a` type as a selector value (to e.g. choose between type class instances). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

The singletons library's `toSing` (or `withSing`) may be what you want. Note that if you use Proxy, you won't be able to make any runtime decisions on the choice of `b`. Richard
On Feb 7, 2017, at 6:55 PM, Ivan Lazar Miljenovic
wrote: Is it possible to automatically lift an arbitrary value into a type? i.e. I'm after a function of type `a -> Proxy (b :: a)`.
More specifically, I'm wanting to be able to write a function that can convert an Enum (e.g. Bool or Ord) into such a Proxy, so I can actually write a function that looks like: `a -> (forall b. Proxy (b :: a) -> r) -> r` and use the `a` type as a selector value (to e.g. choose between type class instances).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.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.

Thanks for the suggestion; I think singletons is a bit of a large
hammer for a small bit of extra functionality I was thinking of adding
though (especially with people needing to use TH to make their
datatypes instances of SingI as well).
On 8 February 2017 at 12:55, Richard Eisenberg
The singletons library's `toSing` (or `withSing`) may be what you want. Note that if you use Proxy, you won't be able to make any runtime decisions on the choice of `b`.
Richard
On Feb 7, 2017, at 6:55 PM, Ivan Lazar Miljenovic
wrote: Is it possible to automatically lift an arbitrary value into a type? i.e. I'm after a function of type `a -> Proxy (b :: a)`.
More specifically, I'm wanting to be able to write a function that can convert an Enum (e.g. Bool or Ord) into such a Proxy, so I can actually write a function that looks like: `a -> (forall b. Proxy (b :: a) -> r) -> r` and use the `a` type as a selector value (to e.g. choose between type class instances).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.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.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

I fear, though, that you'll need a big hammer to be able to do what you want. Could you draw out your example a bit, and then we can see what the smaller hammer might look like. Richard
On Feb 7, 2017, at 10:32 PM, Ivan Lazar Miljenovic
wrote: Thanks for the suggestion; I think singletons is a bit of a large hammer for a small bit of extra functionality I was thinking of adding though (especially with people needing to use TH to make their datatypes instances of SingI as well).
On 8 February 2017 at 12:55, Richard Eisenberg
wrote: The singletons library's `toSing` (or `withSing`) may be what you want. Note that if you use Proxy, you won't be able to make any runtime decisions on the choice of `b`.
Richard
On Feb 7, 2017, at 6:55 PM, Ivan Lazar Miljenovic
wrote: Is it possible to automatically lift an arbitrary value into a type? i.e. I'm after a function of type `a -> Proxy (b :: a)`.
More specifically, I'm wanting to be able to write a function that can convert an Enum (e.g. Bool or Ord) into such a Proxy, so I can actually write a function that looks like: `a -> (forall b. Proxy (b :: a) -> r) -> r` and use the `a` type as a selector value (to e.g. choose between type class instances).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.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.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

As a sample implementation of the current state that I'd like to
simplify, see https://github.com/erikd/fastpack/blob/master/bench/bench.hs
(specifically, the `compareFunc` usage and the definition of
`withLibrary`).
I've found myself writing similar patterns of late and wanted to try
and automate it a bit. Specifically, it's the withLibrary function
I'm trying to work out how I could automatically generate for similar
types (as I've even written such type+function combinations in other
unrelated instances; I've found it a useful approach when I want to
select between typeclass instances).
On 8 February 2017 at 14:35, Richard Eisenberg
I fear, though, that you'll need a big hammer to be able to do what you want. Could you draw out your example a bit, and then we can see what the smaller hammer might look like.
Richard
On Feb 7, 2017, at 10:32 PM, Ivan Lazar Miljenovic
wrote: Thanks for the suggestion; I think singletons is a bit of a large hammer for a small bit of extra functionality I was thinking of adding though (especially with people needing to use TH to make their datatypes instances of SingI as well).
On 8 February 2017 at 12:55, Richard Eisenberg
wrote: The singletons library's `toSing` (or `withSing`) may be what you want. Note that if you use Proxy, you won't be able to make any runtime decisions on the choice of `b`.
Richard
On Feb 7, 2017, at 6:55 PM, Ivan Lazar Miljenovic
wrote: Is it possible to automatically lift an arbitrary value into a type? i.e. I'm after a function of type `a -> Proxy (b :: a)`.
More specifically, I'm wanting to be able to write a function that can convert an Enum (e.g. Bool or Ord) into such a Proxy, so I can actually write a function that looks like: `a -> (forall b. Proxy (b :: a) -> r) -> r` and use the `a` type as a selector value (to e.g. choose between type class instances).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.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.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

Is this the wrong link? I don't see any text matching compareFunc or withLibrary on that page... Sorry! Richard
On Feb 8, 2017, at 12:43 AM, Ivan Lazar Miljenovic
wrote: As a sample implementation of the current state that I'd like to simplify, see https://github.com/erikd/fastpack/blob/master/bench/bench.hs (specifically, the `compareFunc` usage and the definition of `withLibrary`).

Yeah, Erik ended up reverting those changes. Here's what it should
have been: https://github.com/ivan-m/fastpack/blob/ccf08a96e351b3a6ecac651971a1023f830c...
On 9 February 2017 at 13:31, Richard Eisenberg
Is this the wrong link? I don't see any text matching compareFunc or withLibrary on that page... Sorry!
Richard
On Feb 8, 2017, at 12:43 AM, Ivan Lazar Miljenovic
wrote: As a sample implementation of the current state that I'd like to simplify, see https://github.com/erikd/fastpack/blob/master/bench/bench.hs (specifically, the `compareFunc` usage and the definition of `withLibrary`).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

Ah. Now I get it! You originally described a type `a -> (forall b. Proxy (b :: a) -> r) -> r`, which doesn't seem very useful to me. The continuation function in there doesn't get any new information, so it can't make any decisions based on the choice of a. On the other hand, Erik's withLibrary has this type: `Library -> (forall (l :: Library). PutGet l => Proxy l -> k) -> k`. The key difference is that the continuation now has a constraint on it, which means a dictionary will be passed at runtime. Then, the proxy argument is useful, as it can be used to select the dictionary. So, perhaps this is what you want: with :: forall (a :: Type) (c :: a -> Constraint) (r :: Type). a -> (forall (b :: a). c b => Proxy b -> r) -> r `with` would look at the value of type `a` that has been provided, select a dictionary based on that choice, and then pass the dictionary to the continuation. Now, I can answer your original question: No, GHC can't do that. GHC internally is unaware of the relationship between, say, the value True and the type 'True. And even if it were, this would be a hard function to write, as it really does have to case-match at runtime to select the right dictionary. Given that the instances available might not exactly match the constructors of the type `a`, more processing might be necessary. It's conceivable, I suppose, that this ability could be baked in, but it would be non-trivial to do so. By the way, you're right that singletons is way too large a hammer for this. I would just do what Erik did. :) Richard
On Feb 8, 2017, at 10:40 PM, Ivan Lazar Miljenovic
wrote: Yeah, Erik ended up reverting those changes. Here's what it should have been: https://github.com/ivan-m/fastpack/blob/ccf08a96e351b3a6ecac651971a1023f830c...
On 9 February 2017 at 13:31, Richard Eisenberg
wrote: Is this the wrong link? I don't see any text matching compareFunc or withLibrary on that page... Sorry!
Richard
On Feb 8, 2017, at 12:43 AM, Ivan Lazar Miljenovic
wrote: As a sample implementation of the current state that I'd like to simplify, see https://github.com/erikd/fastpack/blob/master/bench/bench.hs (specifically, the `compareFunc` usage and the definition of `withLibrary`).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

On 10 February 2017 at 00:48, Richard Eisenberg
Ah. Now I get it!
You originally described a type `a -> (forall b. Proxy (b :: a) -> r) -> r`, which doesn't seem very useful to me. The continuation function in there doesn't get any new information, so it can't make any decisions based on the choice of a. On the other hand, Erik's withLibrary has this type: `Library -> (forall (l :: Library). PutGet l => Proxy l -> k) -> k`. The key difference is that the continuation now has a constraint on it, which means a dictionary will be passed at runtime. Then, the proxy argument is useful, as it can be used to select the dictionary.
So, perhaps this is what you want:
with :: forall (a :: Type) (c :: a -> Constraint) (r :: Type). a -> (forall (b :: a). c b => Proxy b -> r) -> r
`with` would look at the value of type `a` that has been provided, select a dictionary based on that choice, and then pass the dictionary to the continuation.
Now, I can answer your original question: No, GHC can't do that. GHC internally is unaware of the relationship between, say, the value True and the type 'True. And even if it were, this would be a hard function to write, as it really does have to case-match at runtime to select the right dictionary. Given that the instances available might not exactly match the constructors of the type `a`, more processing might be necessary. It's conceivable, I suppose, that this ability could be baked in, but it would be non-trivial to do so.
By the way, you're right that singletons is way too large a hammer for this. I would just do what Erik did. :)
Well, I wrote it in a pull request for Erik, but yes, it appears that just writing it each time is easier :)
Richard
On Feb 8, 2017, at 10:40 PM, Ivan Lazar Miljenovic
wrote: Yeah, Erik ended up reverting those changes. Here's what it should have been: https://github.com/ivan-m/fastpack/blob/ccf08a96e351b3a6ecac651971a1023f830c...
On 9 February 2017 at 13:31, Richard Eisenberg
wrote: Is this the wrong link? I don't see any text matching compareFunc or withLibrary on that page... Sorry!
Richard
On Feb 8, 2017, at 12:43 AM, Ivan Lazar Miljenovic
wrote: As a sample implementation of the current state that I'd like to simplify, see https://github.com/erikd/fastpack/blob/master/bench/bench.hs (specifically, the `compareFunc` usage and the definition of `withLibrary`).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com
participants (2)
-
Ivan Lazar Miljenovic
-
Richard Eisenberg