Fixing Fix

Erik Hesselink hesselink at gmail.com
Tue Mar 24 14:58:36 UTC 2015


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


More information about the Libraries mailing list