无法推断(Dim n0)



我想使用线性包构建一个希尔伯特矩阵,并将其转换为列表的列表。虽然这似乎是一项简单的任务,但类型级别的约束进入了我的方式:

import Linear
import Linear.V
import Data.Vector qualified as V
-- | Outer (tensor) product of two vectors
outerWith :: (Functor f, Functor g, Num a) => (a -> a -> a) -> f a -> g a -> f (g a)
{-# INLINABLE outerWith #-}
outerWith f a b = fmap (x -> fmap (f x) b) a
hilbertV :: forall a n. (Fractional a, Dim n) => Integer -> V n (V n a)
hilbertV n =
let v = V $ V.fromList $ fromIntegral <$> [1..n]
w = V $ V.fromList $ fromIntegral <$> [0..n-1]
in luInv $ outerWith (+) w v
listsFromM :: V n (V n a) -> [[a]]
listsFromM m = vToList (vToList <$> m)
vToList :: V n a -> [a]
vToList = V.toList . toVector
hilbertL :: forall a. (Fractional a) => Integer -> [[a]]
hilbertL n = listsFromM (hilbertV n)

执行此操作时,在最后一行hilbertL n = listsFromM (hilbertV n)中出现以下错误:

bench/Solve.hs:28:26: error:
• Could not deduce (Dim n0) arising from a use of ‘hilbertV’
from the context: Fractional a
bound by the type signature for:
hilbertL :: forall a. Fractional a => Integer -> [[a]]
at bench/Solve.hs:27:1-56
The type variable ‘n0’ is ambiguous
These potential instances exist:
three instances involving out-of-scope types
instance GHC.TypeNats.KnownNat n => Dim n -- Defined in ‘Linear.V’
instance Data.Reflection.Reifies s Int =>
Dim (Linear.V.ReifiedDim s)
-- Defined in ‘Linear.V’
instance forall k (n :: k) a. Dim n => Dim (V n a)
-- Defined in ‘Linear.V’
• In the first argument of ‘listsFromM’, namely ‘(hilbertV n)’
In the expression: listsFromM (hilbertV n)
In an equation for ‘hilbertL’: hilbertL n = listsFromM (hilbertV n)

我怎么能得到这个编译?

首先,HilbertV的类型是不安全的。你不应该传入一个Integer大小,如果大小应该由类型决定!我想你需要这个:

{-# LANGUAGE TypeApplications, UnicodeSyntax #-}
hilbertV :: ∀ a n. (Fractional a, Dim n) => V n (V n a)
hilbertV = luInv $ outerWith (+) w v
where v = V $ V.fromList $ fromIntegral <$> [1..n]
w = V $ V.fromList $ fromIntegral <$> [0..n-1]
n = reflectDim @n []

([]只是用最简洁的方式填充代理参数,以生成无值的函子输入,因为使用-XTypeApplications更容易传递类型信息。)

事实上,我甚至会避免两次传递n。相反,为什么不排除边缘代呢:

hilbertV :: ∀ a n. (Fractional a, Dim n) => V n (V n a)
hilbertV = luInv $ outerWith (+) w v
where v = fromIntegral <$> enumFinFrom 1
w = fromIntegral <$> enumFinFrom 0
enumFinFrom :: ∀ n a . (Enum a, Dim n) => a -> V n a
enumFinFrom ini = V . V.fromList $ take (reflectDim @n []) [ini..]

现在,对于hilbertL,问题是您有一个依赖类型大小。处理这个问题的技巧是rank - 2量化函数;linear提供reifyDim/reifyVector等。

hilbertL :: ∀ a . Fractional a => Int -> [[a]]
hilbertL n = reifyDim n hilbertL'
where hilbertL' :: ∀ n p . Dim n => p n -> [[a]]
hilbertL' _ = listsFromM $ hilbertV @n

或者,您也可以将hilbertV更改为接受大小的代理参数,然后将其提交。我一直觉得这有点难看,但在这种情况下它实际上更紧凑:

hilbertV :: ∀ a n p . (Fractional a, Dim n) => p n -> V n (V n a)
hilbertV np = luInv $ outerWith (+) w v
where v = V $ V.fromList $ fromIntegral <$> [1..n]
w = V $ V.fromList $ fromIntegral <$> [0..n-1]
n = reflectDim np
hilbertL :: ∀ a . Fractional a => Int -> [[a]]
hilbertL n = reifyDim n (np -> listsFromM $ hilbertV np)

最新更新