我的(公认的折磨)Haskell 函数出现了虚假约束。我怎样才能满足它?
A spurious constraint is appearing on my (admittedly tortured) Haskell function. How can I satisfy it?
在 Haskell 中使用 DataKinds
,我生成了以下代码,它实现并滥用了一些类型级别的一元 nats:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Demo where
import Data.Proxy
import Data.Semigroup
import Numeric.Natural
import Data.Constraint
data Nat = Zero | Succ Nat
type family Pred (n :: Nat) where Pred ('Succ n) = n
class IsNat (n :: Nat) where
nat :: proxy n -> Natural
unNat :: proxy n -> (n ~ 'Zero => x) -> ((n ~ 'Succ (Pred n), IsNat (Pred n)) => x) -> x
instance IsNat 'Zero where
nat _ = 0
unNat _ z _ = z
instance IsNat n => IsNat ('Succ n) where
nat _ = succ (nat (Proxy @n))
unNat _ _ s = s
noneIsNotSuccd :: (n ~ 'Zero, n ~ 'Succ (Pred n)) => proxy n -> a
noneIsNotSuccd _ = error "GHC proved ('Zero ~ 'Succ (Pred 'Zero))!" -- don't worry, this won't happen
predSuccIsNat :: forall n proxy r. (n ~ 'Succ (Pred n)) => proxy n -> (IsNat (Pred n) => r) -> r
predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
data Indexed (n :: Nat) where
Z :: Indexed 'Zero
S :: Indexed n -> Indexed ('Succ n)
instance Show (Indexed n) where
show Z = "0"
show (S n) = "S" <> show n
recr :: forall n x. (IsNat n, Semigroup x) => (forall k. IsNat k => Indexed k -> x) -> Indexed n -> x
recr f Z = f Z
recr f (S predn) = predSuccIsNat (Proxy @n) (f predn) <> f (S predn)
main :: IO ()
main = print $ getSum $ recr (Sum . nat) (S Z)
当我尝试在 GHC 8.2.2 中编译它时,出现以下类型错误:
Demo.hs:35:25: error:
• Could not deduce (IsNat (Pred n)) arising from a use of ‘unNat’
from the context: n ~ 'Succ (Pred n)
bound by the type signature for:
predSuccIsNat :: forall (n :: Nat) (proxy :: Nat -> *) r.
n ~ 'Succ (Pred n) =>
proxy n -> (IsNat (Pred n) => r) -> r
at Demo.hs:34:1-96
• In the expression: unNat proxy (noneIsNotSuccd proxy) r
In an equation for ‘predSuccIsNat’:
predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
|
35 | predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
诚然,这是对 GHC 8.0.1 中发生的事情的改进,compiles fine and then fails at runtime:
*** Exception: Demo.hs:34:23: error:
• Could not deduce (IsNat (Pred n)) arising from a use of ‘unNat’
from the context: n ~ 'Succ (Pred n)
bound by the type signature for:
predSuccIsNat :: n ~ 'Succ (Pred n) =>
proxy n -> (IsNat (Pred n) => r) -> r
at Demo.hs:33:1-78
• In the expression: unNat proxy (noneIsNotSuccd proxy)
In an equation for ‘predSuccIsNat’:
predSuccIsNat proxy = unNat proxy (noneIsNotSuccd proxy)
(deferred type error)
似乎在 GHC 8.2.2 中,unNat
采用了隐式 (IsNat (Pred n))
约束,该约束未出现在类型签名中:
λ» :t unNat
unNat
:: IsNat n =>
proxy n
-> (n ~ 'Zero => x)
-> ((n ~ 'Succ (Pred n), IsNat (Pred n)) => x)
-> x
我有什么方法可以调用 unNat
来实现类似 predSuccIsNat
的东西吗?
predSuccIsNat :: forall n proxy r. (n ~ 'Succ (Pred n)) => proxy n -> (IsNat (Pred n) => r) -> r
predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
^^^^^
我不知道您希望从哪里获得使用 unNat
所需的 IsNat
词典。如果我将它添加到类型签名
predSuccIsNat :: forall n proxy r. IsNat n => (n ~ 'Succ (Pred n)) => proxy n -> (IsNat (Pred n) => r) -> r
predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
一切正常(在 ghc 8.2.1 上,它具有与 8.0.1 相同的延迟问题)。
没有它,您似乎想推断 if n ~ 'Succ (Pred n)
then IsNat n
—— 大概是因为 Pred n
仅在 Succ
上定义.但即使可以做出这种推论,也是不够的。例如 n ~ Succ m
也不足以推断 IsNat
,您还需要 IsNat m
.
在 Haskell 中使用 DataKinds
,我生成了以下代码,它实现并滥用了一些类型级别的一元 nats:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Demo where
import Data.Proxy
import Data.Semigroup
import Numeric.Natural
import Data.Constraint
data Nat = Zero | Succ Nat
type family Pred (n :: Nat) where Pred ('Succ n) = n
class IsNat (n :: Nat) where
nat :: proxy n -> Natural
unNat :: proxy n -> (n ~ 'Zero => x) -> ((n ~ 'Succ (Pred n), IsNat (Pred n)) => x) -> x
instance IsNat 'Zero where
nat _ = 0
unNat _ z _ = z
instance IsNat n => IsNat ('Succ n) where
nat _ = succ (nat (Proxy @n))
unNat _ _ s = s
noneIsNotSuccd :: (n ~ 'Zero, n ~ 'Succ (Pred n)) => proxy n -> a
noneIsNotSuccd _ = error "GHC proved ('Zero ~ 'Succ (Pred 'Zero))!" -- don't worry, this won't happen
predSuccIsNat :: forall n proxy r. (n ~ 'Succ (Pred n)) => proxy n -> (IsNat (Pred n) => r) -> r
predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
data Indexed (n :: Nat) where
Z :: Indexed 'Zero
S :: Indexed n -> Indexed ('Succ n)
instance Show (Indexed n) where
show Z = "0"
show (S n) = "S" <> show n
recr :: forall n x. (IsNat n, Semigroup x) => (forall k. IsNat k => Indexed k -> x) -> Indexed n -> x
recr f Z = f Z
recr f (S predn) = predSuccIsNat (Proxy @n) (f predn) <> f (S predn)
main :: IO ()
main = print $ getSum $ recr (Sum . nat) (S Z)
当我尝试在 GHC 8.2.2 中编译它时,出现以下类型错误:
Demo.hs:35:25: error:
• Could not deduce (IsNat (Pred n)) arising from a use of ‘unNat’
from the context: n ~ 'Succ (Pred n)
bound by the type signature for:
predSuccIsNat :: forall (n :: Nat) (proxy :: Nat -> *) r.
n ~ 'Succ (Pred n) =>
proxy n -> (IsNat (Pred n) => r) -> r
at Demo.hs:34:1-96
• In the expression: unNat proxy (noneIsNotSuccd proxy) r
In an equation for ‘predSuccIsNat’:
predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
|
35 | predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
诚然,这是对 GHC 8.0.1 中发生的事情的改进,compiles fine and then fails at runtime:
*** Exception: Demo.hs:34:23: error:
• Could not deduce (IsNat (Pred n)) arising from a use of ‘unNat’
from the context: n ~ 'Succ (Pred n)
bound by the type signature for:
predSuccIsNat :: n ~ 'Succ (Pred n) =>
proxy n -> (IsNat (Pred n) => r) -> r
at Demo.hs:33:1-78
• In the expression: unNat proxy (noneIsNotSuccd proxy)
In an equation for ‘predSuccIsNat’:
predSuccIsNat proxy = unNat proxy (noneIsNotSuccd proxy)
(deferred type error)
似乎在 GHC 8.2.2 中,unNat
采用了隐式 (IsNat (Pred n))
约束,该约束未出现在类型签名中:
λ» :t unNat
unNat
:: IsNat n =>
proxy n
-> (n ~ 'Zero => x)
-> ((n ~ 'Succ (Pred n), IsNat (Pred n)) => x)
-> x
我有什么方法可以调用 unNat
来实现类似 predSuccIsNat
的东西吗?
predSuccIsNat :: forall n proxy r. (n ~ 'Succ (Pred n)) => proxy n -> (IsNat (Pred n) => r) -> r
predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
^^^^^
我不知道您希望从哪里获得使用 unNat
所需的 IsNat
词典。如果我将它添加到类型签名
predSuccIsNat :: forall n proxy r. IsNat n => (n ~ 'Succ (Pred n)) => proxy n -> (IsNat (Pred n) => r) -> r
predSuccIsNat proxy r = unNat proxy (noneIsNotSuccd proxy) r
一切正常(在 ghc 8.2.1 上,它具有与 8.0.1 相同的延迟问题)。
没有它,您似乎想推断 if n ~ 'Succ (Pred n)
then IsNat n
—— 大概是因为 Pred n
仅在 Succ
上定义.但即使可以做出这种推论,也是不够的。例如 n ~ Succ m
也不足以推断 IsNat
,您还需要 IsNat m
.