termonad-0.2.0.0: Terminal emulator configurable in Haskell

Safe HaskellNone
LanguageHaskell2010

Termonad.FocusList

Synopsis

Documentation

>>> :set -XFlexibleContexts
>>> :set -XScopedTypeVariables

data Focus Source #

Constructors

Focus !Int 
NoFocus 
Instances
Eq Focus Source # 
Instance details

Defined in Termonad.FocusList

Methods

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

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

Ord Focus Source #

NoFocus is always less than Focus.

NoFocus < Focus a
Instance details

Defined in Termonad.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 Termonad.FocusList

Show Focus Source # 
Instance details

Defined in Termonad.FocusList

Methods

showsPrec :: Int -> Focus -> ShowS #

show :: Focus -> String #

showList :: [Focus] -> ShowS #

Generic Focus Source # 
Instance details

Defined in Termonad.FocusList

Associated Types

type Rep Focus :: * -> * #

Methods

from :: Focus -> Rep Focus x #

to :: Rep Focus x -> Focus #

CoArbitrary Focus Source # 
Instance details

Defined in Termonad.FocusList

Methods

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

type Rep Focus Source # 
Instance details

Defined in Termonad.FocusList

type Rep Focus = D1 (MetaData "Focus" "Termonad.FocusList" "termonad-0.2.0.0-R24uHZ2NNP75I6Ub7xf1G" False) (C1 (MetaCons "Focus" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "NoFocus" PrefixI False) (U1 :: * -> *))

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

data FocusList a Source #

Constructors

FocusList 
Instances
Functor FocusList Source # 
Instance details

Defined in Termonad.FocusList

Methods

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

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

Foldable FocusList Source # 
Instance details

Defined in Termonad.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 Termonad.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 Termonad.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 Termonad.FocusList

Methods

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

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

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

Defined in Termonad.FocusList

Generic (FocusList a) Source # 
Instance details

Defined in Termonad.FocusList

Associated Types

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

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 Termonad.FocusList

Methods

arbitrary :: Gen (FocusList a) #

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

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

Defined in Termonad.FocusList

Methods

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

MonoTraversable (FocusList a) Source # 
Instance details

Defined in Termonad.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) #

MonoFoldable (FocusList a) Source # 
Instance details

Defined in Termonad.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 #

MonoFunctor (FocusList a) Source # 
Instance details

Defined in Termonad.FocusList

Methods

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

type Rep (FocusList a) Source # 
Instance details

Defined in Termonad.FocusList

type Rep (FocusList a) = D1 (MetaData "FocusList" "Termonad.FocusList" "termonad-0.2.0.0-R24uHZ2NNP75I6Ub7xf1G" False) (C1 (MetaCons "FocusList" PrefixI True) (S1 (MetaSel (Just "focusListFocus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Focus) :*: (S1 (MetaSel (Just "focusListLen") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "focusList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (IntMap a)))))
type Element (FocusList a) Source # 
Instance details

Defined in Termonad.FocusList

type Element (FocusList a) = a

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

invariantFL :: FocusList a -> Bool Source #

This is an invariant that the FocusList must always protect.

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

Unsafely create a FocusList. This does not check that the focus actually exists in the list.

>>> let fl = unsafeFLFromList (Focus 1) [0..2]
>>> debugFL fl
"FocusList {focusListFocus = Focus 1, focusListLen = 3, focusList = fromList [(0,0),(1,1),(2,2)]}"
>>> let fl = unsafeFLFromList NoFocus []
>>> debugFL fl
"FocusList {focusListFocus = NoFocus, focusListLen = 0, focusList = fromList []}"

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

Safely create a FocusList from a list.

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

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

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

singletonFL :: a -> FocusList a Source #

Create a FocusList with a single element.

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

emptyFL :: FocusList a Source #

Create an empty FocusList without a Focus.

>>> emptyFL
FocusList NoFocus []

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.

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

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

A combination of appendFL and setFocusFL.

