简体   繁体   English

如何扩展 ghc-typelits-natnormalise 以检查普遍量化类型和存在量化类型之间的关系?

[英]How to extend ghc-typelits-natnormalise to check relationships between universally and existentially quantified types?

I'm trying to make my use of Finite s completely safe and non-partial, by using Proxy s in place of Integer s like so:我试图通过使用Proxy代替Integer来使我完全安全且非部分地使用Finite ,如下所示:

-- SO test case, re: my use of ghc-typelits-natnormalise package.
--
-- David Banas <capn.freako@gmail.com>
-- February 9, 2018

{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.Normalise #-}

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}

module Bogus.NewFin where

import GHC.TypeLits
import Data.Proxy
import Data.Finite
import Data.Finite.Internal (Finite(..))
import Data.Reflection

-- A safer form of `finite`.
finite' :: (KnownNat n, KnownNat m, n `CmpNat` m ~ 'GT) => Proxy m -> Finite n
finite' p = Finite $ natVal p

-- A safer form of `getFinite`.
getFinite' :: KnownNat n => Finite n -> (forall m. (KnownNat m, n `CmpNat` m ~ 'GT) => Proxy m -> r) -> r
getFinite' x f = reifyNat (getFinite x) f

And I'm getting this compiler error:我收到这个编译器错误:

Davids-Air-2:test dbanas$ stack ghc -- -c so_natnorm.hs 

so_natnorm.hs:28:41: error:
    • Couldn't match type ‘CmpNat n n1’ with ‘'GT’
        arising from a use of ‘f’
    • In the second argument of ‘reifyNat’, namely ‘f’
      In the expression: reifyNat (getFinite x) f
      In an equation for ‘getFinite'’:
          getFinite' x f = reifyNat (getFinite x) f
    • Relevant bindings include
        f :: forall (m :: Nat).
             (KnownNat m, CmpNat n m ~ 'GT) =>
             Proxy m -> r
          (bound at so_natnorm.hs:28:14)
        x :: Finite n (bound at so_natnorm.hs:28:12)
        getFinite' :: Finite n
                      -> (forall (m :: Nat).
                          (KnownNat m, CmpNat n m ~ 'GT) =>
                          Proxy m -> r)
                      -> r
          (bound at so_natnorm.hs:28:1)

I'm guessing that my problem is trying to relate a universally and an existentially quantified type, through the mechanisms provided by the ghc-typelits-natnormalise package.我猜我的问题是试图通过ghc-typelits-natnormalise包提供的机制将普遍和存在量化的类型联系起来。 Is that correct?那是对的吗?

It seems to me that this ought to be allowed, since the caller is responsible for assigning both:在我看来,这应该被允许,因为调用者负责分配两者:

  • the value of n , and n的值,和
  • the maximum value of m . m的最大值。

Where is my reasoning about this faulty?我对这个错误的推理在哪里?

reifyNat takes as an argument a function which works for any natural. reifyNat将一个适用于任何自然的函数作为参数。 A function of type forall m. (KnownNat m, n `CmpNat` m ~ 'GT) => Proxy m -> r forall m. (KnownNat m, n `CmpNat` m ~ 'GT) => Proxy m -> r类型的函数forall m. (KnownNat m, n `CmpNat` m ~ 'GT) => Proxy m -> r forall m. (KnownNat m, n `CmpNat` m ~ 'GT) => Proxy m -> r doesn't work on any natural; forall m. (KnownNat m, n `CmpNat` m ~ 'GT) => Proxy m -> r不适用于任何自然; it only works on naturals less than some other n .它只适用于比其他n少的自然n

Since you are calling getFinite to produce the actual value, you know that value is less than n .由于您正在调用getFinite来生成实际值,因此您知道该值小于n Unfortunately, you have no way to prove this to the typechecker.不幸的是,您无法向类型检查员证明这一点。 Fortunately, you are allowed to tell the typechecker to trust you:幸运的是,您可以告诉类型检查器信任您:

import Type.Reflection ((:~:)(..))
import Unsafe.Coerce

...

getFinite'' :: KnownNat n => Finite n -> (forall m. (KnownNat m) => Proxy m -> n `CmpNat` m :~: 'GT -> r) -> r
getFinite'' x f = reifyNat (getFinite x) $ \p -> f p (unsafeCoerce Refl)

getFinite' :: forall n r . KnownNat n => Finite n -> (forall m. (KnownNat m, n `CmpNat` m ~ 'GT) => Proxy m -> r) -> r
getFinite' x f = getFinite'' x $ \p Refl -> f p

声明:本站的技术帖子网页,遵循CC BY-SA 4.0协议,如果您需要转载,请注明本站网址或者原文地址。任何问题请咨询:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM