friday-0.2.3.1: 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

Instances

(Image src, Storable p) => FunctorImage src (Manifest p) Source # 

Methods

map :: (ImagePixel src -> ImagePixel (Manifest p)) -> src -> Manifest p Source #

Storable acc => SeparatelyFiltrable src (Manifest p) acc Source # 

Associated Types

type SeparableFilterAccumulator src (Manifest p) acc :: * Source #

(Eq p, Storable p) => Eq (Manifest p) Source # 

Methods

(==) :: Manifest p -> Manifest p -> Bool #

(/=) :: Manifest p -> Manifest p -> Bool #

(Ord p, Storable p) => Ord (Manifest p) Source # 

Methods

compare :: Manifest p -> Manifest p -> Ordering #

(<) :: Manifest p -> Manifest p -> Bool #

(<=) :: Manifest p -> Manifest p -> Bool #

(>) :: Manifest p -> Manifest p -> Bool #

(>=) :: Manifest p -> Manifest p -> Bool #

max :: Manifest p -> Manifest p -> Manifest p #

min :: Manifest p -> Manifest p -> Manifest p #

(Storable p, Show p) => Show (Manifest p) Source # 

Methods

showsPrec :: Int -> Manifest p -> ShowS #

show :: Manifest p -> String #

showList :: [Manifest p] -> ShowS #

NFData (Manifest p) Source # 

Methods

rnf :: Manifest p -> () #

Storable p => FromFunction (Manifest p) Source # 

Associated Types

type FromFunctionPixel (Manifest p) :: * Source #

Methods

fromFunction :: Size -> (Point -> FromFunctionPixel (Manifest p)) -> Manifest p Source #

fromFunctionLine :: Size -> (Int -> a) -> (a -> Point -> FromFunctionPixel (Manifest p)) -> Manifest p Source #

fromFunctionCol :: Storable b => Size -> (Int -> b) -> (b -> Point -> FromFunctionPixel (Manifest p)) -> Manifest p Source #

fromFunctionCached :: Storable b => Size -> (Int -> a) -> (Int -> b) -> (a -> b -> Point -> FromFunctionPixel (Manifest p)) -> Manifest p Source #

Storable p => Image (Manifest p) Source # 
Storable p => MaskedImage (Manifest p) Source # 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Delayed p1) (Manifest p2) Source # 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Manifest p1) (Delayed p2) Source # 
(Storable p1, Storable p2, Convertible p1 p2) => Convertible (Manifest p1) (Manifest p2) Source # 
type SeparableFilterAccumulator src (Manifest p) acc Source # 
type FromFunctionPixel (Manifest p) Source # 
type ImagePixel (Manifest p) Source # 
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

Instances

(Image src, Storable p) => FunctorImage src (Delayed p) Source # 

Methods

map :: (ImagePixel src -> ImagePixel (Delayed p)) -> src -> Delayed p Source #

Storable acc => SeparatelyFiltrable src (Delayed p) acc Source # 

Associated Types

type SeparableFilterAccumulator src (Delayed p) acc :: * Source #

FromFunction (Delayed p) Source # 

Associated Types

type FromFunctionPixel (Delayed p) :: * Source #

Methods

fromFunction :: Size -> (Point -> FromFunctionPixel (Delayed p)) -> Delayed p Source #

fromFunctionLine :: Size -> (Int -> a) -> (a -> Point -> FromFunctionPixel (Delayed p)) -> Delayed p Source #

fromFunctionCol :: Storable b => Size -> (Int -> b) -> (b -> Point -> FromFunctionPixel (Delayed p)) -> Delayed p Source #

fromFunctionCached :: Storable b => Size -> (Int -> a) -> (Int -> b) -> (a -> b -> Point -> FromFunctionPixel (Delayed p)) -> Delayed p Source #

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

Delayed masked images

data DelayedMask p Source #

Constructors

DelayedMask 

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.