JuicyPixels-3.3.3: Picture loading/serialization (in png, jpeg, bitmap, gif, tga, tiff and radiance)

Safe HaskellNone
LanguageHaskell2010

Codec.Picture.Png.Internal.Type

Contents

Description

Low level png module, you should import Internal instead.

Synopsis

Documentation

data PngIHdr Source #

Generic header used in PNG images.

Constructors

PngIHdr 

Fields

Instances
Show PngIHdr Source # 
Instance details

Defined in Codec.Picture.Png.Internal.Type

Binary PngIHdr Source # 
Instance details

Defined in Codec.Picture.Png.Internal.Type

Methods

put :: PngIHdr -> Put #

get :: Get PngIHdr #

putList :: [PngIHdr] -> Put #

data PngFilter Source #

The pixels value should be : +---+---+ | c | b | +---+---+ | a | x | +---+---+ x being the current filtered pixel

Constructors

FilterNone

Filt(x) = Orig(x), Recon(x) = Filt(x)

FilterSub

Filt(x) = Orig(x) - Orig(a), Recon(x) = Filt(x) + Recon(a)

FilterUp

Filt(x) = Orig(x) - Orig(b), Recon(x) = Filt(x) + Recon(b)

FilterAverage

Filt(x) = Orig(x) - floor((Orig(a) + Orig(b)) / 2), Recon(x) = Filt(x) + floor((Recon(a) + Recon(b)) / 2)

FilterPaeth

Filt(x) = Orig(x) - PaethPredictor(Orig(a), Orig(b), Orig(c)), Recon(x) = Filt(x) + PaethPredictor(Recon(a), Recon(b), Recon(c))

type PngPalette = Palette' PixelRGB8 Source #

Palette with indices beginning at 0 to elemcount - 1

data PngImageType Source #

What kind of information is encoded in the IDAT section of the PngFile

newtype PngGamma Source #

Constructors

PngGamma 

Fields

Instances
Binary PngGamma Source # 
Instance details

Defined in Codec.Picture.Png.Internal.Type

Methods

put :: PngGamma -> Put #

get :: Get PngGamma #

putList :: [PngGamma] -> Put #

data PngUnit Source #

Constructors

PngUnitUnknown

0 value

PngUnitMeter

1 value

Instances
Binary PngUnit Source # 
Instance details

Defined in Codec.Picture.Png.Internal.Type

Methods

put :: PngUnit -> Put #

get :: Get PngUnit #

putList :: [PngUnit] -> Put #

data APngFrameDisposal Source #

Encoded in a Word8

Constructors

APngDisposeNone

No disposal is done on this frame before rendering the next; the contents of the output buffer are left as is. Has Value 0

APngDisposeBackground

The frame's region of the output buffer is to be cleared to fully transparent black before rendering the next frame. Has Value 1

APngDisposePrevious

the frame's region of the output buffer is to be reverted to the previous contents before rendering the next frame. Has Value 2

data APngBlendOp Source #

Encoded in a Word8

Constructors

APngBlendSource

Overwrite output buffer. has value '0'

APngBlendOver

Alpha blend to the output buffer. Has value '1'

parsePalette :: PngRawChunk -> Either String PngPalette Source #

Parse a palette from a png chunk.

pngComputeCrc :: [ByteString] -> Word32 Source #

Compute the CRC of a raw buffer, as described in annex D of the PNG specification.

pLTESignature :: ChunkSignature Source #

Signature for a palette chunk in the pgn file. Must occure before iDAT.

iDATSignature :: ChunkSignature Source #

Signature for a data chuck (with image parts in it)

iENDSignature :: ChunkSignature Source #

Signature for the last chunk of a png image, telling the end.

Low level types

type ChunkSignature = ByteString Source #

Value used to identify a png chunk, must be 4 bytes long.

data PngRawImage Source #

Raw parsed image which need to be decoded.

Constructors

PngRawImage 

Fields

Instances
Binary PngRawImage Source # 
Instance details

Defined in Codec.Picture.Png.Internal.Type

data PngChunk Source #

PNG chunk representing some extra information found in the parsed file.

Constructors

PngChunk 

Fields

data PngRawChunk Source #

Data structure during real png loading/parsing

Instances
Binary PngRawChunk Source # 
Instance details

Defined in Codec.Picture.Png.Internal.Type

data PngLowLevel a Source #

Low level access to PNG information

Constructors

PngLowLevel 

Fields