Чтобы установить сцену, вот несколько языковых расширений, которые мы будем использовать, и некоторые упрощенные определения из CLaSH:
{-# LANGUAGE GADTs, StandaloneDeriving #-}
{-# LANGUAGE TypeOperators, DataKinds, PolyKinds #-}
{-# LANGUAGE TypeFamilyDependencies, FlexibleContexts, FlexibleInstances #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE QuantifiedConstraints #-}
data Signal dom a
instance Functor (Signal dom) where
instance Applicative (Signal dom) where
class Bundle a where
type Unbundled dom a = res | res -> dom a
bundle :: Unbundled dom a -> Signal dom a
unbundle :: Signal dom a -> Unbundled dom a
Я хотел бы сделать Bundle
экземпляров для n-арного типа продукта. Сам тип определяется следующим образом:
import Control.Monad.Identity
data ProductF (f :: * -> *) (ts :: [*]) where
NilP :: ProductF f '[]
ConsP :: f a -> ProductF f ts -> ProductF f (a : ts)
deriving instance (Show (f t), Show (ProductF f ts)) => Show (ProductF f (t : ts))
headPF :: ProductF f (t : ts) -> f t
headPF (ConsP x xs) = x
tailP :: ProductF f (t : ts) -> ProductF f ts
tailP (ConsP x xs) = xs
-- Utilities for the simple case
type Product = ProductF Identity
infixr 5 ::>
pattern (::>) :: t -> Product ts -> Product (t : ts)
pattern x ::> xs = ConsP (Identity x) xs
headP :: Product (t : ts) -> t
headP (x ::> xs) = x
Я хотел бы написать экземпляр Bundle
, который просто заменяет Identity
на Signal dom
. К сожалению, мы не можем сделать это за один раз:
instance Bundle (Product ts) where
type Unbundled dom (Product ts) = ProductF (Signal dom) ts
bundle NilP = pure NilP
bundle (ConsP x xs) = (::>) <$> x <*> bundle xs
unbundle = _ -- Can't implement this, since it would require splitting on ts
Здесь unbundle
нужно сделать что-то другое для ts ~ []
и для ts ~ t : ts'
. Хорошо, давайте попробуем написать это в двух случаях:
instance Bundle (Product '[]) where
type Unbundled dom (Product '[]) = ProductF (Signal dom) '[]
bundle NilP = pure NilP
unbundle _ = NilP
instance (Bundle (Product ts), forall dom. Unbundled dom (Product ts) ~ ProductF (Signal dom) ts) => Bundle (Product (t : ts)) where
type Unbundled dom (Product (t : ts)) = ProductF (Signal dom) (t : ts)
bundle (ConsP x xs) = (::>) <$> x <*> bundle xs
unbundle xs = ConsP (headP <$> xs) (unbundle $ tailP <$> xs)
И вот во втором случае возникает проблема. Даже при том, что у нас есть (количественно) равенство типов forall dom. Unbundled dom (Product ts) ~ ProductF (Signal dom) ts
в ограничениях экземпляра, GHC 8.6.3 не использует его во время проверки типов:
Для bundle
:
• Couldn't match type ‘Unbundled dom (Product ts)’
with ‘ProductF (Signal dom) ts’
Expected type: Unbundled dom (Product ts)
Actual type: ProductF (Signal dom) ts1
• In the first argument of ‘bundle’, namely ‘xs’
In the second argument of ‘(<*>)’, namely ‘bundle xs’
In the expression: (::>) <$> x <*> bundle xs
Для unbundle
:
• Couldn't match expected type ‘ProductF (Signal dom) ts’
with actual type ‘Unbundled dom (ProductF Identity ts)’
• In the second argument of ‘ConsP’, namely
‘(unbundle $ tailP <$> xs)’
In the expression: ConsP (headP <$> xs) (unbundle $ tailP <$> xs)
In an equation for ‘unbundle’:
unbundle xs = ConsP (headP <$> xs) (unbundle $ tailP <$> xs)
Возможный обходной путь
Конечно, мы можем просто пойти по длинному пути: создать свой собственный класс специально для Product
и поручить всю настоящую работу этому. Я представляю это решение здесь, но меня особенно интересует нечто менее подробное и специальное, чем это.
class IsProduct (ts :: [*]) where
type UnbundledProd dom ts = (ts' :: [*]) | ts' -> dom ts
bundleProd :: Product (UnbundledProd dom ts) -> Signal dom (Product ts)
unbundleProd :: Signal dom (Product ts) -> Product (UnbundledProd dom ts)
instance (IsProduct ts) => Bundle (Product ts) where
type Unbundled dom (Product ts) = Product (UnbundledProd dom ts)
bundle = bundleProd
unbundle = unbundleProd
, а затем IsProduct
имеет то преимущество, что оно может быть реально реализовано:
type (:::) (name :: k) (a :: k1) = (a :: k1)
instance IsProduct '[] where
type UnbundledProd dom '[] = dom ::: '[]
bundleProd NilP = pure NilP
unbundleProd _ = NilP
instance (IsProduct ts) => IsProduct (t : ts) where
type UnbundledProd dom (t : ts) = Signal dom t : UnbundledProd dom ts
bundleProd (x ::> xs) = (::>) <$> x <*> bundleProd xs
unbundleProd xs = (headP <$> xs) ::> (unbundleProd $ tailP <$> xs)