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

Safe HaskellNone
LanguageHaskell2010

Vision.Image.Type

Contents

Synopsis

Manifest images

data Manifest p Source

Stores the image content in a Vector.

Constructors

Manifest 

Fields

manifestSize :: !Size
 
manifestVector :: !(Vector p)
 

Instances

(Image src, Storable p) => FunctorImage src (Manifest p) 
Storable acc => SeparatelyFiltrable src (Manifest p) acc 
(Eq p, Storable p) => Eq (Manifest p) 
(Ord p, Storable p) => Ord (Manifest p) 
(Show p, Storable p) => Show (Manifest p) 
NFData (Manifest p) 
Storable p => FromFunction (Manifest p) 
Storable p => Image (Manifest p) 
Storable p => MaskedImage (Manifest p) 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Delayed p1) (Manifest p2) 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Manifest p1) (Delayed p2) 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Manifest p1) (Manifest p2) 
type SeparableFilterAccumulator src (Manifest p) acc = Manifest acc 
type FromFunctionPixel (Manifest p) = p 
type ImagePixel (Manifest p) = p 

Delayed images

data Delayed p Source

A delayed image is an image which is constructed using a function.

Usually, a delayed image maps each of its pixels over another image. Delayed images are useful by avoiding intermediate images in a transformation pipeline of images or by avoiding the computation of the whole resulting image when only a portion of its pixels will be accessed.

Constructors

Delayed 

Fields

delayedSize :: !Size
 
delayedFun :: !(Point -> p)
 

Instances

(Image src, Storable p) => FunctorImage src (Delayed p) 
Storable acc => SeparatelyFiltrable src (Delayed p) acc 
FromFunction (Delayed p) 
Storable p => Image (Delayed p) 
Storable p => MaskedImage (Delayed p) 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Delayed p1) (Manifest p2) 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Delayed p1) (Delayed p2) 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Manifest p1) (Delayed p2) 
type SeparableFilterAccumulator src (Delayed p) acc = Delayed acc 
type FromFunctionPixel (Delayed p) = p 
type ImagePixel (Delayed p) = p 

Delayed masked images

Conversion and type helpers

delay :: Image i => i -> Delayed (ImagePixel i) Source

Delays an image in its delayed representation.

compute :: (Image i, Storable (ImagePixel i)) => i -> Manifest (ImagePixel i) Source

Computes the value of an image into a manifest representation.

delayed :: Delayed p -> Delayed p Source

Forces an image to be in its delayed represenation. Does nothing.

manifest :: Manifest p -> Manifest p Source

Forces an image to be in its manifest represenation. Does nothing.