如何最好地表示一组固定维度的笛卡尔积?

4

根据@leftaroundabout的建议,本问题已经进行了严重改写。早期版本可以在编辑历史中看到。

Haskell因为有助于思考而闻名,可以更直接地编码数学抽象。笛卡尔积是一个非常基本的心理对象,许多人从童年时代就熟悉了它。然而,在Haskell中几乎没有一个类型可以表示它。我认为我需要一个,即使只是为了让我的思维流畅。(尽管这篇文章实际上是由我手头的一些务实代码启发的。)让我们形成一个关于这个笛卡尔东西(我将简称为Cartesian)的共同理解。

给定长度为d :: Int的集合序列(例如[[1,2], ['a', 'b']]),我想要在短时间内获得它们元素的所有组合。这意味着对它们进行操作,就像它们在一个通常的Functor、Foldable、Traversable、Monoid等中一样。事实上,我们可以将任何笛卡尔表示为适当嵌套的元组列表:

type Lattice = [[(x, y)]]

type WeightedLattice = [[(x, y, w)]]

zipWith2 :: (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
zipWith2 f = zipWith (zipWith f)

fmap2 :: (Functor f, Functor g) => (a -> b) -> g (f a) -> g (f b)
fmap2 = fmap . fmap

sequence2 :: (Traversable s, Traversable t, Monad m) => t (s (m a)) -> m (t (s a))
sequence2 = sequence . fmap sequence

可以手动编写类似的结构,以适应任何嵌套深度。

我们现在介绍 一种 笛卡尔和 初始 笛卡尔之间的区别:

  • An n-dimensional Cartesian is constructed from a heterogeneous sequence of collections by taking one element from each collection and combining them, orderly, with a suitably typed function. This, a Cartesian of signature [Int, Char, Bool] may be formed by a function such as:

    f :: Int -> Char -> Bool -> Either Char Int
    f i c b = if b then Left c else Right i 
    
  • The initial Cartesian is formed with the tuple constructor of matching arity:

    initial :: Int -> Char -> Bool -> (Int, Char, Bool)
    initial = (,,)
    

很容易看出,我们可以使用类似于以下函数的方式将初始笛卡尔表示为嵌套列表,转换为任何其他相同嵌套深度的笛卡尔:

    (fmap . ... . fmap) (uncurryN f)

然而,我们并不总是能获得正确的 Char ,从一个 Right 3 中恢复它将会很困难。因此,初始笛卡尔积可以代替任何特定的笛卡尔积,但反之则不一定成立。
例如,我们可以使用上述定义的 Lattice 类型来可视化一个场域,并计算其在空间中某些正则分布点的值。我们可以用函数为坐标赋值,任意数量的这样的函数可描述相同点上的不同场,每个对应于类似尺寸的格子。但只有一个初始的 Lattice 只包含坐标。
然而,我们的嵌套列表编码有其缺点。除了需要拼出每个下一个维度所需的所有必要函数外,还不安全:没有什么可以防止您错误地混淆一个 128 x 64 矩阵和一个 64 x 128 矩阵并将它们压缩在一起,最终得到一个 64 x 64 的矩阵;元组中的事物顺序可能与列表嵌套的顺序相对应或者不相关。另一方面,类型系统也会起到抵制作用,不允许像 foldr (.) id [replicate d concat] 这样的事情,这可以减少一些痛苦。这样并不像 Haskell。
但是,这个系统最令人失望的根源在于它没有以任何明显的方式支持笛卡尔积的非常基本的直觉:其 Monoid 实例。这个属性使我们可以将一个点视为具有不止一个、不是一些,而是任意数量的属性 p,轻松地添加、组合或抛弃它们——就像列表元素一样。被钉在某个嵌套深度和某个元组的顺序上,就好像剪断了你的翅膀一样。笛卡尔积乘积是从类别论中的 Set 类别中的幺半群的基本事实,但我们能否定义一个在任意嵌套的元组列表上的 Monoid?因此,编写一个正确的 Cartesian 的挑战涉及以下目标:
  • Any dimension. A list, a matrix, and any other finite-dimensional space should have like interface. Some selection of the usual Data.List functions should be implementable.

  • Type safety. That is, having the types and the dimensions of a given Cartesian encoded in the type system. For example, if I form a space like [1..3] x ['a', 'b'], and another like [1,2] x ['a'..'c'], they should have distinct readable type, and not zip together.

  • As the Cartesian is determined by the selection of the dimensions, any two Cartesians may be combined just as the lists of their dimensions. For example:

    Cartesian [[1..3], ['a', 'b']] <> Cartesian [[True, False]]
    

    -- should be the same thing as:

    Cartesian [[1..3], ['a', 'b'], [True, False]]
    

    -- Just the same as their generating lists would.

  • There should be some notion of the initial Cartesian and the decorations placed over it, so that the coordinates of points are never lost unless the loss is forced. For example, the coordinates of the points of a Lattice should be stored separately of the derived properties of the field it describes. We may then, say, obtain a superposition of fields if the Lattices describing them "match".

  • The initial Cartesian should be a Monoid.

我勾画了一个至少有点可用的类型,并将其作为答案发布,但对于上述大部分内容,我感到困惑。这必须需要一些类型的技巧。我欣赏任何关于如何制作它的想法。


1
一个IArray实例是否适合您?您可以选择将其索引(Ix)设置为元组,但由于数组是线性存储的,因此对它们有简单的Traversable等实例。 - Petr
1
这听起来非常像一篇(我认为相当有名的)论文,它的标题我记不清了,关于使用类型类和类型组合器构建可扩展表达式类型。基本上,它是一个开放的余积模型。你可以做同样的事情,但是构建一个开放的积。我希望这里还有其他人能帮我想起这篇论文的名字。 - luqui
1
也许这是一个愚蠢的建议,但如果你只想从一些列表转换为元组列表,并且每个列表中有固定数量的元素,那么你可以使用应用程序相关的东西:f = liftA2 (,) 然后 f [1,2] [T, F] 就是 [(1,T),(1,F),(2,T),(2,F)],你还可以做例如 liftA3 (,,)。显然,如果你想对任意的 d 进行此操作,则无法使用此方法。 - Dan Robertson
1
@leftaroundabout,我从头开始重新做了一遍,现在好些了吗? - Ignat Insarov
1
@Kindaro 只是一些对术语的挑剔 ;) : "Cartesian is monoid" 听起来很奇怪。你可以说:Sets 是一个带有笛卡尔积的幺范畴,但是你必须以某种方式处理它的连贯性(你似乎想立即“展平”一切,不区分 (A x B) x CA x (B x C))。我不太清楚“初始笛卡尔积”应该是什么。Sets 有一个初始对象:空集,它不是一个幺半群,因为它是空的,因此缺少一个恒等元素。 - Andrey Tyukin
显示剩余12条评论
2个回答

