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
39beda6b
Commit
39beda6b
authored
Mar 27, 2007
by
rl@cse.unsw.edu.au
Browse files
Add scan1S
parent
cb58fb37
Changes
2
Hide whitespace changes
Inline
Side-by-side
Data/Array/Parallel/Stream/Flat.hs
View file @
39beda6b
...
...
@@ -21,7 +21,7 @@ module Data.Array.Parallel.Stream.Flat (
enumFromToS
,
enumFromThenToS
,
enumFromStepLenS
,
toStream
,
fromStream
,
mapS
,
filterS
,
foldS
,
fold1MaybeS
,
scanS
,
mapAccumS
,
mapS
,
filterS
,
foldS
,
fold1MaybeS
,
scanS
,
scan1S
,
mapAccumS
,
zipWithS
,
zipWith3S
,
zipS
,
findS
,
findIndexS
,
...
...
Data/Array/Parallel/Stream/Flat/Combinators.hs
View file @
39beda6b
...
...
@@ -14,7 +14,7 @@
--
module
Data.Array.Parallel.Stream.Flat.Combinators
(
mapS
,
filterS
,
foldS
,
fold1MaybeS
,
scanS
,
mapAccumS
,
mapS
,
filterS
,
foldS
,
fold1MaybeS
,
scanS
,
scan1S
,
mapAccumS
,
zipWithS
,
zipWith3S
,
zipS
)
where
...
...
@@ -83,6 +83,25 @@ scanS f z (Stream next s n) = Stream next' (Box z :*: s) n
Skip
s'
->
Skip
(
Box
z
:*:
s'
)
Yield
x
s'
->
Yield
z
(
Box
(
f
z
x
)
:*:
s'
)
scan1S
::
(
a
->
a
->
a
)
->
Stream
a
->
Stream
a
{-# INLINE [1] scan1S #-}
scan1S
f
(
Stream
next
s
n
)
=
Stream
next'
(
NothingS
:*:
s
)
n
where
{-# INLINE next' #-}
next'
(
NothingS
:*:
s
)
=
case
next
s
of
Yield
x
s'
->
Yield
x
(
JustS
(
Box
x
)
:*:
s'
)
Skip
s'
->
Skip
(
NothingS
:*:
s'
)
Done
->
Done
next'
(
JustS
(
Box
z
)
:*:
s
)
=
case
next
s
of
Yield
x
s'
->
let
y
=
f
z
x
in
Yield
y
(
JustS
(
Box
y
)
:*:
s'
)
Skip
s'
->
Skip
(
JustS
(
Box
z
)
:*:
s
)
Done
->
Done
mapAccumS
::
(
acc
->
a
->
acc
:*:
b
)
->
acc
->
Stream
a
->
Stream
b
{-# INLINE [1] mapAccumS #-}
mapAccumS
f
acc
(
Stream
step
s
n
)
=
Stream
step'
(
s
:*:
Box
acc
)
n
...
...
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