[Haskell-cafe] Fwd: Polymorphic updating with TC/TFs?

adam vogt vogt.adam at gmail.com
Tue Dec 17 05:03:24 UTC 2013


Hello Hans,

You can move the setFoo into a multiparameter type class, to which you
can add that constraint:

class (HasFoo a, HasFoo b, b ~ NoFoo a (Foo b))
     => SetFoo a b where
    setFoo :: Foo b -> a -> b

instance (HasFoo b, b ~ NoFoo (FooT f a) (Foo b))
    => SetFoo (FooT f a) b where
    setFoo f (FooT _ x)     = FooT f x

In my opinion, that's not as nice as the fundep solution which has less names:

class Has s t a b | s -> a, t -> b, s b -> t, t a -> s


On the topic of defining setFoo in terms of setFoo', you might be
interested in -XDefaultSignatures, which can work with the SetFoo
class defined above:

class HasFoo a where
    default setFoo' :: SetFoo a a => Foo a -> a -> a
    setFoo' = setFoo
    setFoo' :: Foo a -> a -> a

Finally, there seems to be some overlap with generic programming.
Changing type parameters isn't supported by the ones I know (syb), but
you can still fake it: <http://www.haskell.org/haskellwiki/SYB#fmap>.


Regards,
Adam

On Mon, Dec 16, 2013 at 7:37 PM, Hans Höglund <hans at hanshoglund.se> wrote:
> Hello,
>
> I am working with a set of type classes of the following form (http://lpaste.net/97110). The idea is that every such class provide an associated type Foo, and a lens to the Foo in every instance. I.e. this class is used to provide view/set/modify for all types that contain a Foo somewhere deep in its structure.
>
> For "simple lenses", i.e. functions that does not modify the associated Foo, this is straightforward. However to support polymorphic updates it seems necessary to add another associated type NoFoo, which must be used to constraint the return type of set.
>
> What bothers me is the redundancy of the two set functions. I would intuitively expect set' to be implemented in terms of set (as it seems to be a restriction of that function), but this is not possible, as the compiler can not deduce that (NoFoo a (Foo a) ~ a). Is there a way to add this constraint to the type class?
>
> Hans
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list