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
681ea9ab
Commit
681ea9ab
authored
Mar 27, 2007
by
rl@cse.unsw.edu.au
Browse files
Add tailS
parent
8e77dee3
Changes
2
Hide whitespace changes
Inline
Side-by-side
Data/Array/Parallel/Stream/Flat.hs
View file @
681ea9ab
...
...
@@ -17,7 +17,7 @@ module Data.Array.Parallel.Stream.Flat (
Step
(
..
),
Stream
(
..
),
emptyS
,
singletonS
,
consS
,
replicateS
,
replicateEachS
,
(
+++
),
indexedS
,
indexedS
,
tailS
,
enumFromToS
,
enumFromThenToS
,
enumFromStepLenS
,
toStream
,
fromStream
,
...
...
Data/Array/Parallel/Stream/Flat/Basics.hs
View file @
681ea9ab
...
...
@@ -15,6 +15,7 @@
module
Data.Array.Parallel.Stream.Flat.Basics
(
emptyS
,
singletonS
,
consS
,
replicateS
,
replicateEachS
,
(
+++
),
indexedS
,
tailS
,
toStream
,
fromStream
)
where
...
...
@@ -114,6 +115,25 @@ indexedS (Stream next s n) = Stream next' (0 :*: s) n
Skip
s'
->
Skip
(
i
:*:
s'
)
Done
->
Done
-- | Substreams
-- ------------
-- | Yield the tail of a stream
--
tailS
::
Stream
a
->
Stream
a
{-# INLINE [1] tailS #-}
tailS
(
Stream
next
s
n
)
=
Stream
next'
(
False
:*:
s
)
(
n
-
1
)
where
{-# INLINE next' #-}
next'
(
False
:*:
s
)
=
case
next
s
of
Yield
x
s'
->
Skip
(
True
:*:
s'
)
Skip
s'
->
Skip
(
False
:*:
s'
)
Done
->
error
"Stream.tailS: empty stream"
next'
(
True
:*:
s
)
=
case
next
s
of
Yield
x
s'
->
Yield
x
(
True
:*:
s'
)
Skip
s'
->
Skip
(
True
:*:
s'
)
Done
->
Done
-- | Conversion to\/from lists
-- --------------------------
...
...
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