>>> let Just fl = flFromList (Focus 1) ["hello", "bye", "tree"]
>>> appendSetFocusFL fl "pie"
FocusList (Focus 3) ["hello","bye","tree","pie"]
(appendSetFocusFL fl a) ^. lensFocusListFocus /= fl ^. lensFocusListFocus

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:

(fl ^. lensFocusListFocus) < (prependFL a fl ^. lensFocusListFocus)

unsafeGetFLFocus :: FocusList a -> Int Source #

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

unsafeGetFLFocusItem :: FocusList a -> a Source #

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

unsafeInsertNewFL :: Int -> a -> FocusList a -> FocusList a Source #

Unsafely insert a new a in a FocusList. This sets the Int value to a. The length of the FocusList will be increased by 1. The FocusLists Focus is not changed.

If there is some value in the FocusList already at the Int, then it will be overwritten. Also, the Int is not checked to make sure it is above 0.

This function is meant to be used after unsafeShiftUpFrom.

>>> let fl = unsafeShiftUpFrom 2 $ unsafeFLFromList (Focus 1) [0,1,200]
>>> debugFL $ unsafeInsertNewFL 2 100 fl
"FocusList {focusListFocus = Focus 1, focusListLen = 4, focusList = fromList [(0,0),(1,1),(2,100),(3,200)]}"
>>> let fl = unsafeFLFromList NoFocus []
>>> debugFL $ unsafeInsertNewFL 0 100 fl
"FocusList {focusListFocus = NoFocus, focusListLen = 1, focusList = fromList [(0,100)]}"

unsafeShiftUpFrom :: forall a. Int -> FocusList a -> FocusList a Source #

This unsafely shifts all values up in a FocusList starting at a given index. It also updates the Focus of the FocusList if it has been shifted. This does not change the length of the FocusList.

It does not check that the Int is greater than 0. It also does not check that there is a Focus.

EXAMPLES

Expand
>>> let fl = unsafeShiftUpFrom 2 $ unsafeFLFromList (Focus 1) [0,1,200]
>>> debugFL fl
"FocusList {focusListFocus = Focus 1, focusListLen = 3, focusList = fromList [(0,0),(1,1),(3,200)]}"
>>> let fl = unsafeShiftUpFrom 1 $ unsafeFLFromList (Focus 1) [0,1,200]
>>> debugFL fl
"FocusList {focusListFocus = Focus 2, focusListLen = 3, focusList = fromList [(0,0),(2,1),(3,200)]}"
>>> let fl = unsafeShiftUpFrom 0 $ unsafeFLFromList (Focus 1) [0,1,200]
>>> debugFL fl
"FocusList {focusListFocus = Focus 2, focusListLen = 3, focusList = fromList [(1,0),(2,1),(3,200)]}"
>>> let fl = unsafeShiftUpFrom 0 $ unsafeFLFromList (Focus 1) [0,1,200]
>>> debugFL fl
"FocusList {focusListFocus = Focus 2, focusListLen = 3, focusList = fromList [(1,0),(2,1),(3,200)]}"

unsafeLookup :: Int -> IntMap a -> a Source #

This is an unsafe lookup function. This assumes that the Int exists in the IntMap.

insertFL Source #

Arguments

:: Int

The index at which to insert the value.

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

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

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

This returns Nothing if the index at which to insert the new value is either less than 0 or greater than the length of the list.

>>> insertFL 100 "hello" emptyFL
Nothing
>>> insertFL 100 "bye" (singletonFL "hello")
Nothing
>>> insertFL (-1) "bye" (singletonFL "hello")
Nothing

unsafeRemove :: Int -> FocusList a -> FocusList a Source #

Unsafely remove a value from a FocusList. It effectively leaves a hole inside the FocusList. It updates the length of the FocusList.

This function does not check that a value actually exists in the FocusList. It also does not update the Focus.

This function does update the length of the FocusList.

