关于通过几个嵌套的函子级别进行映射 [英] About mapping through several nested functorial levels

查看:21
本文介绍了关于通过几个嵌套的函子级别进行映射的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

随机示例:给定以下 [Maybe [a]],

A random example: given the following [Maybe [a]],

x = [Just [1..3], Nothing, Just [9]]

我想通过3层映射f = (^2),从而得到

I want to map f = (^2) through the 3 layers, thus obtaining

[Just [1,4,9],Nothing,Just [81]]

最简单的方法似乎是

(fmap . fmap . fmap) (^2) x

where fmap .地图.fmap 类似于 fmap,但它有 3 层深.

where fmap . fmap . fmap is like fmap, but it goes 3 levels deep.

我怀疑需要这样的东西,在将 fmap 与自身组合给定次数的一般情况下,是并不少见,所以我想知道标准中是否已经有一些东西可以将 fmap 与自身组合一定次数.或者也许是知道"的东西它应该根据输入将 fmap 与自身组合多少次.

I suspect that the need for something like this, in the general case of composing fmap with itself a given number of times, is not uncommon, so I wonder if there's already something in the standard to compose fmap with itself a certain number of times. Or maybe something which "knows" how many times it should compose fmap with itself based on the input.

推荐答案

这个答案受到 DDub 的启发,但我认为它更简单,它应该提供更好的类型推断和可能更好的类型错误.让我们先清清嗓子:

This answer is inspired by DDub's, but I think it's rather simpler, and it should offer slightly better type inference and probably better type errors. Let's first clear our throats:

{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language MultiParamTypeClasses #-}
{-# language DataKinds #-}
{-# language AllowAmbiguousTypes #-}
{-# language UndecidableInstances #-}
{-# language ScopedTypeVariables #-}
module DMap where
import Data.Kind (Type)
import GHC.TypeNats

GHC 的内置 Nat 使用起来非常尴尬,因为我们无法在非 0"上进行模式匹配.所以让我们让它们只是接口的一部分,并在实现中避免它们.

GHC's built-in Nats are pretty awkward to work with, because we can't pattern match on "not 0". So let's make them just part of the interface, and avoid them in the implementation.

-- Real unary naturals
data UNat = Z | S UNat

-- Convert 'Nat' to 'UNat' in the obvious way.
type family ToUnary (n :: Nat) where
  ToUnary 0 = 'Z
  ToUnary n = 'S (ToUnary (n - 1))

-- This is just a little wrapper function to deal with the
-- 'Nat'-to-'UNat' business.
dmap :: forall n s t a b. DMap (ToUnary n) s t a b
     => (a -> b) -> s -> t
dmap = dmap' @(ToUnary n)

既然我们已经解决了完全无聊的部分,剩下的就变得非常简单了.

Now that we've gotten the utterly boring part out of the way, the rest turns out to be pretty simple.

-- @n@ indicates how many 'Functor' layers to peel off @s@
-- and @t@ to reach @a@ and @b@, respectively.
class DMap (n :: UNat) s t a b where
  dmap' :: (a -> b) -> s -> t

我们如何编写实例?让我们从显而易见的方式开始,然后将其转化为可以提供更好推理的方式.显而易见的方法:

How do we write the instances? Let's start with the obvious way, and then transform it into a way that will give better inference. The obvious way:

instance DMap 'Z a b a b where
  dmap' = id

instance (Functor f, DMap n x y a b)
  => DMap ('S n) (f x) (f y) a b where
  dmap' = fmap . dmap' @n

这样写的麻烦是多参数实例解析的常见问题.如果 GHC 看到第一个参数是 'Z 并且 第二个和第四个参数相同 第三个参数,GHC 只会选择第一个实例和第五个参数是一样的.同样,如果它看到第一个参数是'S 并且第二个参数是一个应用程序第三个​​参数,它只会选择第二个实例参数是一个应用程序并且在第二个和第三个参数中应用的构造函数是相同的.

The trouble with writing it this way is the usual problem with multi-parameter instance resolution. GHC will only choose the first instance if it sees that the first argument is 'Z and the second and fourth arguments are the same and the third and fifth arguments are the same. Similarly, it will only choose the second instance if it sees that the first argument is 'S and the second argument is an application and the third argument is an application and the constructors applied in the second and third arguments are the same.

我们希望在我们知道第一个参数后立即选择正确的实例.我们可以通过简单地将其他所有内容移到双箭头左侧来实现:

We want to choose the right instance as soon as we know the first argument. We can do that by simply shifting everything else to the left of the double arrow:

-- This stays the same.
class DMap (n :: UNat) s t a b where
  dmap' :: (a -> b) -> s -> t

instance (s ~ a, t ~ b) => DMap 'Z s t a b where
  dmap' = id

-- Notice how we're allowed to pull @f@, @x@,
-- and @y@ out of thin air here.
instance (Functor f, fx ~ (f x), fy ~ (f y), DMap n x y a b) 
  => DMap ('S n) fx fy a b where
  dmap' = fmap . dmap' @ n

现在,我在上面声称这提供了比 DDub 更好的类型推断,所以我最好支持它.让我拉起GHCi:

Now, I claimed above that this gives better type inference than DDub's, so I'd better back that up. Let me just pull up GHCi:

*DMap> :t dmap @3
dmap @3
  :: (Functor f1, Functor f2, Functor f3) =>
     (a -> b) -> f1 (f2 (f3 a)) -> f1 (f2 (f3 b))

这正是 fmap.fmap.fmap 的类型.完美的!使用 DDub 的代码,我反而得到

That's precisely the type of fmap.fmap.fmap. Perfect! With DDub's code, I instead get

dmap @3
  :: (DMap (FType 3 c), DT (FType 3 c) a ~ c,
      FType 3 (DT (FType 3 c) b) ~ FType 3 c) =>
     (a -> b) -> c -> DT (FType 3 c) b

这是……不太清楚.正如我在评论中提到的,这可以解决,但它给已经有些复杂的代码增加了一点复杂性.

which is ... not so clear. As I mentioned in a comment, this could be fixed, but it adds a bit more complexity to code that is already somewhat complicated.

为了好玩,我们可以使用 traversefoldMap 来实现相同的技巧.

Just for fun, we can pull the same trick with traverse and foldMap.

dtraverse :: forall n f s t a b. (DTraverse (ToUnary n) s t a b, Applicative f) => (a -> f b) -> s -> f t
dtraverse = dtraverse' @(ToUnary n)

class DTraverse (n :: UNat) s t a b where
  dtraverse' :: Applicative f => (a -> f b) -> s -> f t

instance (s ~ a, t ~ b) => DTraverse 'Z s t a b where
  dtraverse' = id

instance (Traversable t, tx ~ (t x), ty ~ (t y), DTraverse n x y a b) => DTraverse ('S n) tx ty a b where
  dtraverse' = traverse . dtraverse' @ n

dfoldMap :: forall n m s a. (DFold (ToUnary n) s a, Monoid m) => (a -> m) -> s -> m
dfoldMap = dfoldMap' @(ToUnary n)

class DFold (n :: UNat) s a where
  dfoldMap' :: Monoid m => (a -> m) -> s -> m

instance s ~ a => DFold 'Z s a where
  dfoldMap' = id

instance (Foldable t, tx ~ (t x), DFold n x a) => DFold ('S n) tx a where
  dfoldMap' = foldMap . dfoldMap' @ n

这篇关于关于通过几个嵌套的函子级别进行映射的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