Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module expose a common "metadata" storage for various image type. Different format can generate different metadatas, and write only a part of them.
Since version 3.2.5
Synopsis
- data Metadatas
- data Keys a where
- Gamma :: Keys Double
- ColorSpace :: Keys ColorSpace
- Format :: Keys SourceFormat
- DpiX :: Keys Word
- DpiY :: Keys Word
- Width :: Keys Word
- Height :: Keys Word
- Title :: Keys String
- Description :: Keys String
- Author :: Keys String
- Copyright :: Keys String
- Software :: Keys String
- Comment :: Keys String
- Disclaimer :: Keys String
- Source :: Keys String
- Warning :: Keys String
- Exif :: !ExifTag -> Keys ExifData
- Unknown :: !String -> Keys Value
- data Value
- data Elem k = forall a.(Show a, NFData a) => !(k a) :=> a
- data SourceFormat
- data ColorSpace
- lookup :: Keys a -> Metadatas -> Maybe a
- empty :: Metadatas
- insert :: (Show a, NFData a) => Keys a -> a -> Metadatas -> Metadatas
- delete :: Keys a -> Metadatas -> Metadatas
- singleton :: (Show a, NFData a) => Keys a -> a -> Metadatas
- foldl' :: (acc -> Elem Keys -> acc) -> acc -> Metadatas -> acc
- foldMap :: Monoid m => (Elem Keys -> m) -> Metadatas -> m
- mkDpiMetadata :: Word -> Metadatas
- mkSizeMetadata :: Integral n => n -> n -> Metadatas
- basicMetadata :: Integral nSize => SourceFormat -> nSize -> nSize -> Metadatas
- simpleMetadata :: (Integral nSize, Integral nDpi) => SourceFormat -> nSize -> nSize -> nDpi -> nDpi -> Metadatas
- extractExifMetas :: Metadatas -> [(ExifTag, ExifData)]
- dotsPerMeterToDotPerInch :: Word -> Word
- dotPerInchToDotsPerMeter :: Word -> Word
- dotsPerCentiMeterToDotPerInch :: Word -> Word
Types
Dependent storage used for metadatas. All metadatas of a given kind are unique within this container.
The current data structure is based on list, so bad performances can be expected.
Store various additional information about an image. If something is not recognized, it can be stored in an unknown tag.
DpiX
Dot per inch on this x axis.DpiY
Dot per inch on this y axis.Width
Image width in pixel. Relying on the metadata for this information can avoid the full decompression of the image. Ignored for image writing.Height
Image height in pixels. Relying on the metadata for this information can void the full decompression of the image. Ignored for image writing.ColorProfile
An unparsed ICC color profile. Currently only supported by the Bitmap format.Unknown
unlikely to be decoded, but usefull for metadata writingExif
Exif tag and associated data.
Gamma :: Keys Double | |
ColorSpace :: Keys ColorSpace | |
Format :: Keys SourceFormat | |
DpiX :: Keys Word | |
DpiY :: Keys Word | |
Width :: Keys Word | |
Height :: Keys Word | |
Title :: Keys String | |
Description :: Keys String | |
Author :: Keys String | |
Copyright :: Keys String | |
Software :: Keys String | |
Comment :: Keys String | |
Disclaimer :: Keys String | |
Source :: Keys String | |
Warning :: Keys String | |
Exif :: !ExifTag -> Keys ExifData | |
Unknown :: !String -> Keys Value |
Encode values for unknown information
Element describing a metadata and it's (typed) associated value.
data SourceFormat Source #
Type describing the original file format of the file.
Instances
Eq SourceFormat Source # | |
Defined in Codec.Picture.Metadata (==) :: SourceFormat -> SourceFormat -> Bool # (/=) :: SourceFormat -> SourceFormat -> Bool # | |
Show SourceFormat Source # | |
Defined in Codec.Picture.Metadata showsPrec :: Int -> SourceFormat -> ShowS # show :: SourceFormat -> String # showList :: [SourceFormat] -> ShowS # | |
NFData SourceFormat Source # | |
Defined in Codec.Picture.Metadata rnf :: SourceFormat -> () # |
data ColorSpace Source #
The same color values may result in slightly different colors on different devices. To get consistent colors accross multiple devices we need a way of mapping color values from a source device into their equivalents on the target device.
The solution is essentially to define, for each device, a family of mappings that convert between device colors and standard CIEXYZ or CIELAB colors. The collection of mappings for a device is known as the 'color-profile' of that device, and each color-profile can be thought of as describing a 'color-space'.
If we know the color-space of the input pixels, and the color space of the output device, then we can convert the colors in the image to their equivalents on the output device.
JuicyPixels does not parse color-profiles or attempt to perform color correction.
The following color space types are recognised:
- sRGB: Standard RGB color space.
- Windows BMP color space: Color space information embedded within a V4 Windows BMP file.
- ICC profile: An ICC color profile.
Instances
Eq ColorSpace Source # | |
Defined in Codec.Picture.Metadata (==) :: ColorSpace -> ColorSpace -> Bool # (/=) :: ColorSpace -> ColorSpace -> Bool # | |
Show ColorSpace Source # | |
Defined in Codec.Picture.Metadata showsPrec :: Int -> ColorSpace -> ShowS # show :: ColorSpace -> String # showList :: [ColorSpace] -> ShowS # | |
NFData ColorSpace Source # | |
Defined in Codec.Picture.Metadata rnf :: ColorSpace -> () # |
Functions
insert :: (Show a, NFData a) => Keys a -> a -> Metadatas -> Metadatas Source #
Insert an element in the metadatas, if an element with the same key is present, it is overwritten.
delete :: Keys a -> Metadatas -> Metadatas Source #
Remove an element of the given keys from the metadatas. If not present does nothing.
singleton :: (Show a, NFData a) => Keys a -> a -> Metadatas Source #
Create metadatas with a single element.
Folding
foldl' :: (acc -> Elem Keys -> acc) -> acc -> Metadatas -> acc Source #
Strict left fold of the metadatas
Helper functions
mkDpiMetadata :: Word -> Metadatas Source #
Create metadatas indicating the resolution, with DpiX == DpiY
mkSizeMetadata :: Integral n => n -> n -> Metadatas Source #
Create metadatas holding width and height information.
basicMetadata :: Integral nSize => SourceFormat -> nSize -> nSize -> Metadatas Source #
Create simple metadatas with Format, Width & Height
simpleMetadata :: (Integral nSize, Integral nDpi) => SourceFormat -> nSize -> nSize -> nDpi -> nDpi -> Metadatas Source #
Create simple metadatas with Format, Width, Height, DpiX & DpiY
Conversion functions
dotsPerMeterToDotPerInch :: Word -> Word Source #
Conversion from dpm to dpi
dotPerInchToDotsPerMeter :: Word -> Word Source #
Conversion from dpi to dpm
dotsPerCentiMeterToDotPerInch :: Word -> Word Source #
Conversion dpcm -> dpi