>>> debugFL $ unsafeRemove 1 $ unsafeFLFromList (Focus 0) [0..2]
"FocusList {focusListFocus = Focus 0, focusListLen = 2, focusList = fromList [(0,0),(2,2)]}"
>>> debugFL $ unsafeRemove 0 $ unsafeFLFromList (Focus 0) [0..2]
"FocusList {focusListFocus = Focus 0, focusListLen = 2, focusList = fromList [(1,1),(2,2)]}"

Trying to remove the last element is completely safe (unless, of course, it is the Focus):

>>> debugFL $ unsafeRemove 2 $ unsafeFLFromList (Focus 2) [0..2]
"FocusList {focusListFocus = Focus 2, focusListLen = 2, focusList = fromList [(0,0),(1,1)]}"

If this function is passed an empty FocusList, it will make the length -1.

>>> debugFL $ unsafeRemove 0 emptyFL
"FocusList {focusListFocus = NoFocus, focusListLen = -1, focusList = fromList []}"

unsafeShiftDownFrom :: forall a. Int -> FocusList a -> FocusList a Source #

This shifts all the values down in a FocusList starting at a given index. It does not change the Focus of the FocusList. It does not change the length of the FocusList.

It does not check that shifting elements down will not overwrite other elements. This function is meant to be called after unsafeRemove.

>>> let fl = unsafeRemove 1 $ unsafeFLFromList (Focus 0) [0..2]
>>> debugFL $ unsafeShiftDownFrom 1 fl
"FocusList {focusListFocus = Focus 0, focusListLen = 2, focusList = fromList [(0,0),(1,2)]}"
>>> let fl = unsafeRemove 0 $ unsafeFLFromList (Focus 0) [0..2]
>>> debugFL $ unsafeShiftDownFrom 0 fl
"FocusList {focusListFocus = Focus 0, focusListLen = 2, focusList = fromList [(0,1),(1,2)]}"

Trying to shift down from the last element after it has been removed is a no-op:

>>> let fl = unsafeRemove 2 $ unsafeFLFromList (Focus 0) [0..2]
>>> debugFL $ unsafeShiftDownFrom 2 fl
"FocusList {focusListFocus = Focus 0, focusListLen = 2, focusList = fromList [(0,0),(1,1)]}"

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 = unsafeFLFromList (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 = unsafeFLFromList (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 = unsafeFLFromList (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 = unsafeFLFromList (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 = unsafeFLFromList (Focus 0) ["hello"]
>>> removeFL (-1) focusList
Nothing
>>> let focusList = unsafeFLFromList (Focus 1) ["hello","bye","cat"]
>>> removeFL 3 focusList
Nothing

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

>>> removeFL 0 emptyFL
Nothing

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

Find the index of the first element in the FocusList.

>>> let Just fl = flFromList (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 = flFromList (Focus 1) ["dog", "cat", "cat"]
>>> indexOfFL "cat" fl
Just 1

If the element doesn't exist, then return Nothing

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

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

Delete an element from a FocusList.

>>> let Just fl = flFromList (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 = flFromList (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 = flFromList (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 = flFromList (Focus 2) ["hello", "good", "bye"]
>>> deleteFL "frog" fl
FocusList (Focus 2) ["hello","good","bye"]

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

Set the Focus for a FocusList.

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

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

updateFocusFL :: Int -> FocusList a -> Maybe (a, FocusList a) Source #

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

>>> updateFocusFL 1 =<< flFromList (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) =<< flFromList (Focus 2) ["hello","bye","dog","cat"]
Nothing
>>> updateFocusFL 4 =<< flFromList (Focus 2) ["hello","bye","dog","cat"]
Nothing

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

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

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

This will only find the first value.

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

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

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

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 = flFromList (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 = flFromList (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 = flFromList (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 = flFromList (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 = flFromList (Focus 2) ["hello", "bye", "parrot"]
>>> moveFromToFL 1 (-1) fl
Nothing