2016-04-18 8 views
3

私は、これが実用的なアプローチであるかどうかを確認するために、部分的には、教育目的のために、加速の上にタイプセーフなマトリックス計算ライブラリを定義しようとしています。accelerate-haskellで行列積を定義する方法

しかし、私はGHCが自分のコードを受け入れ/コンパイルする方法で、行列の積を正しく定義するために完全に固執しています。私はこれのバリエーションたいくつかの試み、持っていた

:エラーstack buildは私を与える

Linear.hs

{-# LANGUAGE TypeOperators #-} 
{-# LANGUAGE DataKinds #-} 
{-# LANGUAGE KindSignatures #-} 
{-# LANGUAGE FlexibleContexts #-} 
{-# LANGUAGE TypeFamilies #-} 
{-# LANGUAGE ScopedTypeVariables #-} 

import qualified Data.Array.Accelerate as A 

import GHC.TypeLits 
import Data.Array.Accelerate ((:.)(..), Array 
          , Exp, Shape, FullShape, Slice 
          , DIM0, DIM1, DIM2, Z(Z) 
          , IsFloating, IsNum, Elt, Acc 
          , Any(Any), All(All)) 
import   Data.Proxy 

newtype Matrix (rows :: Nat) (cols :: Nat) a = AccMatrix {unMatrix :: Acc (Array DIM2 a)} 
(#*#) :: forall k m n a. (KnownNat k, KnownNat m, KnownNat n, IsNum a, Elt a) => 
    Matrix k m a -> Matrix m n a -> Matrix k n a 
v #*# w = let v' = unMatrix v 
       w' = unMatrix w 
      in AccMatrix $ A.generate (A.index2 k' n') undefined 
      where k' = fromInteger $ natVal (Proxy :: Proxy k) 
       n' = fromInteger $ natVal (Proxy :: Proxy n) 
       aux :: Acc (Array (FullShape (Z :. Int) :. Int) e) -> Acc (Array (FullShape (Z :. All) :. Int) e) -> Exp ((Z :. Int) :. Int) -> Exp e 
       aux v w sh = let (Z:.i:.j) = A.unlift sh 
           v' = A.slice v (A.lift $ Z:.i:.All) 
           w' = A.slice w (A.lift $ Z:.All:.j) 
           in A.the $ A.sum $ A.zipWith (*) v' w' 

は、私がAccelerateのドキュメントを参考にしている

.../src/Linear.hs:196:55: 
    Couldn't match type ‘A.Plain ((Z :. head0) :. head1)’ 
        with ‘(Z :. Int) :. Int’ 
    The type variables ‘head0’, ‘head1’ are ambiguous 
    Expected type: Exp (A.Plain ((Z :. head0) :. head1)) 
     Actual type: Exp ((Z :. Int) :. Int) 
    Relevant bindings include 
     i :: head0 (bound at src/Linear.hs:196:38) 
     j :: head1 (bound at src/Linear.hs:196:41) 
    In the first argument of ‘A.unlift’, namely ‘sh’ 
    In the expression: A.unlift sh 

.../src/Linear.hs:197:47: 
    Couldn't match type ‘FullShape (A.Plain (Z :. head0))’ 
        with ‘Z :. Int’ 
    The type variable ‘head0’ is ambiguous 
    Expected type: Acc 
        (Array (FullShape (A.Plain (Z :. head0) :. All)) e) 
     Actual type: Acc (Array (FullShape (Z :. Int) :. Int) e) 
    Relevant bindings include 
     v' :: Acc (Array (A.SliceShape (A.Plain (Z :. head0)) :. Int) e) 
     (bound at src/Linear.hs:197:34) 
     i :: head0 (bound at src/Linear.hs:196:38) 
    In the first argument of ‘A.slice’, namely ‘v’ 
    In the expression: A.slice v (A.lift $ Z :. i :. All) 

.../src/Linear.hs:198:39: 
    Couldn't match type ‘A.SliceShape (A.Plain ((Z :. All) :. head1))’ 
        with ‘A.SliceShape (A.Plain (Z :. head0)) :. Int’ 
    The type variables ‘head0’, ‘head1’ are ambiguous 
    Expected type: Acc 
        (Array (A.SliceShape (A.Plain (Z :. head0)) :. Int) e) 
     Actual type: Acc 
        (Array (A.SliceShape (A.Plain ((Z :. All) :. head1))) e) 
    Relevant bindings include 
     w' :: Acc (Array (A.SliceShape (A.Plain (Z :. head0)) :. Int) e) 
     (bound at src/Linear.hs:198:34) 
     v' :: Acc (Array (A.SliceShape (A.Plain (Z :. head0)) :. Int) e) 
     (bound at src/Linear.hs:197:34) 
     i :: head0 (bound at src/Linear.hs:196:38) 
     j :: head1 (bound at src/Linear.hs:196:41) 
    In the expression: A.slice w (A.lift $ Z :. All :. j) 
    In an equation for ‘w'’: w' = A.slice w (A.lift $ Z :. All :. j) 

.../src/Linear.hs:198:47: 
    Couldn't match type ‘FullShape (A.Plain ((Z :. All) :. head1))’ 
        with ‘(Z :. Int) :. Int’ 
    The type variable ‘head1’ is ambiguous 
    Expected type: Acc 
        (Array (FullShape (A.Plain ((Z :. All) :. head1))) e) 
     Actual type: Acc (Array (FullShape (Z :. All) :. Int) e) 
    Relevant bindings include 
     j :: head1 (bound at src/Linear.hs:196:41) 
    In the first argument of ‘A.slice’, namely ‘w’ 
    In the expression: A.slice w (A.lift $ Z :. All :. j) 

です同様の目的を持っていますが、配列をアサートするためにTypeLitsを使用していないaccelerate-arithmeticも読んでいます/ベクトル次元。

また、私のタイプが間違っている場合に備えて、sliceの使い方について同じ誤解を受けていると考えて、バニラバージョン(つまり自分のマトリックスタイプなし)を作ってみました。私はこれを完全に含むために、私はエラーメッセージを追加することができますが、私はそれらが上記の問題に関係しないと信じているので、それらを省略することを選択しました。

(#*#) :: forall a. (IsNum a, Elt a) => 
    Acc (Array DIM2 a) -> Acc (Array DIM2 a) -> Maybe (Acc (Array DIM2 a)) 
v #*# w = let Z:.k :.m = A.unlift $ A.arrayShape $ I.run v 
       Z:.m':.n = A.unlift $ A.arrayShape $ I.run w 
      in if m /= m' 
       then Nothing 
       else Just $ AccMatrix $ A.generate (A.index2 k n) (aux v w) 
      where aux :: Acc (Array DIM2 a) -> Acc (Array DIM2 a) -> Exp DIM2 -> Exp a 
       aux v w sh = let (Z:.i:.j) = A.unlift sh 
           v' = A.slice v (A.lift $ Z:.i:.All) 
           w' = A.slice w (A.lift $ Z:.All:.j) 
           in A.the $ A.sum $ A.zipWith (*) v' w' 

答えて

1

実際にはコードは正しいです。残念ながら、型チェッカーはそれを把握するために十分にスマートではありませんので、あなたはそれを助けるために持っている:

let (Z:.i:.j) = A.unlift sh 

は、ここで重要なことは、(A.unlift :: A.Unlift c e => c (A.Plain e) -> eしかしA.Plainが関連付けられているタイプの家族であるということです

let (Z:.i:.j) = A.unlift sh :: (Z :. Exp Int) :. Exp Int 

なり従って非注入型であるため)タイプeはタイプシグネチャなしでは決定できず、Unlift c eに使用するインスタンスを選択するにはeが必要です。これは、あいまいなタイプのエラーが出てくるところです。実際はeであいまいです。


また、関連のないエラーがあります。 auxa(#*#)の型シグネチャ内の1つであり、後者の場合に

aux :: (IsNum e, Elt e) => ... 

又は

aux :: (e ~ a) => ... 

タイプはそれが既に制約IsNum, Elt

を有している必要があり
関連する問題