brassica-0.0.3: Featureful sound change applier
Safe HaskellSafe-Inferred
LanguageHaskell2010

Brassica.SoundChange.Apply.Internal.MultiZipper

Description

Warning: This module is internal, and does not follow the Package Versioning Policy. It may be useful for extending Brassica, but be prepared to track development closely if you import this module.

Synopsis

Documentation

data MultiZipper t a Source #

A MultiZipper is a list zipper (list+current index), with the addition of ‘tags’ which can be assigned to indices in the list. Any tag may be assigned to any index, with the restriction that two different indices may not be tagged with the same tag. This sort of data structure is useful for certain algorithms, where it can be convenient to use tags to save positions in the list and then return back to them later.

(One subtlety: unlike most list zipper implementations, a MultiZipper positioned at the ‘end’ of a list is actually at positioned at the index one past the end of the list, rather than at the last element of the list. Although this makes some functions slightly more complex — most notably, value becomes non-total — it makes other algorithms simpler. For instance, this lets functions processing a MultiZipper to process a portion of the MultiZipper and then move to the next element immediately after the processed portion, allowing another function to be run to process the next part of the MultiZipper.)

Instances

Instances details
Foldable (MultiZipper t) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal.MultiZipper

Methods

fold :: Monoid m => MultiZipper t m -> m #

foldMap :: Monoid m => (a -> m) -> MultiZipper t a -> m #

foldMap' :: Monoid m => (a -> m) -> MultiZipper t a -> m #

foldr :: (a -> b -> b) -> b -> MultiZipper t a -> b #

foldr' :: (a -> b -> b) -> b -> MultiZipper t a -> b #

foldl :: (b -> a -> b) -> b -> MultiZipper t a -> b #

foldl' :: (b -> a -> b) -> b -> MultiZipper t a -> b #

foldr1 :: (a -> a -> a) -> MultiZipper t a -> a #

foldl1 :: (a -> a -> a) -> MultiZipper t a -> a #

toList :: MultiZipper t a -> [a] #

null :: MultiZipper t a -> Bool #

length :: MultiZipper t a -> Int #

elem :: Eq a => a -> MultiZipper t a -> Bool #

maximum :: Ord a => MultiZipper t a -> a #

minimum :: Ord a => MultiZipper t a -> a #

sum :: Num a => MultiZipper t a -> a #

product :: Num a => MultiZipper t a -> a #

Traversable (MultiZipper t) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal.MultiZipper

Methods

traverse :: Applicative f => (a -> f b) -> MultiZipper t a -> f (MultiZipper t b) #

sequenceA :: Applicative f => MultiZipper t (f a) -> f (MultiZipper t a) #

mapM :: Monad m => (a -> m b) -> MultiZipper t a -> m (MultiZipper t b) #

sequence :: Monad m => MultiZipper t (m a) -> m (MultiZipper t a) #

Functor (MultiZipper t) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal.MultiZipper

Methods

fmap :: (a -> b) -> MultiZipper t a -> MultiZipper t b #

(<$) :: a -> MultiZipper t b -> MultiZipper t a #

(Show a, Show t) => Show (MultiZipper t a) Source # 
Instance details

Defined in Brassica.SoundChange.Apply.Internal.MultiZipper

Methods

showsPrec :: Int -> MultiZipper t a -> ShowS #

show :: MultiZipper t a -> String #

showList :: [MultiZipper t a] -> ShowS #

Conversion

fromListStart :: [a] -> MultiZipper t a Source #

Convert a list to a MultiZipper positioned at the start of that list.

fromListPos :: [a] -> Int -> Maybe (MultiZipper t a) Source #

Convert a list to a MultiZipper at a specific position in the list. Returns Nothing if the index is invalid.

toList :: MultiZipper t a -> [a] Source #

Get the list stored in a MultiZipper.

Querying

curPos :: MultiZipper t a -> Int Source #

The current position of the MultiZipper.

atStart :: MultiZipper t a -> Bool Source #

Determine whether the MultiZipper is positioned at the start of its list.

atEnd :: MultiZipper t a -> Bool Source #

