Safe Haskell | None |
---|---|
Language | Haskell2010 |
Low level png module, you should import Internal
instead.
Synopsis
- data PngIHdr = PngIHdr {
- width :: !Word32
- height :: !Word32
- bitDepth :: !Word8
- colourType :: !PngImageType
- compressionMethod :: !Word8
- filterMethod :: !Word8
- interlaceMethod :: !PngInterlaceMethod
- data PngFilter
- data PngInterlaceMethod
- type PngPalette = Palette' PixelRGB8
- data PngImageType
- data PngPhysicalDimension = PngPhysicalDimension {}
- newtype PngGamma = PngGamma {}
- data PngUnit
- data APngAnimationControl = APngAnimationControl {}
- data APngFrameDisposal
- data APngBlendOp
- data APngFrameControl = APngFrameControl {}
- parsePalette :: PngRawChunk -> Either String PngPalette
- pngComputeCrc :: [ByteString] -> Word32
- pLTESignature :: ChunkSignature
- iDATSignature :: ChunkSignature
- iENDSignature :: ChunkSignature
- tRNSSignature :: ChunkSignature
- tEXtSignature :: ChunkSignature
- zTXtSignature :: ChunkSignature
- gammaSignature :: ChunkSignature
- pHYsSignature :: ChunkSignature
- animationControlSignature :: ChunkSignature
- type ChunkSignature = ByteString
- data PngRawImage = PngRawImage {
- header :: PngIHdr
- chunks :: [PngRawChunk]
- data PngChunk = PngChunk {}
- data PngRawChunk = PngRawChunk {}
- data PngLowLevel a = PngLowLevel {}
- chunksWithSig :: PngRawImage -> ChunkSignature -> [ByteString]
- mkRawChunk :: ChunkSignature -> ByteString -> PngRawChunk
Documentation
Generic header used in PNG images.
PngIHdr | |
|
The pixels value should be : +---+---+ | c | b | +---+---+ | a | x | +---+---+ x being the current filtered pixel
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)) |
Instances
Enum PngFilter Source # | |
Defined in Codec.Picture.Png.Internal.Type succ :: PngFilter -> PngFilter # pred :: PngFilter -> PngFilter # fromEnum :: PngFilter -> Int # enumFrom :: PngFilter -> [PngFilter] # enumFromThen :: PngFilter -> PngFilter -> [PngFilter] # enumFromTo :: PngFilter -> PngFilter -> [PngFilter] # enumFromThenTo :: PngFilter -> PngFilter -> PngFilter -> [PngFilter] # | |
Show PngFilter Source # | |
Binary PngFilter Source # | |
data PngInterlaceMethod Source #
Different known interlace methods for PNG image
PngNoInterlace | No interlacing, basic data ordering, line by line from left to right. |
PngInterlaceAdam7 | Use the Adam7 ordering, see |
Instances
Enum PngInterlaceMethod Source # | |
Defined in Codec.Picture.Png.Internal.Type succ :: PngInterlaceMethod -> PngInterlaceMethod # pred :: PngInterlaceMethod -> PngInterlaceMethod # toEnum :: Int -> PngInterlaceMethod # fromEnum :: PngInterlaceMethod -> Int # enumFrom :: PngInterlaceMethod -> [PngInterlaceMethod] # enumFromThen :: PngInterlaceMethod -> PngInterlaceMethod -> [PngInterlaceMethod] # enumFromTo :: PngInterlaceMethod -> PngInterlaceMethod -> [PngInterlaceMethod] # enumFromThenTo :: PngInterlaceMethod -> PngInterlaceMethod -> PngInterlaceMethod -> [PngInterlaceMethod] # | |
Show PngInterlaceMethod Source # | |
Defined in Codec.Picture.Png.Internal.Type showsPrec :: Int -> PngInterlaceMethod -> ShowS # show :: PngInterlaceMethod -> String # showList :: [PngInterlaceMethod] -> ShowS # | |
Binary PngInterlaceMethod Source # | |
Defined in Codec.Picture.Png.Internal.Type put :: PngInterlaceMethod -> Put # get :: Get PngInterlaceMethod # putList :: [PngInterlaceMethod] -> Put # |
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
Instances
Show PngImageType Source # | |
Defined in Codec.Picture.Png.Internal.Type showsPrec :: Int -> PngImageType -> ShowS # show :: PngImageType -> String # showList :: [PngImageType] -> ShowS # | |
Binary PngImageType Source # | |
Defined in Codec.Picture.Png.Internal.Type |
data PngPhysicalDimension Source #
Instances
Binary PngPhysicalDimension Source # | |
Defined in Codec.Picture.Png.Internal.Type put :: PngPhysicalDimension -> Put # get :: Get PngPhysicalDimension # putList :: [PngPhysicalDimension] -> Put # |
PngUnitUnknown | 0 value |
PngUnitMeter | 1 value |
data APngAnimationControl Source #
Instances
Show APngAnimationControl Source # | |
Defined in Codec.Picture.Png.Internal.Type showsPrec :: Int -> APngAnimationControl -> ShowS # show :: APngAnimationControl -> String # showList :: [APngAnimationControl] -> ShowS # |
data APngFrameDisposal Source #
Encoded in a Word8
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 |
Instances
Show APngFrameDisposal Source # | |
Defined in Codec.Picture.Png.Internal.Type showsPrec :: Int -> APngFrameDisposal -> ShowS # show :: APngFrameDisposal -> String # showList :: [APngFrameDisposal] -> ShowS # |
data APngBlendOp Source #
Encoded in a Word8
APngBlendSource | Overwrite output buffer. has value '0' |
APngBlendOver | Alpha blend to the output buffer. Has value '1' |
Instances
Show APngBlendOp Source # | |
Defined in Codec.Picture.Png.Internal.Type showsPrec :: Int -> APngBlendOp -> ShowS # show :: APngBlendOp -> String # showList :: [APngBlendOp] -> ShowS # |
data APngFrameControl Source #
APngFrameControl | |
|
Instances
Show APngFrameControl Source # | |
Defined in Codec.Picture.Png.Internal.Type showsPrec :: Int -> APngFrameControl -> ShowS # show :: APngFrameControl -> String # showList :: [APngFrameControl] -> ShowS # |
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.
PngRawImage | |
|
Instances
Binary PngRawImage Source # | |
Defined in Codec.Picture.Png.Internal.Type |
PNG chunk representing some extra information found in the parsed file.
PngChunk | |
|
data PngRawChunk Source #
Data structure during real png loading/parsing
PngRawChunk | |
|
Instances
Binary PngRawChunk Source # | |
Defined in Codec.Picture.Png.Internal.Type |
chunksWithSig :: PngRawImage -> ChunkSignature -> [ByteString] Source #
mkRawChunk :: ChunkSignature -> ByteString -> PngRawChunk Source #