
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
On Tue, Mar 24, 2015 at 2:23 AM, M Farkas-Dyck
I propose
module Data.Fix where
I'd move it to Data.Functor.Fix, so as to help clean up the Data.Everything situation
newtype Fix f = Fix { unFix :: f (Fix f) }
One issue with this particular definition is that the derived Show instance (if any) is quite verbose and ugly. For this sort of newtype construction, I typically define unFoo as a function rather than using the record notation precisely to clean up such noise.
Perhaps too we ought to name and define _ :: (∀ a . f a -> g a) -> Fix f -> Fix g there.
The big question here is what to call it. And, really, we probably want all the functions from unification-fd:Data.Functor.Fixedpoint (perhaps excluding all the y- functions). -- Live well, ~wren