Fixing Fix

Edward Kmett ekmett at gmail.com
Tue Mar 24 18:59:06 UTC 2015


For that version.

There are two viable definitions for Show

instance Show1 f => Show (Fix f)

instance Show (f (Fix f)) => Show (Fix f)

Similarly for Eq, Ord, Read.

The former is the style used in transformers 0.4+ adapted from what I did
in prelude-extras.

The latter is the style we had to use before, but which relies on
UndecidableInstances and FlexibleContexts.

-Edward

On Tue, Mar 24, 2015 at 2:41 PM, David Feuer <david.feuer at gmail.com> wrote:

> I don't understand what you're getting at, Edward. The specific type I
> mentioned, newtype Fix f = Fix (f (Fix f)), seems to be defined and used in
> various places. Are there important differences in the instances *for that
> type*? Or are you concerned about the higher-order versions?
>
> I'm also not at all committed to putting this in base, per se. I just
> don't like the fact that various unrelated packages with very different
> purposes are all doing the same thing, and that these identical types
> cannot be used together.
> On Mar 24, 2015 2:25 PM, "Edward Kmett" <ekmett at gmail.com> wrote:
>
>> History of indexed:
>>
>> The version of indexed on hackage was split out of my old category-extras
>> package by Reiner Pope. I asked a couple of years back if I could replace
>> it with a new version, and he said yes.
>>
>> The version on my github is my exploration of that design space. It was
>> stalled because of issues with GHC circa 7.6. Notably: Any inhabiting every
>> kind meant that it wasn't sound to assume that the only inhabitants of the
>> product kind (i,j) are of the form '(a, b) for a :: i, and b :: j. We've
>> fixed most of those issues in GHC 7.10, so in theory i could pick up my
>> indexed package and finish it. There are other issues still outstanding,
>> but that was the big one.
>>
>> I think there are enough points in this design space that I'm much much
>> happier to have this sort of thing in libraries that are removed from base
>> than having it in base itself. As an example: Making useful instances for
>> it requires either UndecidableInstances or switching to something like
>> Data.Functor.Classes or the machinery prelude-extras. I'm not terribly
>> comfortable with base making a bet on one such horse at the expense of the
>> others, and I'm even less comfortable moving the data type up where any
>> such instances would perforce be orphans if we didn't supply them.
>>
>> *tl;dr* -1
>>
>> -Edward
>>
>>
>> On Tue, Mar 24, 2015 at 1:00 PM, Oliver Charles <ollie at ocharles.org.uk>
>> wrote:
>>
>>> Oh, I see your confusion - you're looking at `indexed` on Hackage, but I
>>> meant the unreleased library on Github. That uses the slice category
>>> presentation of higher-order monads/functors, which is what you're talking
>>> about:
>>>
>>> https://github.com/ekmett/indexed/blob/master/src/Indexed/Functor.hs#L53
>>>
>>> Though HFix isn't there, but I feel it would be a suitable addition to
>>> the library.
>>>
>>> It is unfortunate that there is a name conflict.
>>>
>>> On Tue, Mar 24, 2015 at 4:28 PM, Erik Hesselink <hesselink at gmail.com>
>>> wrote:
>>>
>>>> That seems slightly different, more related to indexed monads with
>>>> pre- and postconditions. They have many more type variables...
>>>>
>>>> Erik
>>>>
>>>> On Tue, Mar 24, 2015 at 5:20 PM, Oliver Charles <ollie at ocharles.org.uk>
>>>> wrote:
>>>> > Higher order stuff is very useful, but I don't think it needs to
>>>> belong in
>>>> > the same place as Data.Functor.Fix. Edward Kmett's 'indexed' library
>>>> will
>>>> > probably deal with this, when we have a GHC that's smart enough to
>>>> > understand it ;)
>>>> >
>>>> > - Ollie
>>>> >
>>>> > On Tue, Mar 24, 2015 at 3:40 PM, Erik Hesselink <hesselink at gmail.com>
>>>> wrote:
>>>> >>
>>>> >> Ugh, you're right, I renamed the variables and made a mistake. The
>>>> >> outer variable should stay the same of course, your signature is
>>>> >> correct.
>>>> >>
>>>> >> For a use site of HFix, see the multirec package [0], although that
>>>> >> might not really clarify things :) We also have a use internally, but
>>>> >> I just realized we can probably simplify that away.
>>>> >>
>>>> >> Regards,
>>>> >>
>>>> >> Erik
>>>> >>
>>>> >> [0]
>>>> >>
>>>> http://hackage.haskell.org/package/multirec-0.7.5/docs/Generics-MultiRec-HFix.html
>>>> >>
>>>> >> On Tue, Mar 24, 2015 at 4:25 PM, David Feuer <david.feuer at gmail.com>
>>>> >> wrote:
>>>> >> > I have no comment on your higher-order version (because I don't
>>>> >> > understand
>>>> >> > it yet), but the type you give for hmap looks unlikely. Did you
>>>> mean
>>>> >> >
>>>> >> > hmap :: (g :-> h) -> f g :-> f h ?
>>>> >> >
>>>> >> > On Mar 24, 2015 10:58 AM, "Erik Hesselink" <hesselink at gmail.com>
>>>> wrote:
>>>> >> >>
>>>> >> >> On Tue, Mar 24, 2015 at 7:23 AM, M Farkas-Dyck <
>>>> strake888 at gmail.com>
>>>> >> >> wrote:
>>>> >> >> > On 22/03/2015 at 23:01:47 -0400, David Feuer wrote:
>>>> >> >> >> There are a good number of different packages that define
>>>> either
>>>> >> >> >>
>>>> >> >> >> newtype Fix f = Fix (f (Fix f))
>>>> >> >> >>
>>>> >> >> >> or something equivalent except for naming. Most of the name
>>>> >> >> >> variation
>>>> >> >> >> is in the name of the data constructor and/or record selector.
>>>> This
>>>> >> >> >> does not look like an ideal situation to me. Most
>>>> problematically,
>>>> >> >> >> the
>>>> >> >> >> only way to convert one to another is with unsafeCoerce.
>>>> >> >> >>
>>>> >> >> >> I think it would be rather nice to choose one canonical place
>>>> for
>>>> >> >> >> this
>>>> >> >> >> definition, and let everyone else use it.
>>>> >> >> >
>>>> >> >> > +1
>>>> >> >> >
>>>> >> >> > I propose
>>>> >> >> >
>>>> >> >> > module Data.Fix where
>>>> >> >> >
>>>> >> >> > newtype Fix f = Fix { unFix :: f (Fix f) }
>>>> >> >>
>>>> >> >> I'm used to
>>>> >> >>
>>>> >> >>     newtype Fix f = In { out : f (Fix f) }
>>>> >> >>
>>>> >> >> But all the other suggestions look fine to me, too.
>>>> >> >>
>>>> >> >> I've also often used this variation:
>>>> >> >>
>>>> >> >>     newtype HFix f a = In { out :: f (HFix f) a }
>>>> >> >>
>>>> >> >> This allows you to take the fixed point of e.g. monad stacks and
>>>> >> >> indexed types. The function you propose below can then be a type
>>>> class
>>>> >> >> function of an indexed Functor class:
>>>> >> >>
>>>> >> >>     type f :-> g = forall a. f a -> g a
>>>> >> >>
>>>> >> >>     class HFunctor f where
>>>> >> >>       hmap :: (a :-> b) -> f a :-> g a
>>>> >> >>
>>>> >> >> Does this deserve a place somewhere as well? Or is it too
>>>> specialized?
>>>> >> >>
>>>> >> >> > Perhaps too we ought to name and define _ :: (∀ a . f a -> g a)
>>>> ->
>>>> >> >> > Fix f
>>>> >> >> > -> Fix g there.
>>>> >> >>
>>>> >> >> Some variation of 'map' seems sensible, like 'hmap' (but see
>>>> above) or
>>>> >> >> 'mapFix'.
>>>> >> >>
>>>> >> >> Erik
>>>> >> _______________________________________________
>>>> >> Libraries mailing list
>>>> >> Libraries at haskell.org
>>>> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>>> >
>>>> >
>>>>
>>>
>>>
>>> _______________________________________________
>>> Libraries mailing list
>>> Libraries at haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>>
>>>
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>
>>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20150324/890d3ce0/attachment-0001.html>


More information about the Libraries mailing list