Copyright | (c) Alexey Kuleshevich 2017 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <[email protected]> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Graphics.Image.ColorSpace
Contents
Description
- class (Eq cs, Enum cs, Show cs, Bounded cs, Typeable cs, Elevator e, Typeable e) => ColorSpace cs e
- data family Pixel cs e :: *
- class (ColorSpace (Opaque cs) e, ColorSpace cs e) => AlphaSpace cs e where
- type Opaque cs
- class Elevator e where
- eqTolPx :: (ColorSpace cs e, Num e, Ord e) => e -> Pixel cs e -> Pixel cs e -> Bool
- data Y = LumaY
- data YA
- data family Pixel cs e :: *
- class ColorSpace cs Double => ToY cs where
- class (ToY (Opaque cs), AlphaSpace cs Double) => ToYA cs where
- data RGB
- data RGBA
- data family Pixel cs e :: *
- class ColorSpace cs Double => ToRGB cs where
- class (ToRGB (Opaque cs), AlphaSpace cs Double) => ToRGBA cs where
- data HSI
- data HSIA
- data family Pixel cs e :: *
- class ColorSpace cs Double => ToHSI cs where
- class (ToHSI (Opaque cs), AlphaSpace cs Double) => ToHSIA cs where
- data CMYK
- data CMYKA
- data family Pixel cs e :: *
- class ColorSpace cs Double => ToCMYK cs where
- class (ToCMYK (Opaque cs), AlphaSpace cs Double) => ToCMYKA cs where
- data YCbCr
- data YCbCrA
- data family Pixel cs e :: *
- class ColorSpace cs Double => ToYCbCr cs where
- class (ToYCbCr (Opaque cs), AlphaSpace cs Double) => ToYCbCrA cs where
- data X = X
- data family Pixel cs e :: *
- toImagesX :: (Array arr cs e, Array arr X e) => Image arr cs e -> [Image arr X e]
- fromImagesX :: forall arr cs e. (Array arr X e, Array arr cs e) => [(cs, Image arr X e)] -> Image arr cs e
- data Binary
- data Bit
- on :: Pixel Binary Bit
- off :: Pixel Binary Bit
- isOn :: Pixel Binary Bit -> Bool
- isOff :: Pixel Binary Bit -> Bool
- fromBool :: Bool -> Pixel Binary Bit
- complement :: Bits a => a -> a
- toPixelBinary :: (Eq (Pixel cs e), Num (Pixel cs e)) => Pixel cs e -> Pixel Binary Bit
- fromPixelBinary :: Pixel Binary Bit -> Pixel Y Word8
- toImageBinary :: (Array arr cs e, Array arr Binary Bit, Eq (Pixel cs e)) => Image arr cs e -> Image arr Binary Bit
- fromImageBinary :: (Array arr Binary Bit, Array arr Y Word8) => Image arr Binary Bit -> Image arr Y Word8
- data Complex a :: * -> * = ~a :+ ~a
- (+:) :: Applicative (Pixel cs) => Pixel cs e -> Pixel cs e -> Pixel cs (Complex e)
- realPart :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e
- imagPart :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e
- mkPolar :: (Applicative (Pixel cs), RealFloat e) => Pixel cs e -> Pixel cs e -> Pixel cs (Complex e)
- cis :: (Applicative (Pixel cs), RealFloat e) => Pixel cs e -> Pixel cs (Complex e)
- polar :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> (Pixel cs e, Pixel cs e)
- magnitude :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e
- phase :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e
- conjugate :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs (Complex e)
- data Word8 :: *
- data Word16 :: *
- data Word32 :: *
- data Word64 :: *
ColorSpace
class (Eq cs, Enum cs, Show cs, Bounded cs, Typeable cs, Elevator e, Typeable e) => ColorSpace cs e Source #
Minimal complete definition
toComponents, fromComponents, promote, getPxC, setPxC, mapPxC, liftPx, liftPx2, foldlPx2
Instances
(Elevator e, Typeable * e) => ColorSpace YCbCrA e Source # | |
(Elevator e, Typeable * e) => ColorSpace YCbCr e Source # | |
(Elevator e, Typeable * e) => ColorSpace YA e Source # | |
(Elevator e, Typeable * e) => ColorSpace Y e Source # | |
(Elevator e, Typeable * e) => ColorSpace X e Source # | |
(Elevator e, Typeable * e) => ColorSpace RGBA e Source # | |
(Elevator e, Typeable * e) => ColorSpace RGB e Source # | |
(Elevator e, Typeable * e) => ColorSpace HSIA e Source # | |
(Elevator e, Typeable * e) => ColorSpace HSI e Source # | |
(Elevator e, Typeable * e) => ColorSpace CMYKA e Source # | |
(Elevator e, Typeable * e) => ColorSpace CMYK e Source # | |
ColorSpace Binary Bit Source # | |
data family Pixel cs e :: * Source #
A Pixel family with a color space and a precision of elements.
Instances
class (ColorSpace (Opaque cs) e, ColorSpace cs e) => AlphaSpace cs e where Source #
A color space that supports transparency.
Methods
getAlpha :: Pixel cs e -> e Source #
Get an alpha channel of a transparant pixel.
addAlpha :: e -> Pixel (Opaque cs) e -> Pixel cs e Source #
Add an alpha channel of an opaque pixel.
addAlpha 0 (PixelHSI 1 2 3) == PixelHSIA 1 2 3 0
dropAlpha :: Pixel cs e -> Pixel (Opaque cs) e Source #
Convert a transparent pixel to an opaque one by dropping the alpha channel.
dropAlpha (PixelRGBA 1 2 3 4) == PixelRGB 1 2 3
class Elevator e where Source #
A class with a set of convenient functions that allow for changing precision of channels within pixels, while scaling the values to keep them in an appropriate range.
>>>
let rgb = PixelRGB 0.0 0.5 1.0 :: Pixel RGB Double
>>>
toWord8 rgb
<RGB:(0|128|255)>
Methods
toWord8 :: e -> Word8 Source #
Values are scaled to [0, 255]
range.
toWord16 :: e -> Word16 Source #
Values are scaled to [0, 65535]
range.
toWord32 :: e -> Word32 Source #
Values are scaled to [0, 4294967295]
range.
toWord64 :: e -> Word64 Source #
Values are scaled to [0, 18446744073709551615]
range.
toFloat :: e -> Float Source #
Values are scaled to [0.0, 1.0]
range.
toDouble :: e -> Double Source #
Values are scaled to [0.0, 1.0]
range.
fromDouble :: Double -> e Source #
Values are scaled from [0.0, 1.0]
range.
Operations on Pixels
Luma
Luma or brightness, which is usually denoted as Y'
.
Constructors
LumaY |
Instances
Luma with Alpha channel.
Instances
data family Pixel cs e :: * Source #
A Pixel family with a color space and a precision of elements.
Instances
class ColorSpace cs Double => ToY cs where Source #
Conversion to Luma color space.
Minimal complete definition
class (ToY (Opaque cs), AlphaSpace cs Double) => ToYA cs where Source #
Conversion to Luma from another color space with Alpha channel.
RGB
Red, Green and Blue color space.
Instances
Red, Green and Blue color space with Alpha channel.
Instances
data family Pixel cs e :: * Source #
A Pixel family with a color space and a precision of elements.
Instances
class ColorSpace cs Double => ToRGB cs where Source #
Conversion to RGB
color space.
Minimal complete definition
class (ToRGB (Opaque cs), AlphaSpace cs Double) => ToRGBA cs where Source #
Conversion to RGBA
from another color space with Alpha channel.
HSI
Hue, Saturation and Intensity color space.
Instances
Bounded HSI Source # | |
Enum HSI Source # | |
Eq HSI Source # | |
Show HSI Source # | |
ChannelColour HSI Source # | |
(Elevator e, Typeable * e) => ColorSpace HSI e Source # | |
Functor (Pixel HSI) Source # | |
Applicative (Pixel HSI) Source # | |
Foldable (Pixel HSI) Source # | |
Eq e => Eq (Pixel HSI e) Source # | |
Floating e => Floating (Pixel HSI e) Source # | |
Fractional e => Fractional (Pixel HSI e) Source # | |
Num e => Num (Pixel HSI e) Source # | |
Show e => Show (Pixel HSI e) Source # | |
Storable e => Storable (Pixel HSI e) Source # | |
data Pixel HSI Source # | |
type Components HSI e Source # | |
Hue, Saturation and Intensity color space with Alpha channel.
Instances
Bounded HSIA Source # | |
Enum HSIA Source # | |
Eq HSIA Source # | |
Show HSIA Source # | |
ChannelColour HSIA Source # | |
(Elevator e, Typeable * e) => AlphaSpace HSIA e Source # | |
(Elevator e, Typeable * e) => ColorSpace HSIA e Source # | |
Functor (Pixel HSIA) Source # | |
Applicative (Pixel HSIA) Source # | |
Foldable (Pixel HSIA) Source # | |
Eq e => Eq (Pixel HSIA e) Source # | |
Floating e => Floating (Pixel HSIA e) Source # | |
Fractional e => Fractional (Pixel HSIA e) Source # | |
Num e => Num (Pixel HSIA e) Source # | |
Show e => Show (Pixel HSIA e) Source # | |
Storable e => Storable (Pixel HSIA e) Source # | |
type Opaque HSIA Source # | |
data Pixel HSIA Source # | |
type Components HSIA e Source # | |
data family Pixel cs e :: * Source #
A Pixel family with a color space and a precision of elements.
Instances
class ColorSpace cs Double => ToHSI cs where Source #
Conversion to HSI
color space.
Minimal complete definition
class (ToHSI (Opaque cs), AlphaSpace cs Double) => ToHSIA cs where Source #
Conversion to HSIA
from another color space with Alpha channel.
CMYK
Cyan, Magenta, Yellow and Black color space.
Instances
Bounded CMYK Source # | |
Enum CMYK Source # | |
Eq CMYK Source # | |
Show CMYK Source # | |
ChannelColour CMYK Source # | |
(Elevator e, Typeable * e) => ColorSpace CMYK e Source # | |
Functor (Pixel CMYK) Source # | |
Applicative (Pixel CMYK) Source # | |
Foldable (Pixel CMYK) Source # | |
Eq e => Eq (Pixel CMYK e) Source # | |
Floating e => Floating (Pixel CMYK e) Source # | |
Fractional e => Fractional (Pixel CMYK e) Source # | |
Num e => Num (Pixel CMYK e) Source # | |
Show e => Show (Pixel CMYK e) Source # | |
Storable e => Storable (Pixel CMYK e) Source # | |
Writable (Image VS CMYK Double) TIF Source # | |
Writable (Image VS CMYK Word8) TIF Source # | |
Writable (Image VS CMYK Word8) JPG Source # | |
Writable (Image VS CMYK Word16) TIF Source # | |
Readable (Image VS CMYK Word8) TIF Source # | |
Readable (Image VS CMYK Word8) JPG Source # | |
Readable (Image VS CMYK Word16) TIF Source # | |
data Pixel CMYK Source # | |
type Components CMYK e Source # | |
Cyan, Magenta, Yellow and Black color space with Alpha channel.
Constructors
CyanCMYKA | Cyan |
MagCMYKA | Magenta |
YelCMYKA | Yellow |
KeyCMYKA | Key (Black) |
AlphaCMYKA | Alpha |
Instances
Bounded CMYKA Source # | |
Enum CMYKA Source # | |
Eq CMYKA Source # | |
Show CMYKA Source # | |
ChannelColour CMYKA Source # | |
(Elevator e, Typeable * e) => AlphaSpace CMYKA e Source # | |
(Elevator e, Typeable * e) => ColorSpace CMYKA e Source # | |
Functor (Pixel CMYKA) Source # | |
Applicative (Pixel CMYKA) Source # | |
Foldable (Pixel CMYKA) Source # | |
Eq e => Eq (Pixel CMYKA e) Source # | |
Floating e => Floating (Pixel CMYKA e) Source # | |
Fractional e => Fractional (Pixel CMYKA e) Source # | |
Num e => Num (Pixel CMYKA e) Source # | |
Show e => Show (Pixel CMYKA e) Source # | |
Storable e => Storable (Pixel CMYKA e) Source # | |
type Opaque CMYKA Source # | |
data Pixel CMYKA Source # | |
type Components CMYKA e Source # | |
data family Pixel cs e :: * Source #
A Pixel family with a color space and a precision of elements.
Instances
class ColorSpace cs Double => ToCMYK cs where Source #
Conversion to CMYK
color space.
Minimal complete definition
class (ToCMYK (Opaque cs), AlphaSpace cs Double) => ToCMYKA cs where Source #
Conversion to CMYKA
from another color space with Alpha channel.
YCbCr
Color space is used to encode RGB information and is used in JPEG compression.
Constructors
LumaYCbCr | Luma component (commonly denoted as Y') |
CBlueYCbCr | Blue difference chroma component |
CRedYCbCr | Red difference chroma component |
Instances
Bounded YCbCr Source # | |
Enum YCbCr Source # | |
Eq YCbCr Source # | |
Show YCbCr Source # | |
ChannelColour YCbCr Source # | |
(Elevator e, Typeable * e) => ColorSpace YCbCr e Source # | |
Functor (Pixel YCbCr) Source # | |
Applicative (Pixel YCbCr) Source # | |
Foldable (Pixel YCbCr) Source # | |
Eq e => Eq (Pixel YCbCr e) Source # | |
Floating e => Floating (Pixel YCbCr e) Source # | |
Fractional e => Fractional (Pixel YCbCr e) Source # | |
Num e => Num (Pixel YCbCr e) Source # | |
Show e => Show (Pixel YCbCr e) Source # | |
Storable e => Storable (Pixel YCbCr e) Source # | |
Writable (Image VS YCbCr Double) TIF Source # | |
Writable (Image VS YCbCr Word8) TIF Source # | |
Writable (Image VS YCbCr Word8) JPG Source # | |
Readable (Image VS YCbCr Word8) JPG Source # | |
data Pixel YCbCr Source # | |
type Components YCbCr e Source # | |
YCbCr color space with Alpha channel.
Constructors
LumaYCbCrA | Luma component (commonly denoted as Y') |
CBlueYCbCrA | Blue difference chroma component |
CRedYCbCrA | Red difference chroma component |
AlphaYCbCrA | Alpha component. |
Instances
Bounded YCbCrA Source # | |
Enum YCbCrA Source # | |
Eq YCbCrA Source # | |
Show YCbCrA Source # | |
ChannelColour YCbCrA Source # | |
(Elevator e, Typeable * e) => AlphaSpace YCbCrA e Source # | |
(Elevator e, Typeable * e) => ColorSpace YCbCrA e Source # | |
Functor (Pixel YCbCrA) Source # | |
Applicative (Pixel YCbCrA) Source # | |
Foldable (Pixel YCbCrA) Source # | |
Eq e => Eq (Pixel YCbCrA e) Source # | |
Floating e => Floating (Pixel YCbCrA e) Source # | |
Fractional e => Fractional (Pixel YCbCrA e) Source # | |
Num e => Num (Pixel YCbCrA e) Source # | |
Show e => Show (Pixel YCbCrA e) Source # | |
Storable e => Storable (Pixel YCbCrA e) Source # | |
type Opaque YCbCrA Source # | |
data Pixel YCbCrA Source # | |
type Components YCbCrA e Source # | |
data family Pixel cs e :: * Source #
A Pixel family with a color space and a precision of elements.
Instances
class ColorSpace cs Double => ToYCbCr cs where Source #
Conversion to YCbCr
color space.
Minimal complete definition
class (ToYCbCr (Opaque cs), AlphaSpace cs Double) => ToYCbCrA cs where Source #
Conversion to YCbCrA
from another color space with Alpha channel.
Gray level
This is a single channel colorspace, that is designed to separate Gray
level values from other types of colorspace, hence it is not convertible to
or from, but rather is here to allow operation on arbirtary single channel
images. If you are looking for a true grayscale colorspace
Y
should be used instead.
Constructors
X |
Instances
Bounded X Source # | |
Enum X Source # | |
Eq X Source # | |
Show X Source # | |
ChannelColour X Source # | |
(Elevator e, Typeable * e) => ColorSpace X e Source # | |
Monad (Pixel X) Source # | |
Functor (Pixel X) Source # | |
Applicative (Pixel X) Source # | |
Foldable (Pixel X) Source # | |
Eq e => Eq (Pixel X e) Source # | |
Floating e => Floating (Pixel X e) Source # | |
Fractional e => Fractional (Pixel X e) Source # | |
Num e => Num (Pixel X e) Source # | |
Ord e => Ord (Pixel X e) Source # | |
Show e => Show (Pixel X e) Source # | |
Storable e => Storable (Pixel X e) Source # | |
data Pixel X Source # | |
type Components X e Source # | |
data family Pixel cs e :: * Source #
A Pixel family with a color space and a precision of elements.
Instances
toImagesX :: (Array arr cs e, Array arr X e) => Image arr cs e -> [Image arr X e] Source #
Separate an image into a list of images with X
pixels containing every
channel from the source image.
>>>
frog <- readImageRGB "images/frog.jpg"
>>>
let [frog_red, frog_green, frog_blue] = toImagesX frog
>>>
writeImage "images/frog_red.png" $ toImageY frog_red
>>>
writeImage "images/frog_green.jpg" $ toImageY frog_green
>>>
writeImage "images/frog_blue.jpg" $ toImageY frog_blue
fromImagesX :: forall arr cs e. (Array arr X e, Array arr cs e) => [(cs, Image arr X e)] -> Image arr cs e Source #
Combine a list of images with X
pixels into an image of any color
space, by supplying an order of color space channels.
For example here is a frog with swapped BlueRGB
and GreenRGB
channels.
>>>
writeImage "images/frog_rbg.jpg" $ fromImagesX [frog_red, frog_green, frog_blue] [RedRGB, BlueRGB, GreenRGB]
It is worth noting though, despite that separating image channels can be sometimes pretty useful, exactly the same effect as in example above can be achieved in a much simpler and a more efficient way:
map ((PixelRGB r g b) -> PixelRGB r b g) frog
Binary
This is a Binary colorspace, pixel's of which can be created using these constructors:
on
- Represents value
1
orTrue
. It's a foreground pixel and is displayed in black. off
- Represents value
0
orFalse
. It's a background pixel and is displayed in white.
Note, that values are inverted before writing to or reading from file, since
grayscale images represent black as a 0
value and white as 1
on a
[0,1]
scale.
Binary pixels also behave as binary numbers with a size of 1-bit, for instance:
>>>
on + on -- equivalent to: 1 .|. 1
<Binary:(1)>>>>
(on + on) * off -- equivalent to: (1 .|. 1) .&. 0
<Binary:(0)>>>>
(on + on) - on
<Binary:(0)>
Instances
Bounded Binary Source # | |
Enum Binary Source # | |
Eq Binary Source # | |
Show Binary Source # | |
ColorSpace Binary Bit Source # | |
Readable [Image VS Binary Bit] [PBM] Source # | |
Eq (Pixel Binary Bit) Source # | |
Num (Pixel Binary Bit) Source # | |
Ord (Pixel Binary Bit) Source # | |
Show (Pixel Binary Bit) Source # | |
Storable (Pixel Binary Bit) Source # | |
Bits (Pixel Binary Bit) Source # | |
Writable (Image VS Binary Bit) TIF Source # | |
Writable (Image VS Binary Bit) TGA Source # | |
Writable (Image VS Binary Bit) PNG Source # | |
Writable (Image VS Binary Bit) BMP Source # | |
Readable (Image VS Binary Bit) TIF Source # | |
Readable (Image VS Binary Bit) TGA Source # | |
Readable (Image VS Binary Bit) PNG Source # | |
Readable (Image VS Binary Bit) BMP Source # | |
Readable (Image VS Binary Bit) PBM Source # | |
type Components Binary Bit Source # | |
data Pixel Binary Bit Source # | |
Under the hood, Binary pixels are represented as Word8
, but can only take
values of 0
or 1
.
Instances
Eq Bit Source # | |
Num Bit Source # | |
Ord Bit Source # | |
Storable Bit Source # | |
Bits Bit Source # | |
Elevator Bit Source # | |
ColorSpace Binary Bit Source # | |
Readable [Image VS Binary Bit] [PBM] Source # | |
Eq (Pixel Binary Bit) Source # | |
Num (Pixel Binary Bit) Source # | |
Ord (Pixel Binary Bit) Source # | |
Show (Pixel Binary Bit) Source # | |
Storable (Pixel Binary Bit) Source # | |
Bits (Pixel Binary Bit) Source # | |
Writable (Image VS Binary Bit) TIF Source # | |
Writable (Image VS Binary Bit) TGA Source # | |
Writable (Image VS Binary Bit) PNG Source # | |
Writable (Image VS Binary Bit) BMP Source # | |
Readable (Image VS Binary Bit) TIF Source # | |
Readable (Image VS Binary Bit) TGA Source # | |
Readable (Image VS Binary Bit) PNG Source # | |
Readable (Image VS Binary Bit) BMP Source # | |
Readable (Image VS Binary Bit) PBM Source # | |
data Vector Bit # | |
data MVector s Bit # | |
type Components Binary Bit Source # | |
data Pixel Binary Bit Source # | |
on :: Pixel Binary Bit Source #
Represents value True
or 1
in binary. Often also called a foreground
pixel of an object.
off :: Pixel Binary Bit Source #
Represents value False
or 0
in binary. Often also called a background
pixel.
fromBool :: Bool -> Pixel Binary Bit Source #
Convert a Bool
to a PixelBin
pixel.
>>>
isOn (fromBool True)
True
complement :: Bits a => a -> a #
Reverse all the bits in the argument
toPixelBinary :: (Eq (Pixel cs e), Num (Pixel cs e)) => Pixel cs e -> Pixel Binary Bit Source #
Convert any pixel to binary pixel.
toImageBinary :: (Array arr cs e, Array arr Binary Bit, Eq (Pixel cs e)) => Image arr cs e -> Image arr Binary Bit Source #
Convert any image to binary image.
fromImageBinary :: (Array arr Binary Bit, Array arr Y Word8) => Image arr Binary Bit -> Image arr Y Word8 Source #
Convert a Binary image to Luma image
Complex
Rectangular form
Complex numbers are an algebraic type.
For a complex number z
,
is a number with the magnitude of abs
zz
,
but oriented in the positive real direction, whereas
has the phase of signum
zz
, but unit magnitude.
The Foldable
and Traversable
instances traverse the real part first.
Constructors
~a :+ ~a infix 6 | forms a complex number from its real and imaginary rectangular components. |
Instances
Monad Complex | |
Functor Complex | |
Applicative Complex | |
Foldable Complex | |
Traversable Complex | |
Generic1 Complex | |
Representable Complex | |
Additive Complex | |
Affine Complex | |
Complicated Complex | |
(RealFloat a, Unbox a) => Vector Vector (Complex a) | |
(RealFloat a, Unbox a) => MVector MVector (Complex a) | |
Eq a => Eq (Complex a) | |
RealFloat a => Floating (Complex a) | |
RealFloat a => Fractional (Complex a) | |
Data a => Data (Complex a) | |
RealFloat a => Num (Complex a) | |
Read a => Read (Complex a) | |
Show a => Show (Complex a) | |
Generic (Complex a) | |
(Default a, RealFloat a) => Default (Complex a) | |
Storable a => Storable (Complex a) | |
NFData a => NFData (Complex a) | |
(RealFloat a, Unbox a) => Unbox (Complex a) | |
type Rep1 Complex | |
type Rep Complex | |
type Diff Complex | |
data MVector s (Complex a) | |
type Rep (Complex a) | |
type Index (Complex a) | |
data Vector (Complex a) | |
realPart :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source #
Extracts the real part of a complex pixel.
imagPart :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source #
Extracts the imaginary part of a complex pixel.
Polar form
mkPolar :: (Applicative (Pixel cs), RealFloat e) => Pixel cs e -> Pixel cs e -> Pixel cs (Complex e) Source #
Form a complex pixel from polar components of magnitude and phase.
polar :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> (Pixel cs e, Pixel cs e) Source #
magnitude :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs e Source #
The nonnegative magnitude of a complex pixel.
Conjugate
conjugate :: (Applicative (Pixel cs), RealFloat e) => Pixel cs (Complex e) -> Pixel cs (Complex e) Source #
The conjugate of a complex pixel.
Re-exports
8-bit unsigned integer type
Instances
16-bit unsigned integer type
Instances
32-bit unsigned integer type
Instances
Bounded Word32 | |
Enum Word32 | |
Eq Word32 | |
Integral Word32 | |
Num Word32 | |
Ord Word32 | |
Read Word32 | |
Real Word32 | |
Show Word32 | |
Ix Word32 | |
Lift Word32 | |
Default Word32 | |
Unpackable Word32 | |
Pixel Pixel32 | |
LumaPlaneExtractable Pixel32 | |
PackeablePixel Pixel32 | |
Storable Word32 | |
Bits Word32 | |
FiniteBits Word32 | |
NFData Word32 | |
Hashable Word32 | |
Prim Word32 | |
Unbox Word32 | |
Elt Word32 | |
IArray UArray Word32 | |
Vector Vector Word32 | |
MVector MVector Word32 | |
MArray (STUArray s) Word32 (ST s) | |
type StorageType Word32 | |
type PixelBaseComponent Pixel32 | |
type PackedRepresentation Pixel32 | |
type Unsigned Word32 | |
type Signed Word32 | |
data Vector Word32 | |
data MVector s Word32 | |
64-bit unsigned integer type
Instances
Bounded Word64 | |
Enum Word64 | |
Eq Word64 | |
Integral Word64 | |
Num Word64 | |
Ord Word64 | |
Read Word64 | |
Real Word64 | |
Show Word64 | |
Ix Word64 | |
Lift Word64 | |
Default Word64 | |
Storable Word64 | |
Bits Word64 | |
FiniteBits Word64 | |
NFData Word64 | |
Hashable Word64 | |
Prim Word64 | |
Unbox Word64 | |
Elt Word64 | |
IArray UArray Word64 | |
Vector Vector Word64 | |
MVector MVector Word64 | |
MArray (STUArray s) Word64 (ST s) | |
type Unsigned Word64 | |
type Signed Word64 | |
data Vector Word64 | |
data MVector s Word64 | |
Orphan instances
Elevator Double Source # | |
Elevator Float Source # | |
Elevator Int Source # | |
Elevator Int8 Source # | |
Elevator Int16 Source # | |
Elevator Int32 Source # | |
Elevator Int64 Source # | |
Elevator Word Source # | |
Elevator Word8 Source # | |
Elevator Word16 Source # | |
Elevator Word32 Source # | |
Elevator Word64 Source # | |
ToYCbCrA RGBA Source # | |
ToYCbCr RGB Source # | |
ToYA YCbCrA Source # | |
ToYA RGBA Source # | |
ToYA HSIA Source # | |
ToY YCbCr Source # | |
ToY X Source # | |
ToY RGB Source # | Computes Luma: |
ToY HSI Source # | |
ToY CMYK Source # | |
ToRGBA YCbCrA Source # | |
ToRGBA YA Source # | |
ToRGBA HSIA Source # | |
ToRGBA CMYKA Source # | |
ToRGB YCbCr Source # | |
ToRGB Y Source # | |
ToRGB HSI Source # | |
ToRGB CMYK Source # | |
ToHSIA YA Source # | |
ToHSIA RGBA Source # | |
ToHSI Y Source # | |
ToHSI RGB Source # | |
ToCMYKA RGBA Source # | |
ToCMYK RGB Source # | |
(Num e, Elevator e, RealFloat e) => Elevator (Complex e) Source # | |