tcod-haskell-0.1.0.0: Bindings to libtcod roguelike engine

Safe HaskellNone
LanguageHaskell2010

Game.TCOD.List

Contents

Synopsis

Documentation

newtype TCODList a Source #

This is a fast, lightweight and generic container, that provides array, list and stack paradigms.

Constructors

TCODList 

Fields

Instances

Eq (TCODList a) Source # 

Methods

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

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

Ord (TCODList a) Source # 

Methods

compare :: TCODList a -> TCODList a -> Ordering #

(<) :: TCODList a -> TCODList a -> Bool #

(<=) :: TCODList a -> TCODList a -> Bool #

(>) :: TCODList a -> TCODList a -> Bool #

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

max :: TCODList a -> TCODList a -> TCODList a #

min :: TCODList a -> TCODList a -> TCODList a #

Show (TCODList a) Source # 

Methods

showsPrec :: Int -> TCODList a -> ShowS #

show :: TCODList a -> String #

showList :: [TCODList a] -> ShowS #

Generic (TCODList a) Source # 

Associated Types

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

Methods

from :: TCODList a -> Rep (TCODList a) x #

to :: Rep (TCODList a) x -> TCODList a #

type Rep (TCODList a) Source # 
type Rep (TCODList a) = D1 (MetaData "TCODList" "Game.TCOD.List" "tcod-haskell-0.1.0.0-9JdFGODCf32GFoGmrQ4wdi" True) (C1 (MetaCons "TCODList" PrefixI True) (S1 (MetaSel (Just Symbol "unTCODList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ptr ()))))

listNew :: IO (TCODList a) Source #

Creating a list

listAllocate Source #

Arguments

:: Int

Number of elements

-> IO (TCODList a) 

You can also create an empty list and pre-allocate memory for elements. Use this if you know the list size and want the memory to fit it perfectly.

listDuplicated :: TCODList a -> IO (TCODList a) Source #

You can create a list by duplicating an existing list.

listDelete :: TCODList a -> IO () Source #

You can delete a list, freeing any allocated resources. Note that deleting the list does not delete it's elements. You have to use clearAndDelete before deleting the list if you want to destroy the elements too.

listPush :: Storable a => TCODList a -> a -> IO () Source #

You can push an element on the stack (append it to the end of the list)

listPushPtr :: TCODList a -> Ptr a -> IO () Source #

You can push an element on the stack (append it to the end of the list)

listPop :: Storable a => TCODList a -> IO (Maybe a) Source #

You can pop an element from the stack (remove the last element of the list).

listPopPtr :: TCODList a -> IO (Ptr a) Source #

You can pop an element from the stack (remove the last element of the list).

listPeek :: Storable a => TCODList a -> IO (Maybe a) Source #

You can read the last element of the stack without removing it :

listPeekPtr :: TCODList a -> IO (Ptr a) Source #

You can read the last element of the stack without removing it :

listAddAll :: TCODList a -> TCODList a -> IO () Source #

You can concatenate two lists. Every element of l2 will be added to current list

listGet :: Storable a => TCODList a -> Int -> IO (Maybe a) Source #

You can retrieve a value with get.

listGetPtr :: TCODList a -> Int -> IO (Ptr a) Source #

You can retrieve a value with get.

listSet :: Storable a => TCODList a -> a -> Int -> IO () Source #

You can assign a value with set. If needed, the array will allocate new elements up to idx.

listSetPtr :: TCODList a -> Ptr a -> Int -> IO () Source #

You can assign a value with set. If needed, the array will allocate new elements up to idx.

listBeginPtr :: TCODList a -> IO (Ptr (Ptr a)) Source #

You can iterate through the elements of the list using an iterator. begin() returns the address of the first element of the list. You go to the next element using the increment operator ++. When the iterator's value is equal to end(), you've gone through all the elements.

Warning ! You cannot insert elements in the list while iterating through it. Inserting elements can result in reallocation of the list and your iterator will not longer be valid.

listEndPtr :: TCODList a -> IO (Ptr (Ptr a)) Source #

You can iterate through the elements of the list using an iterator. begin() returns the address of the first element of the list. You go to the next element using the increment operator ++. When the iterator's value is equal to end(), you've gone through all the elements.

Warning ! You cannot insert elements in the list while iterating through it. Inserting elements can result in reallocation of the list and your iterator will not longer be valid.

listReverse :: TCODList a -> IO () Source #

This function reverses the order of the elements in the list.

listRemoveIterator :: TCODList a -> Ptr (Ptr a) -> IO (Ptr (Ptr a)) Source #

You can remove an element from the list while iterating. The element at the iterator position will be removed. The function returns the new iterator. The _fast versions replace the element to remove with the last element of the list. They're faster, but do not preserve the list order.

listRemoveIteratorFast :: TCODList a -> Ptr (Ptr a) -> IO (Ptr (Ptr a)) Source #

You can remove an element from the list while iterating. The element at the iterator position will be removed. The function returns the new iterator. The _fast versions replace the element to remove with the last element of the list. They're faster, but do not preserve the list order.

listRemovePtr :: TCODList a -> Ptr a -> IO () Source #

Removing an element from the list

listRemove :: Storable a => TCODList a -> a -> IO () Source #

Removing an element from the list

listRemoveFastPtr :: TCODList a -> Ptr a -> IO () Source #

The _fast versions replace the element to remove with the last element of the list. They're faster, but do not preserve the list order.

listRemoveFast :: Storable a => TCODList a -> a -> IO () Source #

The _fast versions replace the element to remove with the last element of the list. They're faster, but do not preserve the list order.

listContainsPtr :: TCODList a -> Ptr a -> IO Bool Source #

Checking if an element is in the list

listContains :: Storable a => TCODList a -> a -> IO Bool Source #

Checking if an element is in the list

listClear :: TCODList a -> IO () Source #

Emptying a list

listClearAndDelete :: TCODList a -> IO () Source #

For lists containing pointers, you can clear the list and delete (or free for C) the elements :

listSize :: TCODList a -> IO Int Source #

Getting the list size

listInsertBeforePtr :: TCODList a -> Ptr a -> Int -> IO (Ptr (Ptr a)) Source #

Insert an element in the list

listInsertBefore :: Storable a => TCODList a -> a -> Int -> IO (Ptr (Ptr a)) Source #

Insert an element in the list

listIsEmpty :: TCODList a -> IO Bool Source #

Checking if a list is empty

Haskell conversion

listToList :: forall a. Storable a => TCODList a -> IO [a] Source #

Load to Haskell list O(N)

listFromList :: forall a f. (Foldable f, Storable a) => f a -> IO (TCODList a) Source #

Unload Haskell list to TCOD container O(N)

listToVectorUnsafe :: forall a. Storable a => TCODList a -> IO (Vector a) Source #

Convert TCOD list to Haskell storable vector. O(1)

Note: The vector reuses memory of the list and valid until the TCOD list is not deleted or reallocated (due mutation).

listToVector :: forall a. Storable a => TCODList a -> IO (Vector a) Source #

Convert TCOD list to Haskell storable vector. O(N)

Note: The vector content is copied into haskell heap.