friday-0.2.3.2: A functional image processing library for Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Vision.Primitive.Shape

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 Source #

Arguments

:: sh

Shape of the array.

-> sh

Index.

-> sh 

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

toLinearIndex Source #

Arguments

:: sh

Shape of the array.

-> sh

Index into the array.

-> Int 

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

fromLinearIndex Source #

Arguments

:: sh

Shape of the array.

-> Int

Index into linear representation.

-> sh 

Inverse of toLinearIndex.

shapeList :: sh -> [sh] Source #

Return the ascending list of indexes for the given shape.

inShape Source #

Arguments

:: sh

Shape of the array.

-> sh

Index to check for.

-> Bool 

Check whether an index is within a given shape.

Instances

Instances details
Shape Z Source # 
Instance details

Defined in Vision.Primitive.Shape

Shape sh => Shape (sh :. Int) Source # 
Instance details

Defined in Vision.Primitive.Shape

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

Instances details
Storable Z Source # 
Instance details

Defined in Vision.Primitive.Shape

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 () #

Read Z Source # 
Instance details

Defined in Vision.Primitive.Shape

Show Z Source # 
Instance details

Defined in Vision.Primitive.Shape

Methods

showsPrec :: Int -> Z -> ShowS #

show :: Z -> String #

showList :: [Z] -> ShowS #

HistogramShape Z Source # 
Instance details

Defined in Vision.Histogram

Methods

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

Shape Z Source # 
Instance details

Defined in Vision.Primitive.Shape

Eq Z Source # 
Instance details

Defined in Vision.Primitive.Shape

Methods

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

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

Ord Z Source # 
Instance details

Defined in Vision.Primitive.Shape

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 #

Unbox Z Source # 
Instance details

Defined in Vision.Primitive.Shape

Vector Vector Z Source # 
Instance details

Defined in Vision.Primitive.Shape

MVector MVector Z Source # 
Instance details

Defined in Vision.Primitive.Shape

Methods

basicLength :: MVector s Z -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s Z -> MVector s Z #

basicOverlaps :: MVector s Z -> MVector s Z -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s Z) #

basicInitialize :: MVector s Z -> ST s () #

basicUnsafeReplicate :: Int -> Z -> ST s (MVector s Z) #

basicUnsafeRead :: MVector s Z -> Int -> ST s Z #

basicUnsafeWrite :: MVector s Z -> Int -> Z -> ST s () #

basicClear :: MVector s Z -> ST s () #

basicSet :: MVector s Z -> Z -> ST s () #

basicUnsafeCopy :: MVector s Z -> MVector s Z -> ST s () #

basicUnsafeMove :: MVector s Z -> MVector s Z -> ST s () #

basicUnsafeGrow :: MVector s Z -> Int -> ST s (MVector s Z) #

newtype Vector Z Source # 
Instance details

Defined in Vision.Primitive.Shape

newtype Vector Z = V_Z (Vector ())
newtype MVector s Z Source # 
Instance details

Defined in Vision.Primitive.Shape

newtype 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

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

Defined in Vision.Primitive.Shape

Methods

basicUnsafeFreeze :: Mutable Vector s (t :. h) -> ST s (Vector (t :. h)) #

basicUnsafeThaw :: Vector (t :. h) -> ST s (Mutable Vector s (t :. h)) #

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

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

basicUnsafeIndexM :: Vector (t :. h) -> Int -> Box (t :. h) #

basicUnsafeCopy :: Mutable Vector s (t :. h) -> Vector (t :. h) -> ST s () #

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

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

Defined in Vision.Primitive.Shape

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 :: Int -> ST s (MVector s (t :. h)) #

basicInitialize :: MVector s (t :. h) -> ST s () #

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

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

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

basicClear :: MVector s (t :. h) -> ST s () #

basicSet :: MVector s (t :. h) -> (t :. h) -> ST s () #

basicUnsafeCopy :: MVector s (t :. h) -> MVector s (t :. h) -> ST s () #

basicUnsafeMove :: MVector s (t :. h) -> MVector s (t :. h) -> ST s () #

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

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

Defined in Vision.Primitive.Shape

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 () #

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

Defined in Vision.Primitive.Shape

Methods

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

readList :: ReadS [tail :. head] #

readPrec :: ReadPrec (tail :. head) #

readListPrec :: ReadPrec [tail :. head] #

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

Defined in Vision.Primitive.Shape

Methods

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

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

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

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

Defined in Vision.Histogram

Methods

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

Shape sh => Shape (sh :. Int) Source # 
Instance details

Defined in Vision.Primitive.Shape

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 #

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

Defined in Vision.Primitive.Shape

Methods

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

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

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

Defined in Vision.Primitive.Shape

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 #

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

Defined in Vision.Primitive.Shape

newtype MVector s (t :. h) Source # 
Instance details

Defined in Vision.Primitive.Shape

newtype MVector s (t :. h) = MV_Dim (MVector s (t, h))
newtype Vector (t :. h) Source # 
Instance details

Defined in Vision.Primitive.Shape

newtype 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 #