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
Glasgow Haskell Compiler
Packages
dph
Commits
bb726d81
Commit
bb726d81
authored
Jun 28, 2007
by
rl@cse.unsw.edu.au
Browse files
Lifted parallel arrays
parent
f013bad4
Changes
4
Hide whitespace changes
Inline
Side-by-side
Data/Array/Parallel/Lifted.hs
0 → 100644
View file @
bb726d81
module
Data.Array.Parallel.Lifted
(
PArray
(
..
),
PA
(
..
),
(
:->
),
(
$:
),
(
$:^
),
closurePA
)
where
import
Data.Array.Parallel.Lifted.PArray
import
Data.Array.Parallel.Lifted.Closure
Data/Array/Parallel/Lifted/Closure.hs
0 → 100644
View file @
bb726d81
module
Data.Array.Parallel.Lifted.Closure
(
(
:->
)(
..
),
PArray
(
..
),
(
$:
),
(
$:^
),
closurePA
)
where
import
Data.Array.Parallel.Lifted.PArray
infixr
0
:->
infixr
0
$:
,
$:^
-- |The type of closures
--
data
a
:->
b
=
forall
e
.
Clo
!
(
PA
e
)
!
(
e
->
a
->
b
)
!
(
PArray
e
->
PArray
a
->
PArray
b
)
e
-- |Closure application
--
(
$:
)
::
(
a
:->
b
)
->
a
->
b
{-# INLINE ($:) #-}
Clo
_
f
_
e
$:
a
=
f
e
a
-- |Arrays of closures (aka array closures)
--
data
instance
PArray
(
a
:->
b
)
=
forall
e
.
AClo
!
(
PA
e
)
!
(
e
->
a
->
b
)
!
(
PArray
e
->
PArray
a
->
PArray
b
)
!
(
PArray
e
)
-- |Lifted closure application
--
(
$:^
)
::
PArray
(
a
:->
b
)
->
PArray
a
->
PArray
b
{-# INLINE ($:^) #-}
AClo
_
_
f
es
$:^
as
=
f
es
as
closure_lengthP
::
PArray
(
a
:->
b
)
->
Int
{-# INLINE closure_lengthP #-}
closure_lengthP
(
AClo
pa
_
_
es
)
=
lengthP
pa
es
closure_replicateP
::
Int
->
(
a
:->
b
)
->
PArray
(
a
:->
b
)
{-# INLINE closure_replicateP #-}
closure_replicateP
n
(
Clo
pa
f
f'
e
)
=
AClo
pa
f
f'
(
replicateP
pa
n
e
)
-- |Closure dictionary
closurePA
::
PA
(
a
:->
b
)
closurePA
=
PA
{
lengthP
=
closure_lengthP
,
replicateP
=
closure_replicateP
}
Data/Array/Parallel/Lifted/PArray.hs
0 → 100644
View file @
bb726d81
module
Data.Array.Parallel.Lifted.PArray
(
PArray
,
PA
(
..
)
)
where
-- |Lifted parallel arrays
--
data
family
PArray
a
-- |Dictionaries
--
data
PA
a
=
PA
{
lengthP
::
PArray
a
->
Int
,
replicateP
::
Int
->
a
->
PArray
a
}
ndp.cabal
View file @
bb726d81
...
...
@@ -12,6 +12,7 @@ exposed-modules:
Data.Array.Parallel.Unlifted
Data.Array.Parallel.Unlifted.Distributed
Data.Array.Parallel.Unlifted.Parallel
Data.Array.Parallel.Lifted
Data.Array.Parallel.Base.Closure
other-modules:
Data.Array.Parallel.Base.Config
...
...
@@ -67,6 +68,8 @@ other-modules:
Data.Array.Parallel.Unlifted.Parallel.Permute
Data.Array.Parallel.Unlifted.Parallel.Enum
Data.Array.Parallel.Unlifted.Parallel.Segmented
Data.Array.Parallel.Lifted.PArray
Data.Array.Parallel.Lifted.Closure
ghc-options: -fglasgow-exts -fbang-patterns -O2 -funbox-strict-fields
-fliberate-case-threshold100 -fdicts-cheap -fno-method-sharing
-fmax-simplifier-iterations6 -threaded -haddock -ftype-families
...
...
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