friday-0.2.3.1: A functional image processing library for Haskell.

Safe HaskellNone
LanguageHaskell2010

Vision.Primitive.Shape

Contents

Description

Shapes are similar to what you could found in repa. Shape are used both for indexes and shapes.

To create a shape/index, use the ix1, ix2, ix3 ... helpers :

size = ix2 200 100

To pull values from a shape, use the Z and :. constructors :

Z :. h :. w = size

Synopsis

Documentation

class Eq sh => Shape sh where Source #

Class of types that can be used as array shapes and indices.

Methods

shapeRank :: sh -> Int Source #

Gets the number of dimensions in a shape.

shapeLength :: sh -> Int Source #

Gets the total number of elements in an array of this shape.

shapeZero :: sh Source #

Gives the first index of an array.

shapeSucc :: sh -> sh -> sh Source #

Gives the successor of an index, given the shape of the array.

toLinearIndex :: sh -> sh -> Int Source #

Convert an index into its equivalent flat, linear, row-major version.

fromLinearIndex :: sh -> Int -> sh Source #

Inverse of toLinearIndex.

shapeList :: sh -> [sh] Source #

Return the ascending list of indexes for the given shape.

inShape :: sh -> sh -> Bool Source #

Check whether an index is within a given shape.

Instances

Shape Z Source # 
Shape sh => Shape ((:.) sh Int) Source # 

Methods

shapeRank :: (sh :. Int) -> Int Source #

shapeLength :: (sh :. Int) -> Int Source #

shapeZero :: sh :. Int Source #

shapeSucc :: (sh :. Int) -> (sh :. Int) -> sh :. Int Source #

toLinearIndex :: (sh :. Int) -> (sh :. Int) -> Int Source #

fromLinearIndex :: (sh :. Int) -> Int -> sh :. Int Source #

shapeList :: (sh :. Int) -> [sh :. Int] Source #

inShape :: (sh :. Int) -> (sh :. Int) -> Bool Source #

data Z Source #

An index of dimension zero.

Constructors

Z 

Instances

Eq Z Source # 

Methods

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

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

Ord Z Source # 

Methods

compare :: Z -> Z -> Ordering #

(<) :: Z -> Z -> Bool #

(<=) :: Z -> Z -> Bool #

(>) :: Z -> Z -> Bool #

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

max :: Z -> Z -> Z #

min :: Z -> Z -> Z #

Read Z Source # 
Show Z Source # 

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

Storable Z Source # 

Methods

sizeOf :: Z -> Int #

alignment :: Z -> Int #

peekElemOff :: Ptr Z -> Int -> IO Z #

pokeElemOff :: Ptr Z -> Int -> Z -> IO () #

peekByteOff :: Ptr b -> Int -> IO Z #

pokeByteOff :: Ptr b -> Int -> Z -> IO () #

peek :: Ptr Z -> IO Z #

poke :: Ptr Z -> Z -> IO () #

Unbox Z Source # 
Shape Z Source # 
HistogramShape Z Source # 

Methods

toBin :: Z -> Z -> Z -> Z Source #

Vector Vector Z Source # 
MVector MVector Z Source # 
data Vector Z Source # 
data Vector Z = V_Z (Vector ())
data MVector s Z Source # 
data MVector s Z = MV_Z (MVector s ())

data tail :. head infixl 3 Source #

Our index type, used for both shapes and indices.

Constructors

!tail :. !head infixl 3 

Instances

(Unbox t, Unbox h) => Vector Vector ((:.) t h) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (t :. h) -> m (Vector (t :. h)) #

basicUnsafeThaw :: PrimMonad m => Vector (t :. h) -> m (Mutable Vector (PrimState m) (t :. h)) #

basicLength :: Vector (t :. h) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (t :. h) -> Vector (t :. h) #

basicUnsafeIndexM :: Monad m => Vector (t :. h) -> Int -> m (t :. h) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (t :. h) -> Vector (t :. h) -> m () #

elemseq :: Vector (t :. h) -> (t :. h) -> b -> b #

(Unbox t, Unbox h) => MVector MVector ((:.) t h) Source # 

Methods

basicLength :: MVector s (t :. h) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (t :. h) -> MVector s (t :. h) #

