stb-image-redux-0.2.1.2: Image loading and writing microlibrary

Copyright(c) Alexis Williams 2016
LicenseBSD3
Maintainersasinestro@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.STBImage

Description

Much like the original library, the focus of this library is placed on ease of use rather than richness of feature set, thus the rather spartan interface.

Synopsis

Documentation

class Storable a => Color a where Source #

Minimal complete definition

loadImage, writePNG, writeBMP, writeTGA, red, green, blue, alpha

Associated Types

data ColorFlag a :: * Source #

Methods

loadImage :: ColorFlag a -> FilePath -> IO (Either String (Image a)) Source #

loadImage reads the image (with ColorFlag Y, YA, RGB, or RGBA) at the supplied path.

writePNG :: FilePath -> Image a -> IO () Source #

writePNG writes the image passed to it out at the path path in PNG format. The path must include the extension.

writeBMP :: FilePath -> Image a -> IO () Source #

writeBMP writes the image passed to it out at the path path in BMP format. The path must include the extension.

writeTGA :: FilePath -> Image a -> IO () Source #

writeTGA writes the image passed to it out at the path path in TGA format. The path must include the extension.

red :: a -> Word8 Source #

green :: a -> Word8 Source #

blue :: a -> Word8 Source #

alpha :: a -> Word8 Source #

Instances

Color RGBAColor Source # 
Color RGBColor Source # 
Color YAColor Source # 
Color YColor Source # 

data YColor Source #

Constructors

YColor 

Fields

Instances

Eq YColor Source # 

Methods

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

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

Generic YColor Source # 

Associated Types

type Rep YColor :: * -> * #

Methods

from :: YColor -> Rep YColor x #

to :: Rep YColor x -> YColor #

Storable YColor Source # 
Color YColor Source # 
Show (ColorFlag YColor) # 
type Rep YColor Source # 
type Rep YColor = D1 * (MetaData "YColor" "Data.STBImage.ColorTypes" "stb-image-redux-0.2.1.2-2ZVqjFmQgUv4yjq0FpvNHU" False) (C1 * (MetaCons "YColor" PrefixI True) (S1 * (MetaSel (Just Symbol "_yGreyscale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8)))
data ColorFlag YColor Source # 

data YAColor Source #

Constructors

YAColor 

Instances

Eq YAColor Source # 

Methods

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

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

Generic YAColor Source # 

Associated Types

type Rep YAColor :: * -> * #

Methods

from :: YAColor -> Rep YAColor x #

to :: Rep YAColor x -> YAColor #

Storable YAColor Source # 
Color YAColor Source # 
Show (ColorFlag YAColor) # 
type Rep YAColor Source # 
type Rep YAColor = D1 * (MetaData "YAColor" "Data.STBImage.ColorTypes" "stb-image-redux-0.2.1.2-2ZVqjFmQgUv4yjq0FpvNHU" False) (C1 * (MetaCons "YAColor" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_yaGreyscale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "_yaAlpha") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8))))
data ColorFlag YAColor Source # 

data RGBColor Source #

Constructors

RGBColor 

Instances

Eq RGBColor Source # 
Generic RGBColor Source # 

Associated Types

type Rep RGBColor :: * -> * #

Methods

from :: RGBColor -> Rep RGBColor x #

to :: Rep RGBColor x -> RGBColor #

Storable RGBColor Source # 
Color RGBColor Source # 
Show (ColorFlag RGBColor) # 
type Rep RGBColor Source # 
type Rep RGBColor = D1 * (MetaData "RGBColor" "Data.STBImage.ColorTypes" "stb-image-redux-0.2.1.2-2ZVqjFmQgUv4yjq0FpvNHU" False) (C1 * (MetaCons "RGBColor" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rgbRed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8)) ((:*:) * (S1 * (MetaSel (Just Symbol "_rgbGreen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "_rgbBlue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8)))))
data ColorFlag RGBColor Source # 

data RGBAColor Source #

Constructors

RGBAColor 

Instances

Eq RGBAColor Source # 
Generic RGBAColor Source # 

Associated Types

type Rep RGBAColor :: * -> * #

Storable RGBAColor Source # 
Color RGBAColor Source # 
Show (ColorFlag RGBAColor) # 
type Rep RGBAColor Source # 
type Rep RGBAColor = D1 * (MetaData "RGBAColor" "Data.STBImage.ColorTypes" "stb-image-redux-0.2.1.2-2ZVqjFmQgUv4yjq0FpvNHU" False) (C1 * (MetaCons "RGBAColor" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rgbaRed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "_rgbaGreen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rgbaBlue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "_rgbaAlpha") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word8)))))
data ColorFlag RGBAColor Source # 

data Image a Source #

Image is the least opinionated reasonable type to represent an image, just a vector of pixel Colors (laid out top-to-bottom, left-to-right) and a size.

Constructors

Image 

Fields

Instances

(Eq a, Storable a) => Eq (Image a) Source # 

Methods

(==) :: Image a -> Image a -> Bool #

(/=) :: Image a -> Image a -> Bool #

Show (Image a) Source # 

Methods

showsPrec :: Int -> Image a -> ShowS #

show :: Image a -> String #

showList :: [Image a] -> ShowS #

Generic (Image a) Source # 

Associated Types

type Rep (Image a) :: * -> * #

Methods

from :: Image a -> Rep (Image a) x #

to :: Rep (Image a) x -> Image a #

type Rep (Image a) Source # 
type Rep (Image a) = D1 * (MetaData "Image" "Data.STBImage.Immutable" "stb-image-redux-0.2.1.2-2ZVqjFmQgUv4yjq0FpvNHU" False) (C1 * (MetaCons "Image" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pixels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Vector a))) ((:*:) * (S1 * (MetaSel (Just Symbol "_width") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_height") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))

flipImage :: Storable a => Image a -> Image a Source #

Utility function to flip images, e.g. for use with OpenGL