Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- offset_to_coord :: Integral a => (a, b) -> a -> (a, a)
- coord_to_offset :: Num a => (a, b) -> (a, a) -> a
- data Grid el a = Grid !(Vector a) !(ForeignPtr el)
- liftRnfV :: Vector a b => (b -> ()) -> a b -> ()
- length :: Grid el (v el) -> Int
- null :: Grid el (v el) -> Bool
- (!) :: Grid el (v el) -> Int -> v el
- (!?) :: Grid el (v el) -> Int -> Maybe (v el)
- head :: Grid el (v el) -> v el
- last :: Grid el (v el) -> v el
- unsafeIndex :: Grid el (v el) -> Int -> v el
- unsafeHead :: Grid el (v el) -> v el
- unsafeLast :: Grid el (v el) -> v el
- slice :: Int -> Int -> Grid el (v el) -> Grid el (v el)
- init :: Grid el (v el) -> Grid el (v el)
- tail :: Grid el (v el) -> Grid el (v el)
- take :: Int -> Grid el (v el) -> Grid el (v el)
- drop :: Int -> Grid el (v el) -> Grid el (v el)
- splitAt :: Int -> Grid el (v el) -> (Grid el (v el), Grid el (v el))
- unsafeSlice :: Int -> Int -> Grid el (v el) -> Grid el (v el)
- unsafeInit :: Grid el (v el) -> Grid el (v el)
- unsafeTail :: Grid el (v el) -> Grid el (v el)
- unsafeTake :: Int -> Grid el (v el) -> Grid el (v el)
- unsafeDrop :: Int -> Grid el (v el) -> Grid el (v el)
- reverse :: Grid el (v el) -> Grid el (v el)
- toList :: Grid el (v el) -> [v el]
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
internal grid implementation
Grid !(Vector a) !(ForeignPtr el) |
Instances
Vector (Grid el) (v el) Source # | |
Defined in Data.Grid.Storable.Internal 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 () # | |
Eq (v el) => Eq (Grid el (v el)) Source # | |
(Data el, Data a) => Data (Grid el a) Source # | |
Defined in Data.Grid.Storable.Internal 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 # | |
Defined in Data.Grid.Storable.Internal 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 # | |
Read (v el) => Read (Grid el (v el)) Source # | |
Show (v el) => Show (Grid el (v el)) Source # | |
NFData (v el) => NFData (Grid el (v el)) Source # | |
Defined in Data.Grid.Storable.Internal | |
type Mutable (Grid el) Source # | |
Defined in Data.Grid.Storable.Internal |
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
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.
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.
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.