cursor-0.3.2.0: Purely Functional Cursors
Safe HaskellNone
LanguageHaskell2010

Cursor.List.NonEmpty

Synopsis

Documentation

data NonEmptyCursor a b Source #

A 'nonempty list' cursor

Instances

Instances details
Functor (NonEmptyCursor a) Source # 
Instance details

Defined in Cursor.List.NonEmpty

Methods

fmap :: (a0 -> b) -> NonEmptyCursor a a0 -> NonEmptyCursor a b #

(<$) :: a0 -> NonEmptyCursor a b -> NonEmptyCursor a a0 #

(Eq b, Eq a) => Eq (NonEmptyCursor a b) Source # 
Instance details

Defined in Cursor.List.NonEmpty

(Show b, Show a) => Show (NonEmptyCursor a b) Source # 
Instance details

Defined in Cursor.List.NonEmpty

Generic (NonEmptyCursor a b) Source # 
Instance details

Defined in Cursor.List.NonEmpty

Associated Types

type Rep (NonEmptyCursor a b) :: Type -> Type #

Methods

from :: NonEmptyCursor a b -> Rep (NonEmptyCursor a b) x #

to :: Rep (NonEmptyCursor a b) x -> NonEmptyCursor a b #

(NFData a, NFData b) => NFData (NonEmptyCursor a b) Source # 
Instance details

Defined in Cursor.List.NonEmpty

Methods

rnf :: NonEmptyCursor a b -> () #

(Validity a, Validity b) => Validity (NonEmptyCursor a b) Source # 
Instance details

Defined in Cursor.List.NonEmpty

type Rep (NonEmptyCursor a b) Source # 
Instance details

Defined in Cursor.List.NonEmpty

type Rep (NonEmptyCursor a b) = D1 ('MetaData "NonEmptyCursor" "Cursor.List.NonEmpty" "cursor-0.3.2.0-Ch3lJwc3yY89mrJgbt03T" 'False) (C1 ('MetaCons "NonEmptyCursor" 'PrefixI 'True) (S1 ('MetaSel ('Just "nonEmptyCursorPrev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [b]) :*: (S1 ('MetaSel ('Just "nonEmptyCursorCurrent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "nonEmptyCursorNext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [b]))))

mapNonEmptyCursor :: (a -> c) -> (b -> d) -> NonEmptyCursor a b -> NonEmptyCursor c d Source #

nonEmptyCursorSelectPrev :: (a -> b) -> (b -> a) -> NonEmptyCursor a b -> Maybe (NonEmptyCursor a b) Source #

nonEmptyCursorSelectNext :: (a -> b) -> (b -> a) -> NonEmptyCursor a b -> Maybe (NonEmptyCursor a b) Source #

nonEmptyCursorSelectFirst :: (a -> b) -> (b -> a) -> NonEmptyCursor a b -> NonEmptyCursor a b Source #

nonEmptyCursorSelectLast :: (a -> b) -> (b -> a) -> NonEmptyCursor a b -> NonEmptyCursor a b Source #

nonEmptyCursorSelectIndex :: (a -> b) -> (b -> a) -> Int -> NonEmptyCursor a b -> Maybe (NonEmptyCursor a b) Source #

nonEmptyCursorAppendAtEndAndSelect :: (a -> b) -> (b -> a) -> b -> NonEmptyCursor a b -> NonEmptyCursor a b Source #

nonEmptyCursorSearch :: (a -> b) -> (b -> a) -> (a -> Bool) -> NonEmptyCursor a b -> Maybe (NonEmptyCursor a b) Source #

nonEmptyCursorSelectOrAdd :: (a -> b) -> (b -> a) -> (a -> Bool) -> a -> NonEmptyCursor a b -> NonEmptyCursor a b Source #

renderNonEmptyCursor :: ([b] -> a -> [b] -> c) -> NonEmptyCursor a b -> c Source #

traverseNonEmptyCursor :: ([b] -> a -> [b] -> f c) -> NonEmptyCursor a b -> f c Source #

foldNonEmptyCursor :: ([b] -> a -> [b] -> c) -> NonEmptyCursor a b -> c Source #