raz-0.1.0.0: Random Access Zippers

Safe HaskellNone
LanguageHaskell2010

Data.Raz.Sequence.Internal

Contents

Synopsis

Types

data Seq' g a Source #

Constructors

Seq' !g !(Tree a) 

Instances

Functor (Seq' g) Source # 

Methods

fmap :: (a -> b) -> Seq' g a -> Seq' g b #

(<$) :: a -> Seq' g b -> Seq' g a #

Applicative (Seq' StdGen) Source #
pure :: a -> Impure (Seq a)
(<*>) :: Seq (a -> b) -> Seq a -> Seq b

Methods

pure :: a -> Seq' StdGen a #

(<*>) :: Seq' StdGen (a -> b) -> Seq' StdGen a -> Seq' StdGen b #

(*>) :: Seq' StdGen a -> Seq' StdGen b -> Seq' StdGen b #

(<*) :: Seq' StdGen a -> Seq' StdGen b -> Seq' StdGen a #

Foldable (Seq' g) Source # 

Methods

fold :: Monoid m => Seq' g m -> m #

foldMap :: Monoid m => (a -> m) -> Seq' g a -> m #

foldr :: (a -> b -> b) -> b -> Seq' g a -> b #

foldr' :: (a -> b -> b) -> b -> Seq' g a -> b #

foldl :: (b -> a -> b) -> b -> Seq' g a -> b #

foldl' :: (b -> a -> b) -> b -> Seq' g a -> b #

foldr1 :: (a -> a -> a) -> Seq' g a -> a #

foldl1 :: (a -> a -> a) -> Seq' g a -> a #

toList :: Seq' g a -> [a] #

null :: Seq' g a -> Bool #

length :: Seq' g a -> Int #

elem :: Eq a => a -> Seq' g a -> Bool #

maximum :: Ord a => Seq' g a -> a #

minimum :: Ord a => Seq' g a -> a #

sum :: Num a => Seq' g a -> a #

product :: Num a => Seq' g a -> a #

Traversable (Seq' g) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Seq' g a -> f (Seq' g b) #

sequenceA :: Applicative f => Seq' g (f a) -> f (Seq' g a) #

mapM :: Monad m => (a -> m b) -> Seq' g a -> m (Seq' g b) #

sequence :: Monad m => Seq' g (m a) -> m (Seq' g a) #

Eq a => Eq (Seq' g a) Source # 

Methods

(==) :: Seq' g a -> Seq' g a -> Bool #

(/=) :: Seq' g a -> Seq' g a -> Bool #

Ord a => Ord (Seq' g a) Source # 

Methods

compare :: Seq' g a -> Seq' g a -> Ordering #

(<) :: Seq' g a -> Seq' g a -> Bool #

(<=) :: Seq' g a -> Seq' g a -> Bool #

(>) :: Seq' g a -> Seq' g a -> Bool #

(>=) :: Seq' g a -> Seq' g a -> Bool #

max :: Seq' g a -> Seq' g a -> Seq' g a #

min :: Seq' g a -> Seq' g a -> Seq' g a #

Show a => Show (Seq' g a) Source # 

Methods

showsPrec :: Int -> Seq' g a -> ShowS #

show :: Seq' g a -> String #

showList :: [Seq' g a] -> ShowS #

Synonyms

The actual type signatures of functions in this module are as general as possible. Alternative signatures may appear in comments:

  • a purely informative "enriched" type with Impure and Splittable marking certain implementation details;
  • a specialization at type Seq that parallels the Data.Sequence API.

type Seq = Seq' StdGen Source #

The sequence type with a default generator.

type Impure a = a Source #

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.

empty :: Seq a Source #

empty :: Impure (Seq a)

O(1). The empty sequence.

singleton :: a -> Seq a Source #

singleton :: a -> Impure (Seq a)

O(1). A singleton sequence.

fromList :: [a] -> Seq a Source #

fromList :: [a] -> Impure (Seq a)

O(n). Create a sequence from a finite list of elements.

The inverse toList is given by the Foldable instance of Seq.

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).

(<|) :: RandomGen g => a -> Seq' g a -> Seq' g a Source #

(<|) :: a -> Seq a -> Seq a

(|>) :: RandomGen g => Seq' g a -> a -> Seq' g a Source #

(|>) :: Seq a -> a -> Seq a

(><) :: RandomGen g => Seq' g a -> Seq' g a -> Seq' g a Source #

(><) :: Seq a -> Seq a -> Seq a

empty' :: g -> Seq' g a Source #

O(1). The empty sequence.

singleton' :: g -> a -> Seq' g a Source #

O(1). A singleton sequence.

fromList' :: RandomGen g => g -> [a] -> Seq' g a Source #

Repetition

replicate :: Int -> a -> Seq a Source #

replicate :: Int -> a -> Impure (Seq a)

O(n).

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).

cycleTaking :: RandomGen g => Int -> Seq' g a -> Seq' g a Source #

cycleTaking :: Int -> Seq a -> Seq a

O(k).

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

null :: Seq' g a -> Bool Source #

null :: Seq a -> Bool

O(1). Is this the empty sequence?

length :: Seq' g a -> Int Source #

length :: Seq a -> Int

O(1). The number of elements in the sequence.

Views

data ViewL' g a Source #

Constructors

EmptyL 
a :< (Seq' g a) 

viewl :: Seq' g a -> ViewL' g a Source #

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

takeWhileR :: (a -> Bool) -> Seq' g a -> Seq' g a Source #

takeWhileR :: (a -> Bool) -> Seq a -> Seq a

dropWhileL :: (a -> Bool) -> Seq' g a -> Seq' g a Source #

dropWhileL :: (a -> Bool) -> Seq a -> Seq a

dropWhileR :: (a -> Bool) -> Seq' g a -> Seq' g a Source #

dropWhileR :: (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)

filter :: (a -> Bool) -> Seq' g a -> Seq' g a Source #

filter :: (a -> Bool) -> Seq a -> Seq a

Indexing

lookup :: Int -> Seq' g a -> Maybe a Source #

lookup :: Int -> Seq a -> Maybe a

(?!) :: Seq' g a -> Int -> Maybe a Source #

(?!) :: Seq a -> Int -> Maybe a

index :: Seq' g a -> Int -> a Source #

index :: Seq a -> Int -> a

adjust :: (a -> a) -> Int -> Seq' g a -> Seq' g a Source #

adjust :: (a -> a) -> Int -> Seq a -> Seq a

adjust' :: (a -> a) -> Int -> Seq' g a -> Seq' g a Source #

adjust' :: (a -> a) -> Int -> Seq a -> Seq a

update :: Int -> a -> Seq' g a -> Seq' g a Source #

update :: Int -> a -> Seq a -> Seq a

take :: Int -> Seq' g a -> Seq' g a Source #

take :: Int -> Seq a -> Seq a

drop :: Int -> Seq' g a -> Seq' g a Source #

drop :: Int -> Seq a -> Seq a

insertAt :: RandomGen g => Int -> a -> Seq' g a -> Seq' g a Source #

insertAt :: Int -> a -> Seq a -> Seq a

deleteAt :: Int -> Seq' g a -> Seq' g a Source #

deleteAt :: Int -> Seq a -> Seq a

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

zip :: Seq' g a -> Seq' g b -> Seq' g (a, b) Source #

zip :: Seq a -> Seq b -> Seq (a, b)

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 manipulation

splitSeq :: Splittable g => Seq' g a -> (Seq' g a, Seq' g a) Source #

refreshSeq :: Seq' g a -> Impure (Seq a) Source #

Put a fresh generator.

createSeq :: Tree a -> Impure (Seq a) Source #

Wrap a Tree into a Seq.

seqBind :: Seq' g a -> (Tree a -> Rand g (Tree b)) -> Seq' g b Source #

seqDnib :: (Tree a -> Rand g (Tree b)) -> Seq' g a -> Seq' g b Source #

seqRun :: g -> Rand g (Tree a) -> Seq' g a Source #

seqLift :: (Tree a -> Tree b) -> Seq' g a -> Seq' g b Source #

seqLift2 :: (Tree a -> Tree b -> Tree c) -> Seq' g a -> Seq' g b -> Seq' g c Source #

seqLiftSplit :: Splittable g => (Tree a -> (Tree b, Tree c)) -> Seq' g a -> (Seq' g b, Seq' g c) Source #

seqApply :: (Tree a -> b) -> Seq' g a -> b Source #

seqLens :: Functor f => (Tree a -> f (Tree b)) -> Seq' g a -> f (Seq' g b) Source #