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

Data.IndexedDoublyLinkedList.Bare

Description

 
Synopsis

Documentation

newtype IDLList s 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

IDLList 

Fields

Instances

Instances details
MonadReader (IDLList s) (IDLListMonad s) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

Methods

ask :: IDLListMonad s (IDLList s) #

local :: (IDLList s -> IDLList s) -> IDLListMonad s a -> IDLListMonad s a #

reader :: (IDLList s -> a) -> IDLListMonad s a #

data Cell Source #

Cells in the Linked List

Constructors

Cell 

Fields

Instances

Instances details
Eq Cell Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

Methods

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

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

Show Cell Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

emptyCell :: Cell Source #

Empty cell with no next or prev cells.

data IDLListMonad s a Source #

Monad in which we can use the IndexedDoublyLinkedList.

Instances

Instances details
Monad (IDLListMonad s) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

Methods

(>>=) :: IDLListMonad s a -> (a -> IDLListMonad s b) -> IDLListMonad s b #

(>>) :: IDLListMonad s a -> IDLListMonad s b -> IDLListMonad s b #

return :: a -> IDLListMonad s a #

Functor (IDLListMonad s) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

Methods

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

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

Applicative (IDLListMonad s) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

Methods

pure :: a -> IDLListMonad s a #

(<*>) :: IDLListMonad s (a -> b) -> IDLListMonad s a -> IDLListMonad s b #

liftA2 :: (a -> b -> c) -> IDLListMonad s a -> IDLListMonad s b -> IDLListMonad s c #

(*>) :: IDLListMonad s a -> IDLListMonad s b -> IDLListMonad s b #

(<*) :: IDLListMonad s a -> IDLListMonad s b -> IDLListMonad s a #

PrimMonad (IDLListMonad s) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

Associated Types

type PrimState (IDLListMonad s) #

Methods

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

MonadReader (IDLList s) (IDLListMonad s) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

Methods

ask :: IDLListMonad s (IDLList s) #

local :: (IDLList s -> IDLList s) -> IDLListMonad s a -> IDLListMonad s a #

reader :: (IDLList s -> a) -> IDLListMonad s a #

type PrimState (IDLListMonad s) Source # 
Instance details

Defined in Data.IndexedDoublyLinkedList.Bare

type PrimState (IDLListMonad s) = s

runIDLListMonad :: Int -> (forall s. IDLListMonad s a) -> a Source #

Runs a DLList Computation, starting with n singleton values

type Index = Int Source #

Cell indices. Must be non-negative.

singletons :: (PrimMonad m, s ~ PrimState m) => Int -> m (IDLList s) Source #

Constructs a new DoublyLinkedList, of size at most n

writeList :: NonEmpty Index -> IDLListMonad s () Source #

Sets the DoublyLinkedList to the given List.

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

getNext :: Index -> IDLListMonad s (Maybe Index) Source #

Next element in the List

getPrev :: Index -> IDLListMonad s (Maybe Index) Source #

Previous Element in the List

toListFrom :: Index -> IDLListMonad s (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 -> IDLListMonad s (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 -> IDLListMonad s (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 -> IDLListMonad s (NonEmpty Index) Source #

Takes the current element and its k next's

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

Takes the current element and its k prev's

insertAfter :: Index -> Index -> IDLListMonad s () Source #

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

insertBefore :: Index -> Index -> IDLListMonad s () Source #

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

delete :: Index -> IDLListMonad s () Source #

Deletes the element from the linked list. This element thus essentially becomes a singleton list.

dump :: IDLListMonad s (Vector Cell) Source #

For debugging purposes, dump the values and the cells