Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Seq' g a = Seq' !g !(Tree a)
- type Seq = Seq' StdGen
- type Impure a = a
- type Splittable g = RandomGen g
- empty :: Seq a
- singleton :: a -> Seq a
- fromList :: [a] -> Seq a
- fromFunction :: Int -> (Int -> a) -> Seq a
- (<|) :: RandomGen g => a -> Seq' g a -> Seq' g a
- (|>) :: RandomGen g => Seq' g a -> a -> Seq' g a
- (><) :: RandomGen g => Seq' g a -> Seq' g a -> Seq' g a
- empty' :: g -> Seq' g a
- singleton' :: g -> a -> Seq' g a
- fromList' :: RandomGen g => g -> [a] -> Seq' g a
- replicate :: Int -> a -> Seq a
- replicateA :: Applicative f => Int -> f a -> f (Seq a)
- replicateM :: Monad m => Int -> m a -> m (Seq a)
- cycleTaking :: RandomGen g => Int -> Seq' g a -> Seq' g a
- iterateN :: Int -> (a -> a) -> a -> Seq a
- unfoldr :: (b -> Maybe (a, b)) -> b -> Seq a
- unfoldl :: (b -> Maybe (b, a)) -> b -> Seq a
- null :: Seq' g a -> Bool
- length :: Seq' g a -> Int
- data ViewL' g a
- viewl :: Seq' g a -> ViewL' g a
- tails :: RandomGen g => Seq' g a -> Seq' g (Seq' g a)
- takeWhileL :: (a -> Bool) -> Seq' g a -> Seq' g a
- takeWhileR :: (a -> Bool) -> Seq' g a -> Seq' g a
- dropWhileL :: (a -> Bool) -> Seq' g a -> Seq' g a
- dropWhileR :: (a -> Bool) -> Seq' g a -> Seq' g a
- spanl :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a)
- spanr :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a)
- breakl :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a)
- breakr :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a)
- partition :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a)
- filter :: (a -> Bool) -> Seq' g a -> Seq' g a
- lookup :: Int -> Seq' g a -> Maybe a
- (?!) :: Seq' g a -> Int -> Maybe a
- index :: Seq' g a -> Int -> a
- adjust :: (a -> a) -> Int -> Seq' g a -> Seq' g a
- adjust' :: (a -> a) -> Int -> Seq' g a -> Seq' g a
- update :: Int -> a -> Seq' g a -> Seq' g a
- take :: Int -> Seq' g a -> Seq' g a
- drop :: Int -> Seq' g a -> Seq' g a
- insertAt :: RandomGen g => Int -> a -> Seq' g a -> Seq' g a
- deleteAt :: Int -> Seq' g a -> Seq' g a
- splitAt :: RandomGen g => Int -> Seq' g a -> (Seq' g a, Seq' g a)
- mapWithIndex :: (Int -> a -> b) -> Seq' g a -> Seq' g b
- traverseWithIndex :: Applicative f => (Int -> a -> f b) -> Seq' g a -> f (Seq' g b)
- zip :: Seq' g a -> Seq' g b -> Seq' g (a, b)
- zipWith :: (a -> b -> c) -> Seq' g a -> Seq' g b -> Seq' g c
- splitSeq :: Splittable g => Seq' g a -> (Seq' g a, Seq' g a)
- refreshSeq :: Seq' g a -> Impure (Seq a)
- createSeq :: Tree a -> Impure (Seq a)
- seqBind :: Seq' g a -> (Tree a -> Rand g (Tree b)) -> Seq' g b
- seqDnib :: (Tree a -> Rand g (Tree b)) -> Seq' g a -> Seq' g b
- seqRun :: g -> Rand g (Tree a) -> Seq' g a
- seqLift :: (Tree a -> Tree b) -> Seq' g a -> Seq' g b
- seqLift2 :: (Tree a -> Tree b -> Tree c) -> Seq' g a -> Seq' g b -> Seq' g c
- seqLiftSplit :: Splittable g => (Tree a -> (Tree b, Tree c)) -> Seq' g a -> (Seq' g b, Seq' g c)
- seqApply :: (Tree a -> b) -> Seq' g a -> b
- seqLens :: Functor f => (Tree a -> f (Tree b)) -> Seq' g a -> f (Seq' g b)
Types
Synonyms
The actual type signatures of functions below are as general as possible.
Alternative signatures may appear in comments:
- A purely informative "enriched" type with Impure
and Splittable
hinting implementation details.
- A specialization at type Seq
that parallels the Data.Sequence
API.
A type synonym for documentation. Marks uses of unsafePerformIO
.
type Splittable g = RandomGen g Source #
A type synonym for documentation. Marks functions that only use the
split
method of random generators.
Construction
Since RAZ makes use of randomness, a pure implementation will leak in the
interface (e.g., via MonadRandom
constraints or explicit generator
passing).
In order to provide the same interface as Data.Sequence
from containers
,
we cheat by requesting a random generator via unsafePerformIO
and storing
it alongside the sequence when constructing it.
Functions that transform existing sequences can then be implemented purely.
Alternative construction functions (empty'
, singleton'
, fromList'
)
are provided for compatibility with other random generators.
fromFunction :: Int -> (Int -> a) -> Seq a Source #
fromFunction :: Int -> (Int -> a) -> Impure
(Seq a)
fromFunction n f = fromList (fmap f [0 .. n - 1])
O(n).
singleton' :: g -> a -> Seq' g a Source #
O(1). A singleton sequence.
Repetition
replicateA :: Applicative f => Int -> f a -> f (Seq a) Source #
replicateA :: Applicative f => Int -> f a -> f (Impure
(Seq a))
O(n).
replicateM :: Monad m => Int -> m a -> m (Seq a) Source #
replicateM :: Monad m => Int -> m a -> m (Impure
(Seq a))
O(n).
Iterative construction
iterateN :: Int -> (a -> a) -> a -> Seq a Source #
iterateN :: Int -> (a -> a) -> a -> Impure
(Seq a)
O(n).
unfoldr :: (b -> Maybe (a, b)) -> b -> Seq a Source #
unfoldr :: (b -> Maybe (a, b)) -> b -> Impure
(Seq a)
O(n), where n
is the length of the output sequence.
unfoldl :: (b -> Maybe (b, a)) -> b -> Seq a Source #
unfoldl :: (b -> Maybe (b, a)) -> b -> Impure
(Seq a)
O(n), where n
is the length of the output sequence.
Deconstruction
Queries
length :: Seq' g a -> Int Source #
length :: Seq
a -> Int
O(1). The number of elements in the sequence.
Views
Sublists
tails :: RandomGen g => Seq' g a -> Seq' g (Seq' g a) Source #
tails ::Splittable
g => Seq' g a -> Seq' g (Seq' g a) tails ::Seq
a ->Seq
(Seq
a)
Sequential searches
takeWhileL :: (a -> Bool) -> Seq' g a -> Seq' g a Source #
takeWhileL :: (a -> Bool) -> Seq a -> Seq a
spanl :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) Source #
spanl :: Splittable
g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a)
spanl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
spanr :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) Source #
spanr ::Splittable
g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) spanr :: (a -> Bool) ->Seq
a -> (Seq
a,Seq
a)
breakl :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) Source #
breakl ::Splittable
g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) breakl :: (a -> Bool) ->Seq
a -> (Seq
a,Seq
a)
breakr :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) Source #
breakr ::Splittable
g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) breakr :: (a -> Bool) ->Seq
a -> (Seq
a,Seq
a)
partition :: RandomGen g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) Source #
partition ::Splittable
g => (a -> Bool) -> Seq' g a -> (Seq' g a, Seq' g a) partition :: (a -> Bool) ->Seq
a -> (Seq
a,Seq
a)
Indexing
splitAt :: RandomGen g => Int -> Seq' g a -> (Seq' g a, Seq' g a) Source #
splitAt :: Splittable
g => Int -> Seq' g a -> (Seq' g a, Seq' g a)
splitAt :: Int -> Seq a -> (Seq a, Seq a)
Transformations
mapWithIndex :: (Int -> a -> b) -> Seq' g a -> Seq' g b Source #
mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b
traverseWithIndex :: Applicative f => (Int -> a -> f b) -> Seq' g a -> f (Seq' g b) Source #
traverseWithIndex :: Applicative f => (Int -> a -> f b) -> Seq a -> Seq b
Zips
zipWith :: (a -> b -> c) -> Seq' g a -> Seq' g b -> Seq' g c Source #
zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
Random generator manipulations
seqLiftSplit :: Splittable g => (Tree a -> (Tree b, Tree c)) -> Seq' g a -> (Seq' g b, Seq' g c) Source #