我有以下模块:
{-# LANGUAGE DataKinds, KindSignatures, TypeFamilies, RoleAnnotations #-}
module Main where
import Data.Coerce (coerce)
-- logical negation for type level booleans
type family Not (x :: Bool) where
Not True = False
Not False = True
-- a 3D vector with a phantom parameter that determines whether this is a
-- column or row vector
data Vector (isCol :: Bool) = Vector Double Double Double
type role Vector phantom
-- convert column to row vector or row to column vector
flipVec :: Vector isCol -> Vector (Not isCol)
flipVec = coerce
-- scalar product is only defined for vectors of different types
-- (row times column or column times row vector)
sprod :: Vector isCol -> Vector (Not isCol) -> Double
sprod (Vector x1 y1 z1) (Vector x2 y2 z2) = x1*x2 + y1*y2 + z1*z2
-- vector norm defined in terms of sprod
norm :: Vector isCol -> Double
-- this definition compiles
norm v = sqrt (v `sprod` flipVec v)
-- this does not (without an additional constraint, see below)
norm v = sqrt (flipVec v `sprod` v)
main = undefined
norm
的第二个定义无法编译,因为flipVec v
返回Vector (Not isCol)
,因此sprod
想要Vector (Not (Not isCol))
作为第二个参数:
Main.hs:22:34:
Couldn't match type ‘isCol’ with ‘Not (Not isCol)’
‘isCol’ is a rigid type variable bound by
the type signature for norm :: Vector isCol -> Double
at Main.hs:20:9
Expected type: Vector (Not (Not isCol))
Actual type: Vector isCol
Relevant bindings include
v :: Vector isCol (bound at Main.hs:22:6)
norm :: Vector isCol -> Double (bound at Main.hs:22:1)
In the second argument of ‘sprod’, namely ‘v’
In the first argument of ‘sqrt’, namely ‘(flipVec v `sprod` v)’
我当然可以将约束isCol ~ Not (Not isCol)
添加到norm
的类型:
norm :: isCol ~ Not (Not isCol) => Vector isCol -> Double
在调用站点,isCol
的实际值已知,编译器将看到确实满足此约束。但是norm
的实现细节泄漏到类型签名中似乎很奇怪。
我的问题:是否有可能以某种方式说服编译器isCol ~ Not (Not isCol)
始终为真,这样就不需要多余的约束了?
答案 0 :(得分:5)
答案:是的,确实如此。如果您具有正确的数据类型,则证明非常简单:
data family Sing (x :: k)
class SingI (x :: k) where
sing :: Sing x
data instance Sing (x :: Bool) where
STrue :: Sing True
SFalse :: Sing False
type SBool x = Sing (x :: Bool)
data (:~:) x y where
Refl :: x :~: x
double_neg :: SBool x -> x :~: Not (Not x)
double_neg x = case x of
STrue -> Refl
SFalse -> Refl
正如您所看到的,编译器将在检查不同情况时看到证明是微不足道的。您可以在多个包中找到所有这些数据定义,例如singletons
。你可以像这样使用证据:
instance Sing True where sing = STrue
instance Sing False where sing = SFalse
norm :: forall isCol . SingI isCol => Vector isCol -> Double
norm v = case double_neg (sing :: Sing isCol) of
Refl -> sqrt (flipVec v `sprod` v)
当然,对于这样一件微不足道的事情,这需要做很多工作。如果你确定你知道自己在做什么,那么你可以“作弊”:
import Unsafe.Coerce
import Data.Proxy
double_neg' :: Proxy x -> x :~: Not (Not x)
double_neg' _ = unsafeCoerce (Refl :: () :~: ())
这使您可以摆脱SingI
约束:
norm' :: forall isCol . Vector isCol -> Double
norm' v = case double_neg' (Proxy :: Proxy isCol) of
Refl -> sqrt (flipVec v `sprod` v)