Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Alex D
GHC
Commits
0fc8eeb4
Commit
0fc8eeb4
authored
Dec 18, 2011
by
chak@cse.unsw.edu.au.
Browse files
Testing vectorisation of superclasses
parent
01477fef
Changes
4
Hide whitespace changes
Inline
Side-by-side
testsuite/.gitignore
View file @
0fc8eeb4
...
...
@@ -142,4 +142,5 @@ tests/dph/primespj/dph-primespj-copy-fast
tests/dph/quickhull/dph-quickhull-copy-fast
tests/dph/quickhull/dph-quickhull-vseg-fast
tests/dph/words/dph-words-copy-fast
tests/dph/words/dph-words-vseg-fast
\ No newline at end of file
tests/dph/words/dph-words-vseg-fast
tests/dph/classes/dph-classes-vseg-fast
\ No newline at end of file
testsuite/tests/dph/classes/DefsVect.hs
View file @
0fc8eeb4
...
...
@@ -5,16 +5,26 @@ module DefsVect where
import
Data.Array.Parallel
import
Data.Array.Parallel.Prelude.Bool
import
Data.Array.Parallel.Prelude.Int
(
Int
)
import
Data.Array.Parallel.Prelude.Int
(
Int
,
sumP
)
{-# VECTORISE class Eq #-}
{-# VECTORISE SCALAR instance Eq Bool #-}
-- {-# VECTORISE SCALAR instance Eq Char #-}
{-# VECTORISE SCALAR instance Eq Int #-}
{-# VECTORISE SCALAR instance Eq Word8 #-}
-- {-# VECTORISE SCALAR instance Eq Float #-}
{-# VECTORISE SCALAR instance Eq Double #-}
{-# VECTORISE SCALAR instance Eq Ordering #-}
{-# VECTORISE class Ord #-}
{-# VECTORISE SCALAR instance Ord Bool #-}
-- {-# VECTORISE SCALAR instance Ord Char #-}
{-# VECTORISE SCALAR instance Ord Int #-}
{-# VECTORISE SCALAR instance Ord Word8 #-}
-- {-# VECTORISE SCALAR instance Ord Float #-}
{-# VECTORISE SCALAR instance Ord Double #-}
{-# VECTORISE SCALAR instance Ord Ordering #-}
-- {-# VECTORISE class Ord #-}
-- {-# VECTORISE SCALAR instance Ord Int #-}
-- {-# VECTORISE type Ordering #-}
data
MyBool
=
MyTrue
|
MyFalse
...
...
@@ -49,4 +59,4 @@ isEqs :: PArray Int -> Bool
isEqs
xs
=
isEqs'
(
fromPArrayP
xs
)
isEqs'
::
[
:
Int
:
]
->
Bool
isEqs'
xs
=
andP
(
mapP
isEq
xs
)
\ No newline at end of file
isEqs'
xs
=
andP
(
mapP
isEq
xs
)
testsuite/tests/dph/classes/dph-classes-vseg-fast.stdout
0 → 100644
View file @
0fc8eeb4
[True,False,True,True]
testsuite/tests/dph/classes/dph-classes.T
View file @
0fc8eeb4
test
('
dph-classes-
copy
-fast
'
test
('
dph-classes-
vseg
-fast
'
,
[
alone
,
extra_clean
(['
Main.o
',
'
Main.hi
',
'
DefsVect.hi
',
'
DefsVect.o
'])
,
reqlib
('
dph-lifted-
copy
')
,
reqlib
('
dph-lifted-
vseg
')
,
reqlib
('
dph-prim-par
')
,
only_ways
(['
normal
',
'
threaded1
',
'
threaded2
'])
]
,
multimod_compile_and_run
,
[
'
Main
'
,
'
-O -fno-enable-rewrite-rules -package dph-lifted-copy
'])
,
'
-O -fno-enable-rewrite-rules -package dph-lifted-vseg
'])
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment