如何为通用向量创建ListIsomorphic实例?

Mai*_*tor 4 haskell typeclass ghc-generics

鉴于以下课程:

class ListIsomorphic l where
    toList   :: l a -> [a]
    fromList :: [a] -> l a
Run Code Online (Sandbox Code Playgroud)

如何使用Data.Vector.Generic?为矢量类型编写实例?这不起作用:

instance (V.Vector v a) => ListIsomorphic v where
    toList   = V.toList
    fromList = V.fromList
Run Code Online (Sandbox Code Playgroud)

给我:

test.hs:31:10:
    Variable ‘a’ occurs more often than in the instance head
      in the constraint: V.Vector v a
    (Use UndecidableInstances to permit this)
    In the instance declaration for ‘ListIsomorphic v’
Run Code Online (Sandbox Code Playgroud)

Cir*_*dec 6

不要.由于实例重叠,将所有实例添加v到您的Listable类将变得很麻烦.

A Vector v a => v与列表不同构,因为它受哪些项可以是列表元素的约束.你需要一个捕获这种约束的类,比如

{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}

import Data.Constraint

class ConstrainedList l where
    type Elem l a :: Constraint
    toList   :: Elem l a => l a -> [a]
    fromList :: Elem l a => [a] -> l a
Run Code Online (Sandbox Code Playgroud)

我们将仅为我们感兴趣的类型定义它,而不是ConstrainedList为所有类型添加实例以Vector v a => v使我们进入重叠的实例区域.以下将涵盖Vector向量包中具有实例的所有类型.

import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Generic as VG

instance ConstrainedList VP.Vector where
    type Elem VP.Vector a = VG.Vector VP.Vector a
    toList   = VG.toList
    fromList = VG.fromList
Run Code Online (Sandbox Code Playgroud)

其他类型的实例

您可以ConstrainedList为常规列表编写一个实例,该实例[]仅需要对其元素使用空约束.

instance ConstrainedList [] where
    type Elem [] a = ()
    toList   = id
    fromList = id
Run Code Online (Sandbox Code Playgroud)

使用toListfromList将需要Elem l a实例的任何地方.

cmap :: (ConstrainedList l, Elem l a, Elem l b) => (a -> b) -> l a -> l b
cmap f = fromList . map f . toList
Run Code Online (Sandbox Code Playgroud)

当我们知道列表和元素的具体类型时,这些函数将易于使用而不会弄乱约束.

cmap (+1) [1,2,3,4]
Run Code Online (Sandbox Code Playgroud)

这里是龙

不要尝试以下内容.如果您对没有附加约束的列表同构的事物类感兴趣,那么只需为它创建另一个类.这只是展示了当你把自己设计成一个角落时你能做什么:召唤一条龙.

您还可以编写需要证明对a的元素没有约束的函数ConstrainedList.这是constraintsGHC并不真正支持的包和编程风格的领域,但是没有足够的constraints例子,所以我将把这个放在这里.

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}

map' :: forall l a b. (ConstrainedList l, () :=> Elem l a, () :=> Elem l b) =>
                      (a -> b) -> l a -> l b
map' f = case (ins :: () :- Elem l a) of { Sub Dict ->
         case (ins :: () :- Elem l b) of { Sub Dict ->
         fromList . map f . toList
         }}
Run Code Online (Sandbox Code Playgroud)

我们可以通过检查它来检查a ConstrainedList没有约束Elem l a ~ (),但如果它的约束以不同的方式写入,那么这将不起作用.

{-# LANGUAGE FlexibleInstances #-}

class Any a
instance Any a

data AList a = AList {getList :: [a]}
    deriving (Show)

instance ConstrainedList AList where
    type Elem AList a = Any a
    toList   = getList
    fromList = AList
Run Code Online (Sandbox Code Playgroud)

()Any a虽然()暗示不是同一类型Any a.约束包他们reifying的类型类抓住这样的关系Class:=>

{-# LANGUAGE MultiParamTypeClasses #-}

--       class () => Any a
instance Class ()   (Any a) where
    cls = Sub Dict

-- instance ()  => Any a
instance    () :=> Any a where
    ins = Sub Dict
Run Code Online (Sandbox Code Playgroud)

所有这些工作都可以让我们轻松地重用函数,而无需在知道具体列表类型时提供所有这些字典.

map'' :: (a -> b) -> AList a -> AList b
map'' = map'
Run Code Online (Sandbox Code Playgroud)


cro*_*eea 5

我经常遇到这个问题.以下是我提出的两个解决方案:

  1. 更改类参数:

    class ListIsomorphic l a where
      toList :: l a -> [a]
      fromList :: [a] -> l a
    
    instance (V.Vector v a) => Listable v a where
      ...
    
    Run Code Online (Sandbox Code Playgroud)
  2. 使用约束种类

    class ListIsomorphic l where
      type C l a :: Constraint
      toList :: l a -> [a]
      fromList :: [a] -> l a
    
    instance Listable v where
      type C v a = (V.Vector v a)
      ...
    
    Run Code Online (Sandbox Code Playgroud)