简体   繁体   English

关于通过多个嵌套功能级别进行映射

[英]About mapping through several nested functorial levels

A random example: given the following [Maybe [a]] ,一个随机的例子:给定以下[Maybe [a]]

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

I want to map f = (^2) through the 3 layers, thus obtaining我想通过3层map f = (^2) ,从而得到

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

The easiest way to do it seems to be最简单的方法似乎是

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

where fmap. fmap. fmap fmap. fmap. fmap fmap. fmap. fmap fmap. fmap. fmap is like fmap , but it goes 3 levels deep. fmap. fmap. fmap类似于fmap ,但它有 3 层深。

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.我怀疑在将fmap与自身组合给定次数的一般情况下,需要这样的东西并不少见,所以我想知道标准中是否已经有一些东西可以与自身组合fmap一定次数。 Or maybe something which "knows" how many times it should compose fmap with itself based on the input.或者可能是“知道”它应该根据输入与自身组合fmap多少次的东西。

You can work with a Compose type to go two (or more if you cascade) levels of functors deep.您可以将Compose类型用于 go 两个(或更多,如果您级联)级别的函子深度。

So we can implement this as:所以我们可以将其实现为:

import Data.Functor.Compose(Compose(Compose, getCompose))

fmap (^2) (Compose (Compose [Just [1,4,9],Nothing,Just [81]]))

This then yields:然后产生:

Prelude Data.Functor.Compose> fmap (^2) (Compose (Compose [Just [1,4,9],Nothing,Just [81]]))
Compose (Compose [Just [1,16,81],Nothing,Just [6561]])

we thus can unwrap it with:因此,我们可以使用以下方法打开它:

Prelude Data.Functor.Compose> (getCompose . getCompose . fmap (^2)) (Compose (Compose [Just [1,4,9],Nothing,Just [81]]))
[Just [1,16,81],Nothing,Just [6561]]

By constructing a Compose that is a structure that is two Functor s deep, we thus make it an instance of Functor that combines the two.通过构造一个具有两个Functor深度的结构的Compose ,我们因此使其成为结合两者的Functor实例。

If you want to super over-engineer this, you can use data kinds and type families.如果您想对此进行超级过度设计,您可以使用数据类型和类型系列。 It's a bit crazy, but consider the following type family:这有点疯狂,但请考虑以下类型系列:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

type family DT fs x where
  DT '[] x = x
  DT (f ': fs) x = f (DT fs x)

Given a type-level list of functors (well, more generally, type function of kind * -> * ), this wraps up a type in each value of the list.给定一个类型级别的函子列表(嗯,更一般地说,类型 function 类型* -> * ),这将在列表的每个值中包含一个类型。 With this, we can write a crazy type class:有了这个,我们可以写一个疯狂的类型 class:

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE AllowAmbiguousTypes #-}

class DMap (fs :: [* -> *]) where
  dmap' :: (a -> b) -> DT fs a -> DT fs b

The function dmap' takes a function to apply (much like fmap ) and then transforms this wrapped up a into a wrapped up b . function dmap'需要一个 function 来应用(很像fmap ),然后将这个包裹a转换成一个包裹b The instances for this follow (somewhat) naturally, applying the idea of composing fmap with itself as many times as there are functors in the list:这个例子自然(有点)遵循,应用fmap与自身组合的想法与列表中的函子一样多:

instance DMap '[] where
  dmap' = id

instance (DMap fs, Functor f) => DMap (f ': fs) where
  dmap' = fmap . dmap' @fs

With this, we can write the following:有了这个,我们可以编写以下内容:

{-# LANGUAGE TypeApplications #-}

x = [Just [1..3], Nothing, Just [9]]
x' = dmap' @'[[], Maybe, []] (^2) x

Woohoo, Well, it's good, but writing out the list of functors is a pain?哇哦,好吧,这很好,但是写出函子列表很痛苦? and shouldn't GHC be able to do that for us: We can add that by introducing another type family: GHC 不应该为我们做到这一点:我们可以通过引入另一个类型族来添加它:

{-# LANGUAGE TypeOperators #-}

import GHC.TypeLits (Nat, type (-))

type family FType n a where
  FType 0 a = '[]
  FType n (f a) = f ': FType (n-1) a

This type family produces a type-level list of functors from a type that already is wrapped up (using the Nat to limit us from going deeper than we may want).这个类型族从一个已经被包装的类型中产生一个类型级别的函子列表(使用Nat来限制我们比我们想要的更深)。 We can then write a proper dmap that uses FType to solve what the list of functors are:然后我们可以编写一个适当的dmap使用FType来解决函子列表是什么:

dmap :: forall n (fs :: [* -> *]) a b c d. (fs ~ FType n c, fs ~ FType n d, DMap fs, DT fs a ~ c, DT fs b ~ d) => (a -> b) -> c -> d
dmap = dmap' @fs

The type signature is a little hairy, but basically it's telling GHC to use the c value to determine what the functors are.类型签名有点复杂,但基本上它告诉 GHC 使用c值来确定函子是什么。 In practice, this means we can write:在实践中,这意味着我们可以写:

x' = dmap @3 (^2) x

(Note, I may have left out a language extension or two here or there.) (注意,我可能在这里或那里遗漏了一两个语言扩展名。)


For the record, I don't know if I'd ever use something like this.为了记录,我不知道我是否曾经使用过这样的东西。 The error messages are not great, to say the least, and to advanced Haskellers, seeing fmap. fmap至少可以说,错误消息不是很好,对于高级 Haskellers,看到fmap. fmap fmap. fmap (or even fmap. fmap. fmap ) is not very scary. fmap. fmap (甚至fmap. fmap. fmap )并不是很可怕。

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.这个答案的灵感来自 DDub,但我认为它更简单,它应该提供更好的类型推断和可能更好的类型错误。 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's built-in Nat s are pretty awkward to work with, because we can't pattern match on "not 0". GHC 的内置Nat很难使用,因为我们不能在“非 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.现在我们已经摆脱了完全无聊的部分,rest 变得非常简单。

-- @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

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.只有当 GHC 看到第一个参数是'Z并且第二个和第四个 arguments 相同并且第三个和第五个 arguments 相同时,GHC 才会选择第一个实例。 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.类似地,如果它看到第一个参数是'S 第二个参数是一个应用程序第三个参数是一个应用程序,并且第二个和第三个arguments中应用的构造函数相同,它只会选择第二个实例。

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

Now, I claimed above that this gives better type inference than DDub's, so I'd better back that up.现在,我在上面声称这提供了比 DDub 更好的类型推断,所以我最好支持它。 Let me just pull up GHCi :让我拉起GHCi

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

That's precisely the type of fmap.fmap.fmap .这正是fmap.fmap.fmap的类型。 Perfect, With DDub's code, I instead get完美,使用 DDub 的代码,我得到了

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.正如我在评论中提到的,这可以修复,但它给已经有些复杂的代码增加了一点复杂性。


Just for fun, we can pull the same trick with traverse and foldMap .只是为了好玩,我们可以使用traversefoldMap来实现相同的技巧。

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

声明:本站的技术帖子网页,遵循CC BY-SA 4.0协议,如果您需要转载,请注明本站网址或者原文地址。任何问题请咨询:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM