diag: no need for type annotation

parent 5cedf5b3
...@@ -30,7 +30,6 @@ Implementation use Accelerate library : ...@@ -30,7 +30,6 @@ Implementation use Accelerate library :
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
...@@ -87,8 +86,8 @@ mkSum r mat = replicate (constant (Z :. (r :: Int) :. All)) $ sum mat ...@@ -87,8 +86,8 @@ mkSum r mat = replicate (constant (Z :. (r :: Int) :. All)) $ sum mat
divByDiag :: Rank -> Acc (Matrix Double) -> Acc (Matrix Double) divByDiag :: Rank -> Acc (Matrix Double) -> Acc (Matrix Double)
divByDiag r mat = zipWith (/) mat (replicate (constant (Z :. (r :: Int) :. All)) $ diag mat) divByDiag r mat = zipWith (/) mat (replicate (constant (Z :. (r :: Int) :. All)) $ diag mat)
diag :: forall e. Elt e => Acc (Matrix e) -> Acc (Vector e) diag :: Elt e => Acc (Matrix e) -> Acc (Vector e)
diag m = backpermute (indexTail (shape m)) (lift1 (\(Z :. x) -> (Z :. x :. (x :: Exp Int)))) (m :: Acc (Array DIM2 e)) diag m = backpermute (indexTail (shape m)) (lift1 (\(Z :. x) -> (Z :. x :. (x :: Exp Int)))) m
type Matrix' a = Acc (Matrix a) type Matrix' a = Acc (Matrix a)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment