focuslist-0.1.0.2: Lists with a focused element

Safe HaskellNone
LanguageHaskell2010

Data.FocusList

Contents

Synopsis

FocusList

data FocusList a Source #

A list with a given element having the Focus.

FocusList has some invariants that must be protected. You should not use the FocusList constructor or the focusListFocus or focusList accessors.

Implemented under the hood as a Seq.

Constructors

FocusList 

Fields

Instances
Functor FocusList Source # 
Instance details

Defined in Data.FocusList

Methods

fmap :: (a -> b) -> FocusList a -> FocusList b #

(<$) :: a -> FocusList b -> FocusList a #

Foldable FocusList Source # 
Instance details

Defined in Data.FocusList

Methods

fold :: Monoid m => FocusList m -> m #

foldMap :: Monoid m => (a -> m) -> FocusList a -> m #

foldr :: (a -> b -> b) -> b -> FocusList a -> b #

foldr' :: (a -> b -> b) -> b -> FocusList a -> b #

foldl :: (b -> a -> b) -> b -> FocusList a -> b #

foldl' :: (b -> a -> b) -> b -> FocusList a -> b #

foldr1 :: (a -> a -> a) -> FocusList a -> a #

foldl1 :: (a -> a -> a) -> FocusList a -> a #

toList :: FocusList a -> [a] #

null :: FocusList a -> Bool #

length :: FocusList a -> Int #

elem :: Eq a => a -> FocusList a -> Bool #

maximum :: Ord a => FocusList a -> a #

minimum :: Ord a => FocusList a -> a #

sum :: Num a => FocusList a -> a #

product :: Num a => FocusList a -> a #

Traversable FocusList Source # 
Instance details

Defined in Data.FocusList

Methods

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

sequenceA :: Applicative f => FocusList (f a) -> f (FocusList a) #

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

sequence :: Monad m => FocusList (m a) -> m (FocusList a) #

Arbitrary1 FocusList Source # 
Instance details

Defined in Data.FocusList

Methods

liftArbitrary :: Gen a -> Gen (FocusList a) #

liftShrink :: (a -> [a]) -> FocusList a -> [FocusList a] #

Eq a => Eq (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Methods

(==) :: FocusList a -> FocusList a -> Bool #

(/=) :: FocusList a -> FocusList a -> Bool #

Show a => Show (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Generic (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Associated Types

type Rep (FocusList a) :: Type -> Type #

Methods

from :: FocusList a -> Rep (FocusList a) x #

to :: Rep (FocusList a) x -> FocusList a #

Arbitrary a => Arbitrary (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Methods

arbitrary :: Gen (FocusList a) #

shrink :: FocusList a -> [FocusList a] #

CoArbitrary a => CoArbitrary (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Methods

coarbitrary :: FocusList a -> Gen b -> Gen b #

SemiSequence (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Associated Types

type Index (FocusList a) :: Type #

MonoFunctor (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Methods

omap :: (Element (FocusList a) -> Element (FocusList a)) -> FocusList a -> FocusList a #

MonoFoldable (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Methods

ofoldMap :: Monoid m => (Element (FocusList a) -> m) -> FocusList a -> m #

ofoldr :: (Element (FocusList a) -> b -> b) -> b -> FocusList a -> b #

ofoldl' :: (a0 -> Element (FocusList a) -> a0) -> a0 -> FocusList a -> a0 #

otoList :: FocusList a -> [Element (FocusList a)] #

oall :: (Element (FocusList a) -> Bool) -> FocusList a -> Bool #

oany :: (Element (FocusList a) -> Bool) -> FocusList a -> Bool #

onull :: FocusList a -> Bool #

olength :: FocusList a -> Int #

olength64 :: FocusList a -> Int64 #

ocompareLength :: Integral i => FocusList a -> i -> Ordering #

otraverse_ :: Applicative f => (Element (FocusList a) -> f b) -> FocusList a -> f () #

ofor_ :: Applicative f => FocusList a -> (Element (FocusList a) -> f b) -> f () #

omapM_ :: Applicative m => (Element (FocusList a) -> m ()) -> FocusList a -> m () #

oforM_ :: Applicative m => FocusList a -> (Element (FocusList a) -> m ()) -> m () #

ofoldlM :: Monad m => (a0 -> Element (FocusList a) -> m a0) -> a0 -> FocusList a -> m a0 #

ofoldMap1Ex :: Semigroup m => (Element (FocusList a) -> m) -> FocusList a -> m #

ofoldr1Ex :: (Element (FocusList a) -> Element (FocusList a) -> Element (FocusList a)) -> FocusList a -> Element (FocusList a) #

ofoldl1Ex' :: (Element (FocusList a) -> Element (FocusList a) -> Element (FocusList a)) -> FocusList a -> Element (FocusList a) #

headEx :: FocusList a -> Element (FocusList a) #

lastEx :: FocusList a -> Element (FocusList a) #

unsafeHead :: FocusList a -> Element (FocusList a) #

unsafeLast :: FocusList a -> Element (FocusList a) #

maximumByEx :: (Element (FocusList a) -> Element (FocusList a) -> Ordering) -> FocusList a -> Element (FocusList a) #

minimumByEx :: (Element (FocusList a) -> Element (FocusList a) -> Ordering) -> FocusList a -> Element (FocusList a) #

oelem :: Element (FocusList a) -> FocusList a -> Bool #

onotElem :: Element (FocusList a) -> FocusList a -> Bool #

MonoTraversable (FocusList a) Source # 
Instance details

Defined in Data.FocusList

Methods

otraverse :: Applicative f => (Element (FocusList a) -> f (Element (FocusList a))) -> FocusList a -> f (FocusList a) #

omapM :: Applicative m => (Element (FocusList a) -> m (Element (FocusList a))) -> FocusList a -> m (FocusList a) #

GrowingAppend (FocusList a) Source # 
Instance details

Defined in Data.FocusList

type Rep (FocusList a) Source # 
Instance details

Defined in Data.FocusList

type Rep (FocusList a) = D1 (MetaData "FocusList" "Data.FocusList" "focuslist-0.1.0.2-BeuRU3jZJpbDsW21V3d6wR" False) (C1 (MetaCons "FocusList" PrefixI True) (S1 (MetaSel (Just "focusListFocus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Focus) :*: S1 (MetaSel (Just "focusList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq a))))
type Index (FocusList a) Source # 
Instance details

Defined in Data.FocusList

type Index (FocusList a) = Int
type Element (FocusList a) Source # 
Instance details

Defined in Data.FocusList

type Element (FocusList a) = a

Conversions

fromListFL :: Focus -> [a] -> Maybe (FocusList a) Source #

Safely create a FocusList from a list.

>>> fromListFL (Focus 1) ["cat","dog","goat"]
Just (FocusList (Focus 1) ["cat","dog","goat"])
>>> fromListFL NoFocus []
Just (FocusList NoFocus [])

If the Focus is out of range for the list, then Nothing will be returned.

>>> fromListFL (Focus (-1)) ["cat","dog","goat"]
Nothing
>>> fromListFL (Focus 3) ["cat","dog","goat"]
Nothing
>>> fromListFL NoFocus ["cat","dog","goat"]
Nothing

complexity: O(n) where n is the length of the input list.

fromFoldableFL :: Foldable f => Focus -> f a -> Maybe (FocusList a) Source #

Create a FocusList from any Foldable container.

This just calls toList on the Foldable, and then passes the result to fromListFL.

fromFoldableFL foc (foldable :: Data.Sequence.Seq Int) == fromListFL foc (toList foldable)

complexity: O(n) where n is the length of the Foldable

toSeqFL :: FocusList a -> Seq a Source #

Get the underlying Seq in a FocusList.

complexity: O(1)

Query

lengthFL :: FocusList a -> Int Source #

Return the length of a FocusList.

>>> let Just fl = fromListFL (Focus 2) ["hello", "bye", "parrot"]
>>> lengthFL fl
3

complexity: O(1)

isEmptyFL :: FocusList a -> Bool Source #

Return True if the FocusList is empty.

>>> isEmptyFL emptyFL
True
>>> isEmptyFL $ singletonFL "hello"
False

Any FocusList with a Focus should never be empty.

hasFocusFL fl ==> not (isEmptyFL fl)

The opposite is also true.

complexity: O(1)

getFocusItemFL :: FocusList a -> Maybe a Source #

Get the item the FocusList is focusing on. Return Nothing if the FocusList is empty.

>>> let Just fl = fromListFL (Focus 0) ['a'..'c']
>>> getFocusItemFL fl
Just 'a'
>>> getFocusItemFL emptyFL
Nothing

This will always return Just if there is a Focus.

hasFocusFL fl ==> isJust (getFocusItemFL fl)

complexity: O(log(min(i, n - i))) where i is the Focus, and n is the length of the FocusList.

lookupFL Source #

Arguments

:: Int

Index to lookup.

-> FocusList a 
-> Maybe a 

Lookup the element at the specified index, counting from 0.

>>> let Just fl = fromListFL (Focus 0) ['a'..'c']
>>> lookupFL 0 fl
Just 'a'

Returns Nothing if the index is out of bounds.

>>> let Just fl = fromListFL (Focus 0) ['a'..'c']
>>> lookupFL 100 fl
Nothing
>>> lookupFL (-1) fl
Nothing

Always returns Nothing if the FocusList is empty.

lookupFL i emptyFL == Nothing

complexity: O(log(min(i, n - i))) where i is the index you want to look up, and n is the length of the FocusList.

indexOfFL :: Eq a => a -> FocusList a -> Maybe Int Source #

Find the index of the first element in the FocusList.

>>> let Just fl = fromListFL (Focus 1) ["hello", "bye", "tree"]
>>> indexOfFL "hello" fl
Just 0

If more than one element exists, then return the index of the first one.

>>> let Just fl = fromListFL (Focus 1) ["dog", "cat", "cat"]
>>> indexOfFL "cat" fl
Just 1

If the element doesn't exist, then return Nothing

>>> let Just fl = fromListFL (Focus 1) ["foo", "bar", "baz"]
>>> indexOfFL "hogehoge" fl
Nothing

findFL :: (a -> Bool) -> FocusList a -> Maybe a Source #

Find a value in a FocusList. Similar to Data.List.find.

>>> let Just fl = fromListFL (Focus 1) ["hello", "bye", "tree"]
>>> findFL (\a -> a == "hello") fl
Just "hello"

This will only find the first value.

>>> let Just fl = fromListFL (Focus 0) ["hello", "bye", "bye"]
>>> findFL (\a -> a == "bye") fl
Just "bye"

If no values match the comparison, this will return Nothing.

>>> let Just fl = fromListFL (Focus 1) ["hello", "bye", "parrot"]
>>> findFL (\a -> a == "ball") fl
Nothing

complexity: O(n) where n is the length of the FocusList.

Query Focus

hasFocusFL :: FocusList a -> Bool Source #

Return True if the Focus in a FocusList exists.

Return False if the Focus in a FocusList is NoFocus.

>>> hasFocusFL $ singletonFL "hello"
True
>>> hasFocusFL emptyFL
False

complexity: O(1)

getFocusFL :: FocusList a -> Focus Source #

Get the Focus from a FocusList.

>>> getFocusFL $ singletonFL "hello"
Focus 0
>>> let Just fl = fromListFL (Focus 3) [0..9]
>>> getFocusFL fl
Focus 3
>>> getFocusFL emptyFL
NoFocus

complexity: O(1)

Manipulate

prependFL :: a -> FocusList a -> FocusList a Source #

Prepend a value to a FocusList.

This can be thought of as a "cons" operation.

>>> prependFL "hello" emptyFL
FocusList (Focus 0) ["hello"]

The focus will be updated when prepending:

>>> prependFL "bye" (singletonFL "hello")
FocusList (Focus 1) ["bye","hello"]

Prepending to a FocusList will always update the Focus:

getFocusFL fl < getFocusFL (prependFL a fl)

complexity: O(1)

appendFL :: FocusList a -> a -> FocusList a Source #

Append a value to the end of a FocusList.

This can be thought of as a "snoc" operation.

>>> appendFL emptyFL "hello"
FocusList (Focus 0) ["hello"]
>>> appendFL (singletonFL "hello") "bye"
FocusList (Focus 0) ["hello","bye"]

Appending a value to an empty FocusList is the same as using singletonFL.

appendFL emptyFL a == singletonFL a

complexity: O(log n) where n is the length of the FocusList.

appendSetFocusFL :: FocusList a -> a -> FocusList a Source #

A combination of appendFL and setFocusFL.

>>> let Just fl = fromListFL (Focus 1) ["hello", "bye", "tree"]
>>> appendSetFocusFL fl "pie"
FocusList (Focus 3) ["hello","bye","tree","pie"]

The Focus will always be updated after calling appendSetFocusFL.

getFocusFL (appendSetFocusFL fl a) > getFocusFL fl

complexity: O(log n) where n is the length of the FocusList.

insertFL Source #

Arguments

:: Int

The index at which to insert the new element.

-> a

The new element.

-> FocusList a 
-> FocusList a 

Insert a new value into the FocusList. The Focus of the list is changed appropriately.

Inserting an element into an empty FocusList will set the Focus on that element.

>>> insertFL 0 "hello" emptyFL
FocusList (Focus 0) ["hello"]

The Focus will not be changed if you insert a new element after the current Focus.

>>> insertFL 1 "hello" (singletonFL "bye")
FocusList (Focus 0) ["bye","hello"]

The Focus will be bumped up by one if you insert a new element before the current Focus.

>>> insertFL 0 "hello" (singletonFL "bye")
FocusList (Focus 1) ["hello","bye"]

Behaves like Data.Sequence.insertAt. If the index is out of bounds, it will be inserted at the nearest available index

>>> insertFL 100 "hello" emptyFL
FocusList (Focus 0) ["hello"]
>>> insertFL 100 "bye" (singletonFL "hello")
FocusList (Focus 0) ["hello","bye"]
>>> insertFL (-1) "bye" (singletonFL "hello")
FocusList (Focus 1) ["bye","hello"]

complexity: O(log(min(i, n - i))) where i is the index you want to insert at, and n is the length of the FocusList.

removeFL Source #

Arguments

:: Int

Index of the element to remove from the FocusList.

-> FocusList a

The FocusList to remove an element from.

-> Maybe (FocusList a) 

Remove an element from a FocusList.

If the element to remove is not the Focus, then update the Focus accordingly.

For example, if the Focus is on index 1, and we have removed index 2, then the focus is not affected, so it is not changed.

>>> let focusList = unsafeFromListFL (Focus 1) ["cat","goat","dog","hello"]
>>> removeFL 2 focusList
Just (FocusList (Focus 1) ["cat","goat","hello"])

If the Focus is on index 2 and we have removed index 1, then the Focus will be moved back one element to set to index 1.

>>> let focusList = unsafeFromListFL (Focus 2) ["cat","goat","dog","hello"]
>>> removeFL 1 focusList
Just (FocusList (Focus 1) ["cat","dog","hello"])

If we remove the Focus, then the next item is set to have the Focus.

>>> let focusList = unsafeFromListFL (Focus 0) ["cat","goat","dog","hello"]
>>> removeFL 0 focusList
Just (FocusList (Focus 0) ["goat","dog","hello"])

If the element to remove is the only element in the list, then the Focus will be set to NoFocus.

>>> let focusList = unsafeFromListFL (Focus 0) ["hello"]
>>> removeFL 0 focusList
Just (FocusList NoFocus [])

If the Int for the index to remove is either less than 0 or greater then the length of the list, then Nothing is returned.

>>> let focusList = unsafeFromListFL (Focus 0) ["hello"]
>>> removeFL (-1) focusList
Nothing
>>> let focusList = unsafeFromListFL (Focus 1) ["hello","bye","cat"]
>>> removeFL 3 focusList
Nothing

If the FocusList passed in is Empty, then Nothing is returned.

>>> removeFL 0 emptyFL
Nothing

complexity: O(log(min(i, n - i))) where i is index of the element to remove, and n is the length of the FocusList.

deleteFL :: forall a. Eq a => a -> FocusList a -> FocusList a Source #

Delete an element from a FocusList.

>>> let Just fl = fromListFL (Focus 0) ["hello", "bye", "tree"]
>>> deleteFL "bye" fl
FocusList (Focus 0) ["hello","tree"]

The focus will be updated if an item before it is deleted.

>>> let Just fl = fromListFL (Focus 1) ["hello", "bye", "tree"]
>>> deleteFL "hello" fl
FocusList (Focus 0) ["bye","tree"]

If there are multiple matching elements in the FocusList, remove them all.

>>> let Just fl = fromListFL (Focus 0) ["hello", "bye", "bye"]
>>> deleteFL "bye" fl
FocusList (Focus 0) ["hello"]

If there are no matching elements, return the original FocusList.

>>> let Just fl = fromListFL (Focus 2) ["hello", "good", "bye"]
>>> deleteFL "frog" fl
FocusList (Focus 2) ["hello","good","bye"]

moveFromToFL Source #

Arguments

:: Show a 
=> Int

Index of the item to move.

-> Int

New index for the item.

-> FocusList a 
-> Maybe (FocusList a) 

Move an existing item in a FocusList to a new index.

The Focus gets updated appropriately when moving items.

>>> let Just fl = fromListFL (Focus 1) ["hello", "bye", "parrot"]
>>> moveFromToFL 0 1 fl
Just (FocusList (Focus 0) ["bye","hello","parrot"])

The Focus may not get updated if it is not involved.

>>> let Just fl = fromListFL (Focus 0) ["hello", "bye", "parrot"]
>>> moveFromToFL 1 2 fl
Just (FocusList (Focus 0) ["hello","parrot","bye"])

If the element with the Focus is moved, then the Focus will be updated appropriately.

>>> let Just fl = fromListFL (Focus 2) ["hello", "bye", "parrot"]
>>> moveFromToFL 2 0 fl
Just (FocusList (Focus 0) ["parrot","hello","bye"])

If the index of the item to move is out bounds, then Nothing will be returned.

>>> let Just fl = fromListFL (Focus 2) ["hello", "bye", "parrot"]
>>> moveFromToFL 3 0 fl
Nothing

If the new index is out of bounds, then Nothing wil be returned.

>>> let Just fl = fromListFL (Focus 2) ["hello", "bye", "parrot"]
>>> moveFromToFL 1 (-1) fl
Nothing

complexity: O(log n) where n is the length of the FocusList.

intersperseFL :: a -> FocusList a -> FocusList a Source #

Intersperse a new element between existing elements in the FocusList.

>>> let Just fl = fromListFL (Focus 0) ["hello", "bye", "cat"]
>>> intersperseFL "foo" fl
FocusList (Focus 0) ["hello","foo","bye","foo","cat"]

The Focus is updated accordingly.

>>> let Just fl = fromListFL (Focus 2) ["hello", "bye", "cat", "goat"]
>>> intersperseFL "foo" fl
FocusList (Focus 4) ["hello","foo","bye","foo","cat","foo","goat"]

The item with the Focus should never change after calling intersperseFL.

getFocusItemFL (fl :: FocusList Int) == getFocusItemFL (intersperseFL a fl)

intersperseFL should not have any effect on a FocusList with less than two items.

emptyFL == intersperseFL x emptyFL
singletonFL a == intersperseFL x (singletonFL a)

complexity: O(n) where n is the length of the FocusList.

reverseFL :: FocusList a -> FocusList a Source #

Reverse a FocusList. The Focus is updated accordingly.

>>> let Just fl = fromListFL (Focus 0) ["hello", "bye", "cat"]
>>> reverseFL fl
FocusList (Focus 2) ["cat","bye","hello"]
>>> let Just fl = fromListFL (Focus 2) ["hello", "bye", "cat", "goat"]
>>> reverseFL fl
FocusList (Focus 1) ["goat","cat","bye","hello"]

The item with the Focus should never change after calling intersperseFL.

getFocusItemFL (fl :: FocusList Int) == getFocusItemFL (reverseFL fl)

Reversing twice should not change anything.

(fl :: FocusList Int) == reverseFL (reverseFL fl)

Reversing empty lists and single lists should not do anything.

emptyFL == reverseFL emptyFL
singletonFL a == reverseFL (singletonFL a)

complexity: O(n) where n is the length of the FocusList.

Manipulate Focus

setFocusFL :: Int -> FocusList a -> Maybe (FocusList a) Source #

Set the Focus for a FocusList.

This is just like updateFocusFL, but doesn't return the newly focused item.

setFocusFL i fl == fmap snd (updateFocusFL i fl)

complexity: O(1)

updateFocusFL Source #

Arguments

:: Int

The new index to put the Focus on.

-> FocusList a 
-> Maybe (a, FocusList a)

A tuple of the new element that gets the Focus, and the new FocusList.

Update the Focus for a FocusList and get the new focused element.

>>> updateFocusFL 1 =<< fromListFL (Focus 2) ["hello","bye","dog","cat"]
Just ("bye",FocusList (Focus 1) ["hello","bye","dog","cat"])

If the FocusList is empty, then return Nothing.

>>> updateFocusFL 1 emptyFL
Nothing

If the new focus is less than 0, or greater than or equal to the length of the FocusList, then return Nothing.

>>> updateFocusFL (-1) =<< fromListFL (Focus 2) ["hello","bye","dog","cat"]
Nothing
>>> updateFocusFL 4 =<< fromListFL (Focus 2) ["hello","bye","dog","cat"]
Nothing

complexity: O(log(min(i, n - i))) where i is the new index to put the Focus on, and n -- is the length of the FocusList.

Sort

sortByFL Source #

Arguments

:: (a -> a -> Ordering)

The function to use to compare elements.

-> FocusList a 
-> FocusList a 

Sort a FocusList.

The Focus will stay with the element that has the Focus.

>>> let Just fl = fromListFL (Focus 2) ["b", "c", "a"]
>>> sortByFL compare fl
FocusList (Focus 0) ["a","b","c"]

Nothing will happen if you try to sort an empty FocusList, or a FocusList with only one element.

emptyFL == sortByFL compare emptyFL
singletonFL a == sortByFL compare (singletonFL a)

The element with the Focus should be the same before and after sorting.

getFocusItemFL (fl :: FocusList Int) == getFocusItemFL (sortByFL compare fl)

Sorting a FocusList and getting the underlying Seq should be the same as getting the underlying Seq and then sorting it.

toSeqFL (sortByFL compare (fl :: FocusList Int)) == sortBy compare (toSeqFL fl)

WARNING: The computational complexity for this is very bad. It should be able to be done in O(n * log n), but the current implementation is O(n^2) (or worse), where n is the length of the FocusList. This function could be implemented the same way Data.Sequence.sortBy is implemented. However, a small change needs to be added to that function to keep track of the Focus in the FocusList and make sure it gets updated properly. If you're interested in fixing this, please send a PR.

Construction

emptyFL :: FocusList a Source #

Create an empty FocusList without a Focus.

>>> emptyFL
FocusList NoFocus []

complexity: O(1)

singletonFL :: a -> FocusList a Source #

Create a FocusList with a single element.

>>> singletonFL "hello"
FocusList (Focus 0) ["hello"]

complexity: O(1)

Unsafe Functions

unsafeFromListFL :: Focus -> [a] -> FocusList a Source #

Unsafely create a FocusList. This does not check that the focus actually exists in the list. This is an internal function and should generally not be used. It is only safe to use if you ALREADY know the Focus is within the list.

Instead, you should generally use fromListFL.

The following is an example of using unsafeFromListFL correctly.

>>> unsafeFromListFL (Focus 1) [0..2]
FocusList (Focus 1) [0,1,2]
>>> unsafeFromListFL NoFocus []
FocusList NoFocus []

unsafeFromListFL can also be used uncorrectly. The following is an example of unsafeFromListFL allowing you to create a FocusList that does not pass invariantFL.

>>> unsafeFromListFL (Focus 100) [0..2]
FocusList (Focus 100) [0,1,2]

If fromListFL returns a Just FocusList, then unsafeFromListFL should return the same FocusList.

complexity: O(n) where n is the length of the input list.

unsafeGetFocusFL :: FocusList a -> Int Source #

Unsafely get the Focus from a FocusList. If the Focus is NoFocus, this function returns error.

This function is only safe if you already have knowledge that the FocusList has a Focus.

Generally, getFocusFL should be used instead of this function.

>>> let Just fl = fromListFL (Focus 1) [0..9]
>>> unsafeGetFocusFL fl
1
>>> unsafeGetFocusFL emptyFL
*** Exception: ...
...

complexity: O(1)

unsafeGetFocusItemFL :: FocusList a -> a Source #

Unsafely get the value of the Focus from a FocusList. If the Focus is NoFocus, this function returns error.

This function is only safe if you already have knowledge that the FocusList has a Focus.

Generally, getFocusItemFL should be used instead of this function.

>>> let Just fl = fromListFL (Focus 0) ['a'..'c']
>>> unsafeGetFocusItemFL fl
'a'
>>> unsafeGetFocusFL emptyFL
*** Exception: ...
...

complexity: O(log(min(i, n - i))) where i is the Focus, and n is the length of the FocusList.

Invariants

invariantFL :: FocusList a -> Bool Source #

This is an invariant that the FocusList must always protect.

The functions in this module should generally protect this invariant. If they do not, it is generally a bug.

The invariants are as follows:

complexity: O(log n), where n is the length of the FocusList.

Testing

genValidFL :: forall a. Gen a -> Gen (FocusList a) Source #

Given a Gen for a, generate a valid FocusList.

Optics

These optics allow you to get/set the internal state of a FocusList. You should make sure not to directly set the internal state of a FocusList unless you are sure that the invariants for the FocusList are protected. See invariantFL.

lensFocusList :: forall a a. Lens (FocusList a) (FocusList a) (Seq a) (Seq a) Source #

Focus

data Focus Source #

A Focus for the FocusList.

The Focus is either NoFocus (if the Focuslist is empty), or Focus Int to represent focusing on a specific element of the FocusList.

Constructors

Focus !Int 
NoFocus 
Instances
Eq Focus Source # 
Instance details

Defined in Data.FocusList

Methods

(==) :: Focus -> Focus -> Bool #

(/=) :: Focus -> Focus -> Bool #

Ord Focus Source #

NoFocus is always less than Focus.

NoFocus < Focus a

The ordering of Focus depends on the ordering of the integer contained inside.

(a < b) ==> (Focus a < Focus b)
Instance details

Defined in Data.FocusList

Methods

compare :: Focus -> Focus -> Ordering #

(<) :: Focus -> Focus -> Bool #

(<=) :: Focus -> Focus -> Bool #

(>) :: Focus -> Focus -> Bool #

(>=) :: Focus -> Focus -> Bool #

max :: Focus -> Focus -> Focus #

min :: Focus -> Focus -> Focus #

Read Focus Source # 
Instance details

Defined in Data.FocusList

Show Focus Source # 
Instance details

Defined in Data.FocusList

Methods

showsPrec :: Int -> Focus -> ShowS #

show :: Focus -> String #

showList :: [Focus] -> ShowS #

Generic Focus Source # 
Instance details

Defined in Data.FocusList

Associated Types

type Rep Focus :: Type -> Type #

Methods

from :: Focus -> Rep Focus x #

to :: Rep Focus x -> Focus #

Arbitrary Focus Source # 
Instance details

Defined in Data.FocusList

Methods

arbitrary :: Gen Focus #

shrink :: Focus -> [Focus] #

CoArbitrary Focus Source # 
Instance details

Defined in Data.FocusList

Methods

coarbitrary :: Focus -> Gen b -> Gen b #

type Rep Focus Source # 
Instance details

Defined in Data.FocusList

type Rep Focus = D1 (MetaData "Focus" "Data.FocusList" "focuslist-0.1.0.2-BeuRU3jZJpbDsW21V3d6wR" False) (C1 (MetaCons "Focus" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "NoFocus" PrefixI False) (U1 :: Type -> Type))

hasFocus :: Focus -> Bool Source #

Returns True if a Focus exists, and False if not.

>>> hasFocus (Focus 0)
True
>>> hasFocus NoFocus
False

complexity: O(1)

getFocus :: Focus -> Maybe Int Source #

Get the focus index from a Focus.

>>> getFocus (Focus 3)
Just 3
>>> getFocus NoFocus
Nothing

complexity: O(1)

maybeToFocus :: Maybe Int -> Focus Source #

Convert a Maybe Int to a Focus.

>>> maybeToFocus (Just 100)
Focus 100
>>> maybeToFocus Nothing
NoFocus

maybeToFocus and getFocus witness an isomorphism.

focus == maybeToFocus (getFocus focus)
maybeInt == getFocus (maybeToFocus maybeInt)

complexity: O(1)

foldFocus :: b -> (Int -> b) -> Focus -> b Source #

A fold function for Focus.

This is similar to maybe for Maybe.

>>> foldFocus "empty" (\i -> "focus at " <> show i) (Focus 3)
"focus at 3"
>>> foldFocus Nothing Just NoFocus
Nothing
foldFocus NoFocus Focus focus == focus

Optics

_Focus :: Prism' Focus Int Source #

A Prism' for focusing on the Focus constructor in a Focus data type.

_NoFocus :: Prism' Focus () Source #

A Prism' for focusing on the NoFocus constructor in a Focus data type.

Unsafe Functions

unsafeGetFocus :: Focus -> Int Source #

Unsafely get the focus index from a Focus.

Returns an error if NoFocus.

>>> unsafeGetFocus (Focus 50)
50
>>> unsafeGetFocus NoFocus
*** Exception: ...
...

complexity: O(1)