list-zipper-0.0.3: A list zipper

Safe HaskellNone
LanguageHaskell2010

Data.ListZipper

Documentation

data ListZipper a Source #

Constructors

ListZipper [a] a [a] 
Instances
Functor ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

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

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

Applicative ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

pure :: a -> ListZipper a #

(<*>) :: ListZipper (a -> b) -> ListZipper a -> ListZipper b #

liftA2 :: (a -> b -> c) -> ListZipper a -> ListZipper b -> ListZipper c #

(*>) :: ListZipper a -> ListZipper b -> ListZipper b #

(<*) :: ListZipper a -> ListZipper b -> ListZipper a #

Foldable ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

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

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

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

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

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

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

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

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

toList :: ListZipper a -> [a] #

null :: ListZipper a -> Bool #

length :: ListZipper a -> Int #

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

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

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

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

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

Traversable ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

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

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

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

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

Eq1 ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

liftEq :: (a -> b -> Bool) -> ListZipper a -> ListZipper b -> Bool #

Show1 ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ListZipper a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ListZipper a] -> ShowS #

Comonad ListZipper Source # 
Instance details

Defined in Data.ListZipper

Apply ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

(<.>) :: ListZipper (a -> b) -> ListZipper a -> ListZipper b #

(.>) :: ListZipper a -> ListZipper b -> ListZipper b #

(<.) :: ListZipper a -> ListZipper b -> ListZipper a #

liftF2 :: (a -> b -> c) -> ListZipper a -> ListZipper b -> ListZipper c #

Traversable1 ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

traverse1 :: Apply f => (a -> f b) -> ListZipper a -> f (ListZipper b) #

sequence1 :: Apply f => ListZipper (f b) -> f (ListZipper b) #

Foldable1 ListZipper Source # 
Instance details

Defined in Data.ListZipper

Methods

fold1 :: Semigroup m => ListZipper m -> m #

foldMap1 :: Semigroup m => (a -> m) -> ListZipper a -> m #

toNonEmpty :: ListZipper a -> NonEmpty a #

Extend ListZipper Source # 
Instance details

Defined in Data.ListZipper

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

Defined in Data.ListZipper

Methods

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

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

Ord a => Ord (ListZipper a) Source # 
Instance details

Defined in Data.ListZipper

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

Defined in Data.ListZipper

Semigroup a => Semigroup (ListZipper a) Source # 
Instance details

Defined in Data.ListZipper

Ixed (ListZipper a) Source # 
Instance details

Defined in Data.ListZipper

Reversing (ListZipper a) Source # 
Instance details

Defined in Data.ListZipper

Methods

reversing :: ListZipper a -> ListZipper a #

HasListZipper (ListZipper a) a Source # 
Instance details

Defined in Data.ListZipper

AsListZipper (ListZipper a) a Source # 
Instance details

Defined in Data.ListZipper

