new-typeable, new cast?

Richard Eisenberg eir at cis.upenn.edu
Wed Jul 31 10:38:06 CEST 2013


 From these recent emails, I understand we wish to make two changes:

1) Add a {-# LANGUAGE Trustworthy #-} pragma.

2) Add the asProxyTypeOf function.

As for the instances' behavior being different from GHC's generated 
versions, I think the lazier ones (as implemented) are probably more 
useful. In the end though, I didn't think too much about it -- I was 
just implementing the proposal on 
http://ghc.haskell.org/trac/ghc/wiki/TypeLevelReasoning, which includes 
the instances as pushed.

If I don't hear otherwise by the end of the day, I'll push these 
changes.

Richard

On 2013-07-31 00:35, Edward Kmett wrote:
> I would really want to keep asProxyTypeOf around as it is commonly
> used and has no other plausible home within tagged. 
> 
> reproxy is quite negotiable.
> 
> Ever since its signature was generalized a version or two ago in
> tagged, it has started to feel quite silly.
> 
> If I move
> 
> coerce :: (Functor f, Contravariant f) => f a -> f b
> coerce = contramap absurd . fmap absurd -- using absurd from 'void'
>  -- or equivalently:  coerce = contramap (const ()) . fmap (const ())
> 
> from lens up into the contravariant package, then the role that
> function plays can be replaced entirely with that more general purpose
> combinator in "user land" without needing any funny looking functions
> in base.
> 
> Proxy is both Contravariant and a normal covariant Functor as it
> doesn't use its argument, just like Const m. reproxy originally
> witnessed this fact just for Proxy, but that fact in its broader
> generality has since been exploited to make getters and folds in lens,
> so reproxy is basically just residue of an old approach.
> 
> -Edward
> 
> On Tue, Jul 30, 2013 at 6:44 PM, Shachaf Ben-Kiki <shachaf at gmail.com>
> wrote:
> 
>> On Mon, Jul 22, 2013 at 1:23 AM, José Pedro Magalhães
>> <jpm at cs.uu.nl> wrote:
>>> Thanks for bringing this up again. This was started in my
>> data-proxy branch
>>> of base,
>>> but never really finished. We definitely want to have this in
>> 7.8, and I
>>> think there's
>>> only some minor finishing work to do (check if we have all the
>> instances we
>>> want,
>>> document, etc.). Perhaps you can look through what's there
>> already, and what
>>> you
>>> think is missing? I'm more than happy to accept contributing
>> patches too :-)
>>> 
>>> 
>> 
>> I'm looking at the current state of Data.Proxy in base (it looks
>> like
>> Richard merged data-proxy into master) and it looks pretty good
>> instance-wise. Issues I'm aware of:
>> 
>> * It looks like there's a SafeHaskell issue -- should this be
>> marked
>> Trustworthy? See https://github.com/ekmett/tagged/pull/13 [1]
>> * tagged's Data.Proxy defines some useful functions that aren't
>> present in base. Two of them can move into tagged's Data.Tagged,
>> but
>> the other two should probably go in base's Data.Proxy. In
>> particular
>> 
>> asProxyTypeOf :: a -> proxy a -> a
>> asProxyTypeOf = const
>> 
>> reproxy :: proxy s -> Proxy t
>> reproxy _ = Proxy
>> 
>> When these are fixed, tagged can probably shuffle a couple of
>> functions around and then use base's Data.Proxy rather than
>> exporting
>> its own module (for GHC ≥ 7.7).
>> 
>> (By the way: Some instances are slightly different from what GHC
>> would
>> derive -- e.g. «_ == _ = True» is different from «Proxy == Proxy
>> =
>> True», which is ()'s Eq behavior. I think this is OK but I wanted
>> to
>> mention it.)
>> 
>> Thanks,
>> 
>>     Shachaf
>> 
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries [2]
> 
> 
> 
> Links:
> ------
> [1] https://github.com/ekmett/tagged/pull/13
> [2] http://www.haskell.org/mailman/listinfo/libraries
> 
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries




More information about the Libraries mailing list