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 decoding implementation.
Note: This is an internal module not subject to PVP adherence.
Synopsis
- data DecodeConfig = DecodeConfig {
- punch :: Float
- outputWidth :: Int
- outputHeight :: Int
- data DecodeError
- decodeConfigDefault :: DecodeConfig
- decodeRGB8 :: ByteString -> Either DecodeError (Image PixelRGB8)
- decodeRGB8WithConfig :: DecodeConfig -> ByteString -> Either DecodeError (Image PixelRGB8)
- decodeLinear :: ByteString -> Either DecodeError (Image PixelRGBF)
- decodeLinearWithConfig :: DecodeConfig -> ByteString -> Either DecodeError (Image PixelRGBF)
- decodePixel :: Vector PixelRGBF -> Int -> Int -> Int -> Int -> Int -> Int -> PixelRGBF
- base83DecodeTagged :: ByteString -> Either DecodeError Int
Documentation
data DecodeConfig Source #
Configuration for how to decode a blurhash to an image.
>>>
let myDecodeConfig = decodeConfigDefault { punch = 1.1, outputWidth = 64, outputHeight = 64}
DecodeConfig | |
|
Instances
Show DecodeConfig Source # | |
Defined in Codec.Picture.Blurhash.Internal.Decode showsPrec :: Int -> DecodeConfig -> ShowS # show :: DecodeConfig -> String # showList :: [DecodeConfig] -> ShowS # | |
Generic DecodeConfig Source # | |
Defined in Codec.Picture.Blurhash.Internal.Decode type Rep DecodeConfig :: Type -> Type # from :: DecodeConfig -> Rep DecodeConfig x # to :: Rep DecodeConfig x -> DecodeConfig # | |
type Rep DecodeConfig Source # | |
Defined in Codec.Picture.Blurhash.Internal.Decode type Rep DecodeConfig = D1 (MetaData "DecodeConfig" "Codec.Picture.Blurhash.Internal.Decode" "JuicyPixels-blurhash-0.1.0.0-DaqpokmttsPFp5F95koWnn" False) (C1 (MetaCons "DecodeConfig" PrefixI True) (S1 (MetaSel (Just "punch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float) :*: (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "outputHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) |
data DecodeError Source #
Decoding error types.
InvalidCharacterError Word8 | The provided blurhash included an un-decodable byte. |
InvalidHashLength | The provided blurhash length was wrong. |
Instances
Show DecodeError Source # | |
Defined in Codec.Picture.Blurhash.Internal.Decode showsPrec :: Int -> DecodeError -> ShowS # show :: DecodeError -> String # showList :: [DecodeError] -> ShowS # | |
Generic DecodeError Source # | |
Defined in Codec.Picture.Blurhash.Internal.Decode type Rep DecodeError :: Type -> Type # from :: DecodeError -> Rep DecodeError x # to :: Rep DecodeError x -> DecodeError # | |
type Rep DecodeError Source # | |
Defined in Codec.Picture.Blurhash.Internal.Decode type Rep DecodeError = D1 (MetaData "DecodeError" "Codec.Picture.Blurhash.Internal.Decode" "JuicyPixels-blurhash-0.1.0.0-DaqpokmttsPFp5F95koWnn" False) (C1 (MetaCons "InvalidCharacterError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8)) :+: C1 (MetaCons "InvalidHashLength" PrefixI False) (U1 :: Type -> Type)) |
decodeConfigDefault :: DecodeConfig Source #
A reasonable default configuration for decoding.
>>>
punch decodeConfigDefault == 1
True
>>>
outputWidth decodeConfigDefault == 32
True
>>>
outputHeight decodeConfigDefault == 32
True
:: ByteString | The blurhash |
-> Either DecodeError (Image PixelRGB8) |
Decode a blurhash into an Image
PixelRGB8
. Calls decodeRGB8WithConfig
with decodeConfigDefault
.
When in doubt, use this function to decode a blurhash.
:: DecodeConfig | |
-> ByteString | The blurhash. |
-> Either DecodeError (Image PixelRGB8) |
Decode a blurhash into an Image
PixelRGB8
given a DecodeConfig
:: ByteString | The blurhash |
-> Either DecodeError (Image PixelRGBF) |
Decode a blurhash into an Image
PixelRGBF
. Calls decodeLinearWithConfig
with decodeConfigDefault
.
Note: Blurhash implementations use a non-naive PixelRGBF
to PixelRGB8
conversion. If your
ultimate goal is to end up with an Image
PixelRGB8
, be careful using this function and
scaling pixels by 255 as you will get different results.
decodeLinearWithConfig Source #
:: DecodeConfig | |
-> ByteString | The blurhash |
-> Either DecodeError (Image PixelRGBF) |
decodePixel :: Vector PixelRGBF -> Int -> Int -> Int -> Int -> Int -> Int -> PixelRGBF Source #
Helper function to decode a single pixel.
base83DecodeTagged :: ByteString -> Either DecodeError Int Source #
Helper function to decode a base83 value or return an errorl