Creating polymorphic lens

我的未来我决定 提交于 2019-12-14 02:09:21

问题


I am able to create a lens for the last field (c) in my data types by doing the follow:

{-# LANGUAGE DuplicateRecordFields #-}

data X1 a c = X1 { a' :: a, b' :: Int, c' :: c } 

data X2 a b c = X2 { a' :: a, b' :: b, c' :: c }

class HavingFieldC x cs ct where
  c :: Functor f => (cs -> f ct) -> x cs -> f (x ct)

instance HavingFieldC (X1 a) cs ct  where
  c = lens
    (\X1 { c' } -> c')
    (\X1 {..} v -> X1 {c' = v, ..})

instance HavingFieldC (X2 a b) cs ct where
  c = lens
    (\X2 { c' } -> c')
    (\X2 {..} v -> X2 {c' = v, ..})

Is there something similar I can do for fields a and b


回答1:


You can generalize the definition of the HavingField class; in particular, you can express the relationship between the updated type variable and the record type using functional dependencies. This allows the update type variable to occur in any position; and it allows updates to monomorphic fields.

class FieldC k k' x x' | k x' -> k', k' x -> k, k -> x, k' -> x' where
  fieldC :: Functor f => (x -> f x') -> k -> f k'

instance (b ~ b0, b' ~ b0') => FieldC (X1 a b) (X1 a b') b0 b0' where ...
instance (b ~ b0, b' ~ b0') => FieldC (X2 c a b) (X2 c a b') b0 b0' where ...

You define instances in much the same way; note that some of the equality constraints are placed in the context to improve type inference. You can read the first instance above as instance FieldC (X1 a b) (X1 a b') b b'.

The classes for other fields are defined in exactly the same way; this is essentially the most general way to define a class for lenses (which should be more apparent if one notes that the type of fieldC is actually just Lens k k' x x').

class FieldA k k' x x' | k x' -> k', k' x -> k, k -> x, k' -> x' where
  fieldA :: Functor f => (x -> f x') -> k -> f k'

class FieldB k k' x x' | k x' -> k', k' x -> k, k -> x, k' -> x' where
  fieldB :: Functor f => (x -> f x') -> k -> f k'

(Note: this too can be generalized to a single class with an additional parameter corresponding to the field name; this is probably outside the scope of this question).

Now it should be clearer how to write the instance declarations:

instance (x0 ~ Int, x1 ~ Int) => FieldB (X1 a c) (X1 a c) x0 x1 where ...
instance (b0 ~ b, b0' ~ b') => FieldB (X2 a b c) (X2 a b' c) b0 b0' where ...

instance (a ~ a0, a' ~ a0') => FieldA (X1 a c) (X1 a' c) a0 a0' where ...
instance (a0 ~ a, a0' ~ a') => FieldA (X2 a b c) (X2 a' b c) a0 a0' where ...

The only difference for monomorphic fields being that the field types are monomorphic types.

A simple test will show that the proper polymorphic types are assigned:

foo x = 
  let y = view fieldB x
  in set fieldA (2 * y) $ set fieldC (3 + y) x

You can ask GHCi for the inferred types at particular instantiations:

\x -> foo x `asTypeOf` X1{} :: X1 a b -> X1 Int Int
\x -> foo x `asTypeOf` X2{} :: Num a0' => X2 a a0' b -> X2 a0' a0' a0'

This general pattern can be found implemented e.g. here. This implementation is slightly more permissive; the f in Functor f => .. is a typeclass parameter instead of being universally quantified over. Depending on your specific use cases, this may or may not work for you.



来源:https://stackoverflow.com/questions/47270018/creating-polymorphic-lens

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!