storable-grid-0.1.0.0: Contiguous blocks of Storables, represented as a Vector of Vectors

Safe HaskellNone
LanguageHaskell2010

Data.Grid.Storable.Internal

Description

Internal bits and pieces. The actual Grid data structure is defined here, and various Vector operations on it.

Not intended for public consumption; use Data.Grid.Storable instead.

Synopsis

Documentation

offset_to_coord :: Integral a => (a, b) -> a -> (a, a) Source #

convert an offset to an (x,y) pair

coord_to_offset :: Num a => (a, b) -> (a, a) -> a Source #

convert an (x,y) pair to an offset

data Grid el a Source #

internal grid implementation

Constructors

Grid !(Vector a) !(ForeignPtr el) 
Instances
Vector (Grid el) (v el) Source # 
Instance details

Defined in Data.Grid.Storable.Internal

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable (Grid el) (PrimState m) (v el) -> m (Grid el (v el)) #

basicUnsafeThaw :: PrimMonad m => Grid el (v el) -> m (Mutable (Grid el) (PrimState m) (v el)) #

basicLength :: Grid el (v el) -> Int #

basicUnsafeSlice :: Int -> Int -> Grid el (v el) -> Grid el (v el) #

basicUnsafeIndexM :: Monad m => Grid el (v el) -> Int -> m (v el) #

basicUnsafeCopy :: PrimMonad m => Mutable (Grid el) (PrimState m) (v el) -> Grid el (v el) -> m () #

elemseq :: Grid el (v el) -> v el -> b -> b #

Eq (v el) => Eq (Grid el (v el)) Source # 
Instance details

Defined in Data.Grid.Storable.Internal

Methods

(==) :: Grid el (v el) -> Grid el (v el) -> Bool #

(/=) :: Grid el (v el) -> Grid el (v el) -> Bool #

(Data el, Data a) => Data (Grid el a) Source # 
Instance details

Defined in Data.Grid.Storable.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Grid el a -> c (Grid el a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Grid el a) #

toConstr :: Grid el a -> Constr #

dataTypeOf :: Grid el a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Grid el a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Grid el a)) #

gmapT :: (forall b. Data b => b -> b) -> Grid el a -> Grid el a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Grid el a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Grid el a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Grid el a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Grid el a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Grid el a -> m (Grid el a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Grid el a -> m (Grid el a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Grid el a -> m (Grid el a) #

Ord (v el) => Ord (Grid el (v el)) Source # 
Instance details

Defined in Data.Grid.Storable.Internal

Methods

compare :: Grid el (v el) -> Grid el (v el) -> Ordering #

(<) :: Grid el (v el) -> Grid el (v el) -> Bool #

(<=) :: Grid el (v el) -> Grid el (v el) -> Bool #

(>) :: Grid el (v el) -> Grid el (v el) -> Bool #

(>=) :: Grid el (v el) -> Grid el (v el) -> Bool #

max :: Grid el (v el) -> Grid el (v el) -> Grid el (v el) #

min :: Grid el (v el) -> Grid el (v el) -> Grid el (v el) #

Read (v el) => Read (Grid el (v el)) Source # 
Instance details

Defined in Data.Grid.Storable.Internal

Methods

readsPrec :: Int -> ReadS (Grid el (v el)) #

readList :: ReadS [Grid el (v el)] #

readPrec :: ReadPrec (Grid el (v el)) #

readListPrec :: ReadPrec [Grid el (v el)] #

Show (v el) => Show (Grid el (v el)) Source # 
Instance details

Defined in Data.Grid.Storable.Internal

Methods

showsPrec :: Int -> Grid el (v el) -> ShowS #

show :: Grid el (v el) -> String #

showList :: [Grid el (v el)] -> ShowS #

NFData (v el) => NFData (Grid el (v el)) Source # 
Instance details

Defined in Data.Grid.Storable.Internal

Methods

rnf :: Grid el (v el) -> () #

type Mutable (Grid el) Source # 
Instance details

Defined in Data.Grid.Storable.Internal

type Mutable (Grid el)

liftRnfV :: Vector a b => (b -> ()) -> a b -> () Source #

length :: Grid el (v el) -> Int Source #

O(1) Yield the length of the vector

null :: Grid el (v el) -> Bool Source #

O(1) Test whether a vector is empty

(!) :: Grid el (v el) -> Int -> v el Source #

O(1) Indexing

(!?) :: Grid el (v el) -> Int -> Maybe (v el) Source #

O(1) Safe indexing

head :: Grid el (v el) -> v el Source #

O(1) First element

last :: Grid el (v el) -> v el Source #

O(1) Last element

unsafeIndex :: Grid el (v el) -> Int -> v el Source #

O(1) Unsafe indexing without bounds checking

unsafeHead :: Grid el (v el) -> v el Source #

O(1) First element without checking if the vector is empty

unsafeLast :: Grid el (v el) -> v el Source #

O(1) Last element without checking if the vector is empty

slice Source #

Arguments

:: Int

i starting index

-> Int

n length

-> Grid el (v el) 
-> Grid el (v el) 

O(1) Yield a slice of the vector without copying it. The vector must contain at least i+n elements.

init :: Grid el (v el) -> Grid el (v el) Source #

O(1) Yield all but the last element without copying. The vector may not be empty.

tail :: Grid el (v el) -> Grid el (v el) Source #

O(1) Yield all but the first element without copying. The vector may not be empty.

take :: Int -> Grid el (v el) -> Grid el (v el) Source #

O(1) Yield at the first n elements without copying. The vector may contain less than n elements in which case it is returned unchanged.

drop :: Int -> Grid el (v el) -> Grid el (v el) Source #

O(1) Yield all but the first n elements without copying. The vector may contain less than n elements in which case an empty vector is returned.

splitAt :: Int -> Grid el (v el) -> (Grid el (v el), Grid el (v el)) Source #

O(1) Yield the first n elements paired with the remainder without copying.

Note that splitAt n v is equivalent to (take n v, drop n v) but slightly more efficient.

unsafeSlice Source #

Arguments

:: Int

i starting index

-> Int

n length

-> Grid el (v el) 
-> Grid el (v el) 

O(1) Yield a slice of the vector without copying. The vector must contain at least i+n elements but this is not checked.

unsafeInit :: Grid el (v el) -> Grid el (v el) Source #

O(1) Yield all but the last element without copying. The vector may not be empty but this is not checked.

unsafeTail :: Grid el (v el) -> Grid el (v el) Source #

O(1) Yield all but the first element without copying. The vector may not be empty but this is not checked.

unsafeTake :: Int -> Grid el (v el) -> Grid el (v el) Source #

O(1) Yield the first n elements without copying. The vector must contain at least n elements but this is not checked.

unsafeDrop :: Int -> Grid el (v el) -> Grid el (v el) Source #

O(1) Yield all but the first n elements without copying. The vector must contain at least n elements but this is not checked.

reverse :: Grid el (v el) -> Grid el (v el) Source #

O(n) Reverse a vector

toList :: Grid el (v el) -> [v el] Source #

O(n) Convert a vector to a list.

Be very cautious about using this. If the underlying ForeignPtr goes out of scope and gets garbage-collected, then the data it points to may get freed, meaning all the data in the vectors returned by this function is probably invalid. Probably you should use the version in Data.Grid.Storable instead.