You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
support request => you might also like to ask your question on the mailing list or gitter chat.
Description
The following computation gives different results when run with the Native and PTX backends:
mat :: Acc (Matrix Int)
mat = use $ fromList (Z :. 4 :. 3) [1..]
s :: Acc (Scalar Int)
s = A.unit (A.constant 0)
A.slice mat . lift $ Any :. the s :. All
Expected behaviour
The expected result is given by the Native backend:
Vector (Z :. 3) [1,2,3]
Current behaviour
The PTX backend gives the following result:
Vector (Z :. 3) [4,5,6]
Note that this result is given regardless of the value of s. For example, if we change
s :: Acc (Scalar Int)
s = A.unit (A.constant 3)
the native backend gives the expected result of
Vector (Z :. 3) [10,11,12]
while the PTX backend gives
Vector (Z :. 3) [4,5,6]
Steps to reproduce (for bugs)
Here is a test program:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE GADTs #-}
module Main where
import Prelude hiding (Num, zipWith, Eq, (==), (!!))
import qualified Prelude as P
import Data.Array.Accelerate as A hiding ((++))
import qualified Data.Array.Accelerate.LLVM.Native as Native
import qualified Data.Array.Accelerate.LLVM.PTX as PTX
mat :: Acc (Matrix Int)
mat = use $ fromList (Z :. 4 :. 3) [1..]
s :: Acc (Scalar Int)
s = A.unit (A.constant 3)
testCase :: (forall a . Arrays a => Acc a -> a) -> Acc (Scalar Int) -> Acc (Matrix Int) -> IO ()
testCase run ix m = do
putStrLn "given a matrix m ="
print (run m)
putStrLn $ "\n... and an index ix = " ++ show (run ix)
let sliced = A.slice mat . lift $ Any :. the s :. All
putStrLn $ "\nthe row at index " ++ show (run ix) ++ " is:\n" ++ show (run sliced)
main = do
putStrLn "==============================="
putStrLn "Native backend...\n"
testCase Native.run s mat
putStrLn "==============================="
putStrLn "\n\n\n"
putStrLn "==============================="
putStrLn "PTX backend...\n"
testCase PTX.run s mat
putStrLn "==============================="
... and here is what it prints on my system:
===============================
Native backend...
given a matrix m =
Matrix (Z :. 4 :. 3)
[ 1, 2, 3,
4, 5, 6,
7, 8, 9,
10, 11, 12]
... and an index ix = Scalar Z [3]
the row at index Scalar Z [3] is:
Vector (Z :. 3) [10,11,12]
===============================
===============================
PTX backend...
given a matrix m =
Matrix (Z :. 4 :. 3)
[ 1, 2, 3,
4, 5, 6,
7, 8, 9,
10, 11, 12]
... and an index ix = Scalar Z [3]
the row at index Scalar Z [3] is:
Vector (Z :. 3) [4,5,6]
===============================
Your environment
Version used: accelerate == 1.3
Backend(s) used and version: accelerate-llvm == 1.3, accelerate-llvm-native == 1.3, accelerate-llvm-ptx == 1.3
GHC version: 8.8.4
Operating system and version: Arch Linux
If this is a bug with the GPU backend, include the output of nvidia-device-query: I don't seem to have this program. Where do I get it?
GPU details:
GPU: GeForce GTX 1650
NVIDIA driver: 455.45.01
The text was updated successfully, but these errors were encountered:
I am submitting a...
Description
The following computation gives different results when run with the Native and PTX backends:
Expected behaviour
The expected result is given by the
Native
backend:Current behaviour
The PTX backend gives the following result:
Note that this result is given regardless of the value of
s
. For example, if we changethe native backend gives the expected result of
while the PTX backend gives
Steps to reproduce (for bugs)
Here is a test program:
... and here is what it prints on my system:
Your environment
nvidia-device-query
: I don't seem to have this program. Where do I get it?GPU details:
The text was updated successfully, but these errors were encountered: