Copyright | (c) 2020 Sam Protas |
---|---|
License | BSD3 |
Maintainer | Sam Protas <sam.protas@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Internal Blurhash encoding implementation.
Note: This is an internal module not subject to PVP adherence.
Synopsis
- data EncodeConfig = EncodeConfig {
- componentsX :: !Int
- componentsY :: !Int
- data EncodeError
- encodeConfigDefault :: EncodeConfig
- checkComponent :: Int -> Either EncodeError Int
- encodeDynamic :: DynamicImage -> Either EncodeError ByteString
- encodeDynamicWithConfig :: EncodeConfig -> DynamicImage -> Either EncodeError ByteString
- encodeRGB8 :: Image PixelRGB8 -> Either EncodeError ByteString
- encodeRGB8WithConfig :: EncodeConfig -> Image PixelRGB8 -> Either EncodeError ByteString
- encodeLinear :: Image PixelRGBF -> Either EncodeError ByteString
- encodeLinearWithConfig :: EncodeConfig -> Image PixelRGBF -> Either EncodeError ByteString
- base83EncodeTagged :: Int -> Int -> Either EncodeError Builder
- encodeComponents :: Int -> Int -> Image PixelRGBF -> EncodedComponents
- encodeComponent :: Int -> Int -> Float -> Image PixelRGBF -> PixelRGBF
- data EncodedComponents = EncodedComponents !(DList PixelRGBF) !Float
- encodeDcValue :: PixelRGBF -> Int
- encodeAcValue :: Float -> PixelRGBF -> Int
Documentation
data EncodeConfig Source #
Configuration for how to encode an image into a blurhash.
Create custom configs using record update syntax and encodeConfigDefault
.
>>>
let myEncodeConfig = encodeConfigDefault { componentsX = 4, componentsY = 3 }
EncodeConfig | |
|
Instances
Show EncodeConfig Source # | |
Defined in Codec.Picture.Blurhash.Internal.Encode showsPrec :: Int -> EncodeConfig -> ShowS # show :: EncodeConfig -> String # showList :: [EncodeConfig] -> ShowS # | |
Generic EncodeConfig Source # | |
Defined in Codec.Picture.Blurhash.Internal.Encode type Rep EncodeConfig :: Type -> Type # from :: EncodeConfig -> Rep EncodeConfig x # to :: Rep EncodeConfig x -> EncodeConfig # | |
type Rep EncodeConfig Source # | |
Defined in Codec.Picture.Blurhash.Internal.Encode type Rep EncodeConfig = D1 (MetaData "EncodeConfig" "Codec.Picture.Blurhash.Internal.Encode" "JuicyPixels-blurhash-0.1.0.0-DaqpokmttsPFp5F95koWnn" False) (C1 (MetaCons "EncodeConfig" PrefixI True) (S1 (MetaSel (Just "componentsX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "componentsY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) |
data EncodeError Source #
Encoding error types.
InvalidComponents | The provided config components were invalid. |
B83EncodingError Int Int | The provided number cannot be base83 encoded into the provided length. |
Instances
Show EncodeError Source # | |
Defined in Codec.Picture.Blurhash.Internal.Encode showsPrec :: Int -> EncodeError -> ShowS # show :: EncodeError -> String # showList :: [EncodeError] -> ShowS # | |
Generic EncodeError Source # | |
Defined in Codec.Picture.Blurhash.Internal.Encode type Rep EncodeError :: Type -> Type # from :: EncodeError -> Rep EncodeError x # to :: Rep EncodeError x -> EncodeError # | |
type Rep EncodeError Source # | |
Defined in Codec.Picture.Blurhash.Internal.Encode type Rep EncodeError = D1 (MetaData "EncodeError" "Codec.Picture.Blurhash.Internal.Encode" "JuicyPixels-blurhash-0.1.0.0-DaqpokmttsPFp5F95koWnn" False) (C1 (MetaCons "InvalidComponents" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "B83EncodingError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) |
encodeConfigDefault :: EncodeConfig Source #
A reasonable default configuration for encoding.
>>>
componentsX encodeConfigDefault == 4
True
>>>
componentsY encodeConfigDefault == 4
True
checkComponent :: Int -> Either EncodeError Int Source #
A helper funciton to validate the provided encoding component count.
encodeDynamic :: DynamicImage -> Either EncodeError ByteString Source #
Encode a DynamicImage
to a blurhash. Calls encodeDynamicWithConfig
with encodeConfigDefault
.
Note: Relies on convertRGB8
before proceding with the standard Blurhash algorithm.
encodeDynamicWithConfig :: EncodeConfig -> DynamicImage -> Either EncodeError ByteString Source #
Encode a DynamicImage
to a blurhash with a given an EncodeConfig
.
Note: Relies on convertRGB8
before proceding with the standard Blurhash algorithm.
encodeRGB8 :: Image PixelRGB8 -> Either EncodeError ByteString Source #
Encode an Image
PixelRGB8
to a blurhash. Calls encodeRGB8WithConfig
with encodeConfigDefault
.
Note: This is the most direct port of other language's implementation's default encoding function.
encodeRGB8WithConfig :: EncodeConfig -> Image PixelRGB8 -> Either EncodeError ByteString Source #
Encode an Image
PixelRGB8
to a blurhash given an EncodeConfig
.
Note: This is the most direct port of other languages implementation's encoding function.
encodeLinear :: Image PixelRGBF -> Either EncodeError ByteString Source #
Encode an Image
PixelRGBF
to a blurhash. Calls encodeLinearWithConfig
with encodeConfigDefault
.
Note: Blurhash implementations use a non-naive PixelRGB8
to PixelRGBF
conversion. Beware that using promotePixel
or promoteImage
from ColorConvertible
to convert an Image
PixelRGB8
to an Image
PixelRGBF
before using encodeLinear
will give different results than encodeRGB8
.
encodeLinearWithConfig :: EncodeConfig -> Image PixelRGBF -> Either EncodeError ByteString Source #
Encode an Image
PixelRGBF
to a blurhash given an EncodeConfig
.
Note: Blurhash implementations use a non-naive PixelRGB8
to PixelRGBF
conversion. Beware that using promotePixel
or promoteImage
from ColorConvertible
to convert an Image
PixelRGB8
to an Image
PixelRGBF
before using encodeLinearWithConfig
will give different results than encodeRGB8WithConfig
.
:: Int | toEncode |
-> Int | encoded length |
-> Either EncodeError Builder |
Helper function to encode a base83 value or return an error.
encodeComponents :: Int -> Int -> Image PixelRGBF -> EncodedComponents Source #
Encode encode the color components.
encodeComponent :: Int -> Int -> Float -> Image PixelRGBF -> PixelRGBF Source #
Encode a single color component.
data EncodedComponents Source #
Intermediate data for calculating color components and macAC in one pass.
encodeDcValue :: PixelRGBF -> Int Source #
Helper function for encoding the DC value.