MonadReader (ListZipper x) (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

ask :: ListZipperOp x (ListZipper x) #

local :: (ListZipper x -> ListZipper x) -> ListZipperOp x a -> ListZipperOp x a #

reader :: (ListZipper x -> a) -> ListZipperOp x a #

MonadState (ListZipper x) (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

get :: ListZipperOp x (ListZipper x) #

put :: ListZipper x -> ListZipperOp x () #

state :: (ListZipper x -> (a, ListZipper x)) -> ListZipperOp x a #

Each (ListZipper a) (ListZipper a) a a Source # 
Instance details

Defined in Data.ListZipper

Methods

each :: Traversal (ListZipper a) (ListZipper a) a a #

type Index (ListZipper a) Source # 
Instance details

Defined in Data.ListZipper

type Index (ListZipper a) = Int
type IxValue (ListZipper a) Source # 
Instance details

Defined in Data.ListZipper

type IxValue (ListZipper a) = a

class AsListZipper z a | z -> a where Source #

Instances
AsListZipper (ListZipper a) a Source # 
Instance details

Defined in Data.ListZipper

class HasListZipper z a | z -> a where Source #

Minimal complete definition

listZipper

Instances
HasListZipper (ListZipper a) a Source # 
Instance details

Defined in Data.ListZipper

zipper0L :: a -> [a] -> ListZipper a Source #

zipper0R :: [a] -> a -> ListZipper a Source #

list :: ListZipper a -> [a] Source #

newtype ListZipperOp x a Source #

Constructors

ListZipperOp (ListZipper x -> Maybe (ListZipper x, a)) 
Instances
MonadError () (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

throwError :: () -> ListZipperOp x a #

catchError :: ListZipperOp x a -> (() -> ListZipperOp x a) -> ListZipperOp x a #

Monad (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

(>>=) :: ListZipperOp x a -> (a -> ListZipperOp x b) -> ListZipperOp x b #

(>>) :: ListZipperOp x a -> ListZipperOp x b -> ListZipperOp x b #

return :: a -> ListZipperOp x a #

fail :: String -> ListZipperOp x a #

Functor (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

fmap :: (a -> b) -> ListZipperOp x a -> ListZipperOp x b #

(<$) :: a -> ListZipperOp x b -> ListZipperOp x a #

MonadFix (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

mfix :: (a -> ListZipperOp x a) -> ListZipperOp x a #

MonadFail (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

fail :: String -> ListZipperOp x a #

Applicative (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

pure :: a -> ListZipperOp x a #

(<*>) :: ListZipperOp x (a -> b) -> ListZipperOp x a -> ListZipperOp x b #

liftA2 :: (a -> b -> c) -> ListZipperOp x a -> ListZipperOp x b -> ListZipperOp x c #

(*>) :: ListZipperOp x a -> ListZipperOp x b -> ListZipperOp x b #

(<*) :: ListZipperOp x a -> ListZipperOp x b -> ListZipperOp x a #

Alternative (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

empty :: ListZipperOp x a #

(<|>) :: ListZipperOp x a -> ListZipperOp x a -> ListZipperOp x a #

some :: ListZipperOp x a -> ListZipperOp x [a] #

many :: ListZipperOp x a -> ListZipperOp x [a] #

MonadPlus (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

mzero :: ListZipperOp x a #

mplus :: ListZipperOp x a -> ListZipperOp x a -> ListZipperOp x a #

Apply (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

(<.>) :: ListZipperOp x (a -> b) -> ListZipperOp x a -> ListZipperOp x b #

(.>) :: ListZipperOp x a -> ListZipperOp x b -> ListZipperOp x b #

(<.) :: ListZipperOp x a -> ListZipperOp x b -> ListZipperOp x a #

liftF2 :: (a -> b -> c) -> ListZipperOp x a -> ListZipperOp x b -> ListZipperOp x c #

Alt (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Bind (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

(>>-) :: ListZipperOp x a -> (a -> ListZipperOp x b) -> ListZipperOp x b #

join :: ListZipperOp x (ListZipperOp x a) -> ListZipperOp x a #

MonadReader (ListZipper x) (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

ask :: ListZipperOp x (ListZipper x) #

local :: (ListZipper x -> ListZipper x) -> ListZipperOp x a -> ListZipperOp x a #

reader :: (ListZipper x -> a) -> ListZipperOp x a #

MonadState (ListZipper x) (ListZipperOp x) Source # 
Instance details

Defined in Data.ListZipper

Methods

get :: ListZipperOp x (ListZipper x) #

put :: ListZipper x -> ListZipperOp x () #

state :: (ListZipper x -> (a, ListZipper x)) -> ListZipperOp x a #

Semigroup (ListZipperOp x y) Source # 
Instance details

Defined in Data.ListZipper

Methods

(<>) :: ListZipperOp x y -> ListZipperOp x y -> ListZipperOp x y #

sconcat :: NonEmpty (ListZipperOp x y) -> ListZipperOp x y #

stimes :: Integral b => b -> ListZipperOp x y -> ListZipperOp x y #

Monoid (ListZipperOp x y) Source # 
Instance details

Defined in Data.ListZipper

Wrapped (ListZipperOp x' a') Source # 
Instance details

Defined in Data.ListZipper

Associated Types

type Unwrapped (ListZipperOp x' a') :: Type #

Methods

_Wrapped' :: Iso' (ListZipperOp x' a') (Unwrapped (ListZipperOp x' a')) #

ListZipperOp x a ~ t => Rewrapped (ListZipperOp x' a') t Source # 
Instance details

Defined in Data.ListZipper

AsListZipperOp (ListZipperOp x y) x y Source # 
Instance details

Defined in Data.ListZipper

HasListZipperOp (ListZipperOp x y) x y Source # 
Instance details

Defined in Data.ListZipper

Methods

lo :: Lens' (ListZipperOp x y) (ListZipperOp x y) Source #

type Unwrapped (ListZipperOp x' a') Source # 
Instance details

Defined in Data.ListZipper

type Unwrapped (ListZipperOp x' a') = ListZipper x' -> Maybe (ListZipper x', a')

class HasListZipperOp lo x y | lo -> x y where Source #

Methods

lo :: Lens' lo (ListZipperOp x y) Source #

Instances
HasListZipperOp (ListZipperOp x y) x y Source # 
Instance details

Defined in Data.ListZipper

Methods

lo :: Lens' (ListZipperOp x y) (ListZipperOp x y) Source #

class AsListZipperOp t x y | t -> x y where Source #

Instances
AsListZipperOp (ListZipperOp x y) x y Source # 
Instance details

Defined in Data.ListZipper

opUntil :: ListZipperOp x () -> (x -> Bool) -> ListZipperOp x () Source #