hgeometry-combinatorial-0.12.0.1: Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.IndexedDoublyLinkedList

Description

 
Synopsis

Documentation

data DLList s a Source #

Doubly linked list implemented by a mutable vector. So actually this data type can represent a collection of Linked Lists that can efficiently be concatenated and split.

Supports O(1) indexing, and O(1) insertions, deletions

Constructors

DLList 

Fields

Instances

Instances details
Functor (DLList s) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Methods

fmap :: (a -> b) -> DLList s a -> DLList s b #

(<$) :: a -> DLList s b -> DLList s a #

MonadReader (DLList s b) (DLListMonad s b) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Methods

ask :: DLListMonad s b (DLList s b) #

local :: (DLList s b -> DLList s b) -> DLListMonad s b a -> DLListMonad s b a #

reader :: (DLList s b -> a) -> DLListMonad s b a #

data Cell Source #

Cells in the Linked List

Constructors

Cell 

Fields

Instances

Instances details
Eq Cell Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Methods

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

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

Show Cell Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

emptyCell :: Cell Source #

Empty cell with no next or prev cells.

data DLListMonad s b a Source #

Monad in which we can use the IndexedDoublyLinkedList.

Instances

Instances details
Monad (DLListMonad s b) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Methods

(>>=) :: DLListMonad s b a -> (a -> DLListMonad s b b0) -> DLListMonad s b b0 #

(>>) :: DLListMonad s b a -> DLListMonad s b b0 -> DLListMonad s b b0 #

return :: a -> DLListMonad s b a #

Functor (DLListMonad s b) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Methods

fmap :: (a -> b0) -> DLListMonad s b a -> DLListMonad s b b0 #

(<$) :: a -> DLListMonad s b b0 -> DLListMonad s b a #

Applicative (DLListMonad s b) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Methods

pure :: a -> DLListMonad s b a #

(<*>) :: DLListMonad s b (a -> b0) -> DLListMonad s b a -> DLListMonad s b b0 #

liftA2 :: (a -> b0 -> c) -> DLListMonad s b a -> DLListMonad s b b0 -> DLListMonad s b c #

(*>) :: DLListMonad s b a -> DLListMonad s b b0 -> DLListMonad s b b0 #

(<*) :: DLListMonad s b a -> DLListMonad s b b0 -> DLListMonad s b a #

PrimMonad (DLListMonad s b) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Associated Types

type PrimState (DLListMonad s b) #

Methods

primitive :: (State# (PrimState (DLListMonad s b)) -> (# State# (PrimState (DLListMonad s b)), a #)) -> DLListMonad s b a #

MonadReader (DLList s b) (DLListMonad s b) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

Methods

ask :: DLListMonad s b (DLList s b) #

local :: (DLList s b -> DLList s b) -> DLListMonad s b a -> DLListMonad s b a #

reader :: (DLList s b -> a) -> DLListMonad s b a #

type PrimState (DLListMonad s b) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList

type PrimState (DLListMonad s b) = s

runDLListMonad :: Vector b -> (forall s. DLListMonad s b a) -> a Source #

Runs a DLList Computation, starting with singleton values, crated from the input vector.

type Index = Int Source #

Cell indices. Must be non-negative.

singletons :: (PrimMonad m, s ~ PrimState m) => Vector b -> m (DLList s b) Source #

Constructs a new DoublyLinkedList. Every element is its own singleton list

writeList :: NonEmpty Index -> DLListMonad s b () Source #

Sets the DoublyLinkedList to the given List.

Indices that do not occur in the list are not touched.

valueAt :: Index -> DLListMonad s b b Source #

Gets the value at Index i

getNext :: Index -> DLListMonad s b (Maybe Index) Source #

Next element in the List

getPrev :: Index -> DLListMonad s b (Maybe Index) Source #

Previous Element in the List

toListFrom :: Index -> DLListMonad s b (NonEmpty Index) Source #

Computes a maximal length list starting from the Given index

running time: \(O(k)\), where \(k\) is the length of the output list

toListFromR :: Index -> DLListMonad s b (NonEmpty Index) Source #

Computes a maximal length list by walking backwards in the DoublyLinkedList, starting from the Given index

running time: \(O(k)\), where \(k\) is the length of the output list

toListContains :: Index -> DLListMonad s b (NonEmpty Index) Source #

Computes a maximal length list that contains the element i.

running time: \(O(k)\), where \(k\) is the length of the output list

toListFromK :: Index -> Int -> DLListMonad s b (NonEmpty Index) Source #

Takes the current element and its k next's

toListFromRK :: Index -> Int -> DLListMonad s b (NonEmpty Index) Source #

Takes the current element and its k prev's

insertAfter :: Index -> Index -> DLListMonad s b () Source #

Inserts the second argument after the first one into the linked list

insertBefore :: Index -> Index -> DLListMonad s b () Source #

Inserts the second argument before the first one into the linked list

delete :: Index -> DLListMonad s b (Maybe Index, Maybe Index) Source #

Deletes the element from the linked list. This element thus essentially becomes a singleton list. Returns the pair of indices that now have become neighbours (i.e. the predecessor and successor of j just before we deleted j).

dump :: DLListMonad s a (Vector a, Vector Cell) Source #

For debugging purposes, dump the values and the cells