Determine whether the MultiZipper is positioned at the end of its list.

atBoundary :: MultiZipper t a -> Bool Source #

Determine whether the MultiZipper is positioned at the start or end of its list.

value :: MultiZipper t a -> Maybe a Source #

The element at the current position of the MultiZipper. Returns Nothing if the MultiZipper is positioned ‘at the end of the list’ (recall this actually means that the MultiZipper is positioned after the last element of its list).

valueN :: Int -> MultiZipper t a -> Maybe ([a], MultiZipper t a) Source #

valueN n mz returns the next n elements of mz starting from the current position, as well as returning a new MultiZipper positioned past the end of those n elements. (So running valueN m and then valueN n would return the next m+n elements.) Returns Nothing if this would move the position of the MultiZipper past the end of the list.

locationOf :: Ord t => t -> MultiZipper t a -> Maybe Int Source #

Given a tag, return its position

yank :: (a -> Maybe b) -> MultiZipper t a -> Maybe b Source #

Find first element before point which returns Just when queried, if any, returning the result of the query function.

Movement

move :: Int -> MultiZipper t a -> Maybe (MultiZipper t a) Source #

move n mz will move the position of mz by n forward (if n>0) or by -n backward (if n<0). Returns Nothing if this would cause the MultiZipper to move after the end or before the beginning of the list.

fwd :: MultiZipper t a -> Maybe (MultiZipper t a) Source #

Move one position forward if possible, otherwise return Nothing.

bwd :: MultiZipper t a -> Maybe (MultiZipper t a) Source #

Move one position backwards if possible, otherwise return Nothing.

consume :: MultiZipper t a -> Maybe (a, MultiZipper t a) Source #

If possible, move one position forward, returning the value moved over

seek :: Ord t => t -> MultiZipper t a -> Maybe (MultiZipper t a) Source #

Move the MultiZipper to be at the specified tag. Returns Nothing if that tag is not present.

toBeginning :: MultiZipper t a -> MultiZipper t a Source #

Move to the beginning of the MultiZipper.

toEnd :: MultiZipper t a -> MultiZipper t a Source #

Move to the end of the MultiZipper.

Modification

insert :: a -> MultiZipper t a -> MultiZipper t a Source #

Insert a new element at point and move forward by one position.

insertMany :: [a] -> MultiZipper t a -> MultiZipper t a Source #

Insert multiple elements at point and move after them. A simple wrapper around insert.

zap :: (a -> Maybe a) -> MultiZipper t a -> MultiZipper t a Source #

Modify the first element before point to which the modification function returns Just.

tag :: Ord t => t -> MultiZipper t a -> MultiZipper t a Source #

Set a tag at the current position.

tagAt :: Ord t => t -> Int -> MultiZipper t a -> Maybe (MultiZipper t a) Source #

Set a tag at a given position if possible, otherwise return Nothing.

query :: Ord t => MultiZipper t a -> [t] Source #

Get all tags at the current position

untag :: MultiZipper t a -> MultiZipper t a Source #

Remove all tags.

untagWhen :: (t -> Bool) -> MultiZipper t a -> MultiZipper t a Source #

Remove tags satisfying predicate

modifyBetween Source #

Arguments

:: Ord t 
=> (t, t)

Selected tags. Note that the resulting interval will be [inclusive, exclusive).

-> ([a] -> [a])

Function to modify designated interval.

-> MultiZipper t a 
-> Maybe (MultiZipper t a) 

Modify a MultiZipper between the selected tags. Returns Nothing if a nonexistent tag is selected, else returns the modified MultiZipper.

extend :: (MultiZipper t a -> b) -> MultiZipper t a -> MultiZipper t b Source #

Given a function to compute a value from a MultiZipper starting at a particular point, apply that function to all possible starting points and collect the results. Tags are left unchanged.

(Note: this is really just the same extend method as in the Comonad typeclass, although MultiZipper wouldn’t be a lawful comonad.)

extend' :: (MultiZipper t a -> b) -> MultiZipper t a -> MultiZipper t b Source #

Like extend, but includes the end position of the zipper, thus increasing the MultiZipper length by one when called.