basicOverlaps :: MVector s (t :. h) -> MVector s (t :. h) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (t :. h)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (t :. h) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (t :. h) -> m (MVector (PrimState m) (t :. h)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (t :. h) -> Int -> m (t :. h) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (t :. h) -> Int -> (t :. h) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (t :. h) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (t :. h) -> (t :. h) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (t :. h) -> MVector (PrimState m) (t :. h) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (t :. h) -> MVector (PrimState m) (t :. h) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (t :. h) -> Int -> m (MVector (PrimState m) (t :. h)) #

(Eq head, Eq tail) => Eq ((:.) tail head) Source # 

Methods

(==) :: (tail :. head) -> (tail :. head) -> Bool #

(/=) :: (tail :. head) -> (tail :. head) -> Bool #

(Ord head, Ord tail) => Ord ((:.) tail head) Source # 

Methods

compare :: (tail :. head) -> (tail :. head) -> Ordering #

(<) :: (tail :. head) -> (tail :. head) -> Bool #

(<=) :: (tail :. head) -> (tail :. head) -> Bool #

(>) :: (tail :. head) -> (tail :. head) -> Bool #

(>=) :: (tail :. head) -> (tail :. head) -> Bool #

max :: (tail :. head) -> (tail :. head) -> tail :. head #

min :: (tail :. head) -> (tail :. head) -> tail :. head #

(Read head, Read tail) => Read ((:.) tail head) Source # 

Methods

readsPrec :: Int -> ReadS (tail :. head) #

readList :: ReadS [tail :. head] #

readPrec :: ReadPrec (tail :. head) #

readListPrec :: ReadPrec [tail :. head] #

(Show head, Show tail) => Show ((:.) tail head) Source # 

Methods

showsPrec :: Int -> (tail :. head) -> ShowS #

show :: (tail :. head) -> String #

showList :: [tail :. head] -> ShowS #

Storable sh => Storable ((:.) sh Int) Source # 

Methods

sizeOf :: (sh :. Int) -> Int #

alignment :: (sh :. Int) -> Int #

peekElemOff :: Ptr (sh :. Int) -> Int -> IO (sh :. Int) #

pokeElemOff :: Ptr (sh :. Int) -> Int -> (sh :. Int) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (sh :. Int) #

pokeByteOff :: Ptr b -> Int -> (sh :. Int) -> IO () #

peek :: Ptr (sh :. Int) -> IO (sh :. Int) #

poke :: Ptr (sh :. Int) -> (sh :. Int) -> IO () #

(Unbox t, Unbox h) => Unbox ((:.) t h) Source # 
Shape sh => Shape ((:.) sh Int) Source # 

Methods

shapeRank :: (sh :. Int) -> Int Source #

shapeLength :: (sh :. Int) -> Int Source #

shapeZero :: sh :. Int Source #

shapeSucc :: (sh :. Int) -> (sh :. Int) -> sh :. Int Source #

toLinearIndex :: (sh :. Int) -> (sh :. Int) -> Int Source #

fromLinearIndex :: (sh :. Int) -> Int -> sh :. Int Source #

shapeList :: (sh :. Int) -> [sh :. Int] Source #

inShape :: (sh :. Int) -> (sh :. Int) -> Bool Source #

HistogramShape sh => HistogramShape ((:.) sh Int) Source # 

Methods

toBin :: (sh :. Int) -> (sh :. Int) -> (sh :. Int) -> sh :. Int Source #

data MVector s ((:.) t h) Source # 
data MVector s ((:.) t h) = MV_Dim (MVector s (t, h))
data Vector ((:.) t h) Source # 
data Vector ((:.) t h) = V_Dim (Vector (t, h))

Common dimensions.

type DIM0 = Z Source #

Helpers

ix1 :: Int -> DIM1 Source #

Helper for index construction.

Use this instead of explicit constructors like (Z :. (x :: Int)) The this is sometimes needed to ensure that x is constrained to be in Int.

ix2 :: Int -> Int -> DIM2 Source #

ix3 :: Int -> Int -> Int -> DIM3 Source #

ix4 :: Int -> Int -> Int -> Int -> DIM4 Source #

ix5 :: Int -> Int -> Int -> Int -> Int -> DIM5 Source #

ix6 :: Int -> Int -> Int -> Int -> Int -> Int -> DIM6 Source #

ix7 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM7 Source #

ix8 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM8 Source #

ix9 :: Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> DIM9 Source #