2015-09-19 12 views
10

Mam następujący moduł:Jak udowodnić podwójną negację dla wartości typu booleans?

{-# 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 

Druga definicja norm nie kompiluje, ponieważ flipVec v powraca Vector (Not isCol) i stąd sprod chce Vector (Not (Not isCol)) jako drugi argument:

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)’ 

Mógłbym oczywiście dodać ograniczenie isCol ~ Not (Not isCol) do typu norm:

norm :: isCol ~ Not (Not isCol) => Vector isCol -> Double 

W witrynie połączenia znana jest rzeczywista wartość isCol, a kompilator zobaczy, że to ograniczenie jest rzeczywiście spełnione. Ale wydaje się dziwne, że szczegóły implementacji norm są przeciekające do sygnatury typu.

Moje pytanie: czy można w jakiś sposób przekonać kompilator, że isCol ~ Not (Not isCol) jest zawsze prawdziwe, więc zbędne ograniczenie nie jest konieczne?

Odpowiedz

5

Odpowiedź: tak, jest. Dowodem na to jest dość trywialne, jeśli masz odpowiednie typy danych:

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 

Jak widać, kompilator będzie widać, że dowód jest trywialny trakcie kontroli poszczególnych przypadków. Wszystkie te definicje danych znajdziesz w kilku pakietach, na przykład singletons. Używasz takiego dowodu:

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) 

Oczywiście, że to dużo pracy dla tak trywialnej rzeczy. Jeśli jesteś naprawdę pewien, że wiesz, co robisz, można „oszukać”:

import Unsafe.Coerce 
import Data.Proxy 

double_neg' :: Proxy x -> x :~: Not (Not x) 
double_neg' _ = unsafeCoerce (Refl ::() :~:()) 

To pozwala pozbyć się SingI przymusu:

norm' :: forall isCol . Vector isCol -> Double 
norm' v = case double_neg' (Proxy :: Proxy isCol) of 
      Refl -> sqrt (flipVec v `sprod` v) 
+0

Awesome, dziękuję! –

+4

To trochę niesatysfakcjonujące, że nie możemy wyeliminować ograniczenia (bez oszukiwania), chociaż wydaje się, że naprawdę nie potrzebujemy słownika w czasie wykonywania. Czy jest to podstawowy powód? Albo jakiego rodzaju ulepszenie GHC byłoby potrzebne, aby uniknąć ograniczeń? –

+0

To propozycyjna równość, więc wciąż wymaga (trywialnego) dowodu. –

Powiązane problemy