在类型列表上映射依赖类型

ale*_*404 5 haskell type-families data-kinds

我认为从简单的代码中理解我的问题相当简单,但另一方面,我不确定答案!直觉上,我想要做的是给出一个类型列表[*]和一些依赖类型Foo,生成类型[Foo*].也就是说,我想在基类型上"映射"依赖类型.

首先,我正在使用以下扩展

{-# LANGUAGE TypeOperators,DataKinds,GADTs,TypeFamilies #-}
Run Code Online (Sandbox Code Playgroud)

假设我们有一些依赖类型

class Distribution m where
    type SampleSpace m :: *
Run Code Online (Sandbox Code Playgroud)

它表征了一些概率分布的样本空间.如果我们想要在可能异构的值上定义产品分布,我们可能会写类似的东西

data PDistribution (ms :: [*]) where
    DNil :: PDistribution ('[])
    (:*:) :: Distribution m => m -> (PDistribution ms) -> PDistribution (m ': ms)
Run Code Online (Sandbox Code Playgroud)

并补充它

data PSampleSpace (m :: [*]) where
    SSNil :: PSampleSpace ('[])
    (:+:) :: Distribution m => SampleSpace m -> (PSampleSpace ms) -> PSampleSpace (m ': ms)
Run Code Online (Sandbox Code Playgroud)

这样我们就可以定义了

instance Distribution (PDistribution ms) where
    type SampleSpace (PDistribution ms) = PSampleSpace ms
Run Code Online (Sandbox Code Playgroud)

现在这一切都相当不错,除了PSampleSpace的类型将导致一些问题.特别是,如果我们想直接构建PSampleSpace,例如

ss = True :+: 3.0 :+: SNil
Run Code Online (Sandbox Code Playgroud)

我们必须明确地给它一组分布,它们产生它或者遇到单态限制.此外,由于两个发行版当然可以共享一个SampleSpace(Normals和Exponentials都描述双打),因此选择一个发行版来修复类型似乎很愚蠢.我真正想要定义的是定义一个简单的异构列表

data HList (xs :: [*]) where
    Nil :: HList ('[])
    (:+:) :: x -> (HList xs) -> HList (x ': xs)
Run Code Online (Sandbox Code Playgroud)

写点东西

instance Distribution (PDistribution (m ': ms)) where
    type SampleSpace (PDistribution (m ': ms)) = HList (SampleSpace m ': mxs)
Run Code Online (Sandbox Code Playgroud)

其中mxs已经以某种方式转换为我想要的SampleSpaces列表.当然,最后一点代码不起作用,我不知道如何解决它.干杯!

编辑

正如我所提出的解决方案问题的一个可靠的例子,假设我有这个类

class Distribution m => Generative m where
    generate :: m -> Rand (SampleSpace m)
Run Code Online (Sandbox Code Playgroud)

即使它似乎应该键入检查,以下

instance Generative (HList '[]) where
    generate Nil = return Nil

instance (Generative m, Generative (HList ms)) => Generative (HList (m ': ms)) where
    generate (m :+: ms) = do
        x <- generate m
        (x :+:) <$> generate ms
Run Code Online (Sandbox Code Playgroud)

才不是.GHC抱怨它

Could not deduce (SampleSpace (HList xs) ~ HList (SampleSpaces xs))
Run Code Online (Sandbox Code Playgroud)

现在我可以使用我的PDistribution GADT了,因为我在子发行版上强制所需的类型类.

最终编辑

所以有几种方法可以解决这个问题.TypeList是最常用的.我的问题不仅仅是在这一点上回答.

Cir*_*dec 1

为什么要从列表中取出分布的乘积?普通元组(两种类型的乘积)可以代替 吗:*:

{-# LANGUAGE TypeOperators,TypeFamilies #-}

class Distribution m where
    type SampleSpace m :: *

data (:+:) a b = ProductSampleSpaceWhatever
    deriving (Show)

instance (Distribution m1, Distribution m2) => Distribution (m1, m2) where
    type SampleSpace (m1, m2) = SampleSpace m1 :+: SampleSpace m2

data NormalDistribution = NormalDistributionWhatever

instance Distribution NormalDistribution where
    type SampleSpace NormalDistribution = Doubles

data ExponentialDistribution = ExponentialDistributionWhatever

instance Distribution ExponentialDistribution where
    type SampleSpace ExponentialDistribution = Doubles

data Doubles = DoublesSampleSpaceWhatever

example :: SampleSpace (NormalDistribution, ExponentialDistribution)
example = ProductSampleSpaceWhatever

example' :: Doubles :+: Doubles
example' = example

-- Just to prove it works:
main = print example'
Run Code Online (Sandbox Code Playgroud)

元组树和列表之间的区别在于,元组树是类似岩浆的(有一个二元运算符),而列表是类似幺半群的(有一个二元运算符、一个恒等式,并且该运算符是关联的)。所以没有单一的、挑出来的DNil就是身份,并且类型并不强迫我们放弃(NormalDistribution :*: ExponentialDistribution) :*: BinaryDistribution和 之间的区别NormalDistribution :*: (ExponentialDistribution :*: BinaryDistribution)

编辑

以下代码使用关联运算符TypeListConcat和标识来创建类型列表TypeListNilTypeList没有什么可以保证除了提供的两种类型之外不会有其他实例。我无法让TypeOperators语法满足我想要的一切。

{-# LANGUAGE TypeFamilies,MultiParamTypeClasses,FlexibleInstances,TypeOperators #-}

-- Lists of types

-- The class of things where the end of them can be replaced with something
-- The extra parameter t combined with FlexibleInstances lets us get away with essentially
--  type TypeListConcat :: * -> *
-- And instances with a free variable for the first argument
class TypeList l a where
    type TypeListConcat    l    a :: * 
    typeListConcat      :: l -> a -> TypeListConcat l a

-- An identity for a list of types. Nothing guarantees it is unique
data TypeListNil = TypeListNil
    deriving (Show)

instance TypeList TypeListNil a where
    type TypeListConcat TypeListNil a = a
    typeListConcat      TypeListNil a = a

-- Cons for a list of types, nothing guarantees it is unique.
data (:::) h t = (:::) h t
    deriving (Show)

infixr 5 :::

instance (TypeList t a) => TypeList (h ::: t) a where
    type TypeListConcat (h ::: t) a = h ::: (TypeListConcat t a)
    typeListConcat      (h ::: t) a = h ::: (typeListConcat t a)

-- A Distribution instance for lists of types
class Distribution m where
    type SampleSpace m :: *

instance Distribution TypeListNil where
    type SampleSpace TypeListNil = TypeListNil

instance (Distribution m1, Distribution m2) => Distribution (m1 ::: m2) where
    type SampleSpace (m1 ::: m2) = SampleSpace m1 ::: SampleSpace m2

-- Some types and values to play with
data NormalDistribution = NormalDistributionWhatever

instance Distribution NormalDistribution where
    type SampleSpace NormalDistribution = Doubles

data ExponentialDistribution = ExponentialDistributionWhatever

instance Distribution ExponentialDistribution where
    type SampleSpace ExponentialDistribution = Doubles

data BinaryDistribution = BinaryDistributionWhatever

instance Distribution BinaryDistribution where
    type SampleSpace BinaryDistribution = Bools

data Doubles = DoublesSampleSpaceWhatever
    deriving (Show)

data Bools = BoolSampleSpaceWhatever
    deriving (Show)

-- Play with them

example1 :: TypeListConcat (Doubles ::: TypeListNil) (Doubles ::: Bools ::: TypeListNil)
example1 = (DoublesSampleSpaceWhatever ::: TypeListNil) `typeListConcat` (DoublesSampleSpaceWhatever ::: BoolSampleSpaceWhatever ::: TypeListNil)

example2 :: TypeListConcat (Doubles ::: Doubles ::: TypeListNil) (Bools ::: TypeListNil)
example2 = example2

example3 :: Doubles ::: Doubles ::: Bools ::: TypeListNil
example3 = example1

example4 :: SampleSpace (NormalDistribution ::: ExponentialDistribution ::: BinaryDistribution ::: TypeListNil)
example4 = example3

main = print example4
Run Code Online (Sandbox Code Playgroud)

TypeList使用s编辑代码

以下是一些与您在编辑中添加的代码类似的代码。我不知道Rand应该是什么,所以我编了一些别的东西。

-- Distributions with sampling

class Distribution m => Generative m where
    generate :: m -> StdGen -> (SampleSpace m, StdGen)

instance Generative TypeListNil where
    generate TypeListNil g = (TypeListNil, g)

instance (Generative m1, Generative m2) => Generative (m1 ::: m2) where
    generate (m ::: ms) g =
        let
            (x, g') = generate m g
            (xs, g'') = generate ms g'
        in (x ::: xs, g'')

-- Distributions with modes

class Distribution m => Modal m where
    modes :: m -> [SampleSpace m]

instance Modal TypeListNil where
    modes TypeListNil = [TypeListNil]

instance (Modal m1, Modal m2) => Modal (m1 ::: m2) where
    modes (m ::: ms) = [ x ::: xs | x <- modes m, xs <- modes ms] 
Run Code Online (Sandbox Code Playgroud)