2015-09-19 19 views
10

我有以下模块:如何证明类型级布尔的双重否定?

{-# 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)总是为真,这样多余的约束就不是必须的了?

回答

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) 
+0

真棒,谢谢! –

+4

即使看起来我们实际上不需要字典在运行时,我们也无法消除约束(没有作弊),这有点让人不满意。这是否有根本原因?或者需要什么样的GHC改进来避免约束? –

+0

这是一个命题平等,所以它仍然需要(微不足道的)证明。 –