4
这个问题比较模糊,但看起来你可能对类似于“黑胶唱片”的东西感兴趣。我的定义与真正的“黑胶唱片”有些不同,你可以使用你喜欢的定义。
{-# language DataKinds, PolyKinds, TypeOperators, GADTs #-}
module Cart where
import Data.Kind (Type)
import Data.Functor.Identity

infixr 4 :<
data Rec :: [k] -> (k -> Type) -> Type where
  Nil :: Rec '[] f
  (:<) :: f a -> Rec as f -> Rec (a ': as) f

newtype HList xs = HList (Rec xs Identity)

prod :: Rec as [] -> [HList as]
prod = map HList . go
  where
    go :: Rec as [] -> [Rec as Identity]
    go Nil = [Nil]
    go (xs :< xss) = [ Identity x :< r | x <- xs, r <- go xss]

使用适当的Show实例(直截了当但有点烦人),您将获得以下内容

> prod $ [3,4,5] :< ["hello", "goodbye"] :< ['x'] :< Nil

[ H[3,"hello",'x'], H[3,"goodbye",'x'], H[4,"hello",'x']
, H[4,"goodbye",'x'], H[5,"hello",'x'], H[5,"goodbye",'x'] ]

这个版本的prod可能太具体了,因为它只适用于Identity和列表。下面是一个简单的泛化版本,其中遍历函数“分裂”了Rec的基本函子,并且我们使用任意的Applicative而不仅仅是[]

class Trav (t :: (k -> Type) -> Type) where
  trav :: Applicative g => (forall a. f a -> g (h a)) -> t f -> g (t h)

instance Trav (Rec as) where
  trav f Nil = pure Nil
  trav f (xs :< xss) = (:<) <$> f xs <*> trav f xss

这就像 Data.Vinyl.rtraverse 的类比,最终我也意识到了这一点。


这种记录类型不形成Monoid,因为无法定义mappend。但是你可以将它们连接起来:

type family (++) xs ys where
  '[] ++ ys = ys
  (x ': xs) ++ ys = x ': xs ++ ys

(><) :: Rec xs f -> Rec ys f -> Rec (xs ++ ys) f
Nil >< ys = ys
(x :< xs) >< ys = x :< (xs >< ys)

这个表现非常好。特别是,您可以在追加记录后遍历它们,或者在遍历它们之后追加结果。

trav f (xs >< ys) = (><) <$> trav f xs <*> trav f ys

您也可以按照原则重新排列它们(类似于您的气泡设备)。类型
forall f k (as :: [k]) (bs :: [k]). Rec as f -> Rec bs f

这里提到的任何可以重新排列Rec的函数,无论其内部包含什么内容都可以使用。


既然您提到了映射:

class Functor1 (t :: (k -> Type) -> Type) where
  map1 :: (forall x. f x -> g x) -> t f -> t g

instance Functor1 (Rec as) where
  map1 f = runIdentity . trav (\x -> Identity (f x))

压缩功能也可用:
rzip :: (forall x. f x -> g x -> h x)
     -> Rec as f -> Rec as g -> Rec as h
rzip f Nil Nil = Nil
rzip f (x :< xs) (y :< ys) = f x y :< rzip f xs ys

我重新制作了这个问题,现在是否更清晰明了? - Ignat Insarov
@Kindaro,不,我还是很迷茫。 - dfeuer

0

通过使用这样的类型,可以减轻一些痛苦:

type A e = Array Int e

data Cartesian v = Cartesian
    { _dimensions :: [Int]
    , _values :: A v
    } deriving (Show, Eq, Ord, Functor, Foldable, Traversable)

-- # Some helper functions.

autoListArray :: [a] -> A a
autoListArray xs = listArray (0, pred (length xs)) xs

-- | Get elements of an array such that they all belong to the
--   congruence class c modulo n.
getByCongruentIndices :: Int -> Int -> A v -> [v]
getByCongruentIndices n c arr =
    let (low, high) = bounds arr
    in  (arr !) <$> [low + c, low + c + n.. high]

arr :: [v] -> A v
arr = autoListArray

unarr :: A v -> [v]
unarr = elems

congr :: Int -> Int -> A v -> [v]
congr = getByCongruentIndices

congr0 :: Int -> A v -> [v]
congr0 n = congr n 0

我现在会去勾选相关的选项。

  • Functor,Foldable,Traversable: 可以神奇地从盒子中衍生出来。

  • 创建:通过逐渐增加unicons的方式,您可以创建任何您想要的笛卡尔。

    -- | 构造一维笛卡尔。
    uni :: [v] -> Cartesian v
    uni vs = Cartesian { _dimensions = [length vs], _values = arr vs }
    
    -- | 维度增量。
    cons :: (u -> v -> w) -> [u] -> Cartesian v -> Cartesian w
    cons f xs Cartesian{..} = Cartesian
        { _dimensions = length xs: _dimensions
        , _values = arr [ x `f` y | x <- xs, y <- unarr _values ]
        }
    
  • 销毁:您可以使用uncons将笛卡尔的层剥离。

    -- | 维度减量。
    uncons :: (u -> (v, w)) -> Cartesian u -> Maybe ([v], Cartesian w)
    uncons _ Cartesian { _dimensions = [] } = Nothing
    uncons f Cartesian { _dimensions = (_: ds), _values = xs } =
        let ys = fmap (fst . f) . congr0 (product ds) $ xs
            zs = fmap (snd . f) . take (product ds) . unarr $ xs
        in  Just (ys, Cartesian { _dimensions = ds, _values = arr zs })
    
  • 转置:您可以使用(↑) 泡泡 设备改变维度的顺序。我没有证据,但我几乎确定您可以获得任何您想要的转置。特别是,(↑) x 1 等价于 Data.List.traverse

    -- | Bubble: 将从 0 到 (i - 1) 的循环应用到维度上。也就是说,使第 i 维成为第一维。我认为泡泡是对称群的生成器。
    (↑) :: Cartesian u -> Int -> Cartesian u
    Cartesian{..} ↑ i =
        let d  = product . drop i $ _dimensions
            ds = take i _dimensions ++ drop (succ i) _dimensions  -- 删除第 i 维。
        in  Cartesian
                { _dimensions = ds
                , _values = arr . concat $ ($ _values) <$> (congr d <$> [0..pred d])
                }
    
  • consuncons(↑) 允许您切割和再次组合任意两个笛卡尔,或者它们的部分。但还有一种直接组合笛卡尔的方法:

    appendWith :: (u -> v -> w) -> Cartesian u -> Cartesian v -> Cartesian w
    appendWith f x y = Cartesian { _dimensions = _dimensions x ++ _dimensions y
                                 , _values = arr [ x `f` y | x <- unarr (_values x), y <- unarr (_values y) ]
                                 }
    
  • 您还可以对其进行压缩:

    glue f x y | _dimensions x == _dimensions y
                    = Cartesian
                        { _dimensions = _dimensions x
                        , _values = arr $ zipWith f (unarr $ _values x) (unarr $ _values y)
                        }
               | otherwise = undefined
    

不足之处在于,您必须明确提供一个二元函数,该函数可以将您在笛卡尔积中拥有的类型组合起来。这通常是一个元组构造函数,但您并不局限于此。

我在定义Monoid实例时遇到了麻烦,特别是mempty部分,而且初始值还远远不够。


网页内容由stack overflow 提供, 点击上面的
可以查看英文原文,
原文链接