Copyright | (c) 2020 Sam Protas |
---|---|
License | BSD3 |
Maintainer | Sam Protas <sam.protas@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Blurhash is a very compact represenation of a placeholder for an image.
This library provides a Blurhash encoding and decoding implementation based on the JuicyPixels represenation of images.
For the full Blurhash sales pitch and algorithm explaination see either of:
- The website: https://blurha.sh/
- The central git repo: https://github.com/woltapp/blurhash
An image such as:
Can be encoded as:
LGFFaWYk^6#M@-5c,1Ex@@or[j6o
Which your client can render as:
Synopsis
- encodeDynamic :: DynamicImage -> Either EncodeError ByteString
- encodeRGB8 :: Image PixelRGB8 -> Either EncodeError ByteString
- encodeLinear :: Image PixelRGBF -> Either EncodeError ByteString
- encodeDynamicWithConfig :: EncodeConfig -> DynamicImage -> Either EncodeError ByteString
- encodeRGB8WithConfig :: EncodeConfig -> Image PixelRGB8 -> Either EncodeError ByteString
- encodeLinearWithConfig :: EncodeConfig -> Image PixelRGBF -> Either EncodeError ByteString
- encodeConfigDefault :: EncodeConfig
- data EncodeConfig
- componentsX :: EncodeConfig -> Int
- componentsY :: EncodeConfig -> Int
- data EncodeError
- decodeRGB8 :: ByteString -> Either DecodeError (Image PixelRGB8)
- decodeLinear :: ByteString -> Either DecodeError (Image PixelRGBF)
- decodeRGB8WithConfig :: DecodeConfig -> ByteString -> Either DecodeError (Image PixelRGB8)
- decodeLinearWithConfig :: DecodeConfig -> ByteString -> Either DecodeError (Image PixelRGBF)
- decodeConfigDefault :: DecodeConfig
- data DecodeConfig
- punch :: DecodeConfig -> Float
- outputWidth :: DecodeConfig -> Int
- outputHeight :: DecodeConfig -> Int
- data DecodeError
Example Use
First some imports.
>>>
:set -XOverloadedStrings
>>>
import Codec.Picture (readImage)
>>>
import qualified Codec.Picture.Blurhash as BH
>>>
import Data.ByteString.Lazy (ByteString)
Given a an image filepath (imgFilePath :: FilePath)
.
>>>
:{
do Right img <- readImage imgFilePath print $ BH.encodeDynamic img :} Right "UBMOZfK1GG%LBBNG,;Rj2skq=eE1s9n4S5Na"
Now you can store this nice compact encoding in a database column and send it to the client along with the asset path to the full size image.
If you're lucky enough to write your client in Haskell, you receive that encoding and draw a Blurhash placeholder while the full asset is fetched.
>>>
let Right myBlurryPlaceholderImg = BH.decodeRGB8 "UBMOZfK1GG%LBBNG,;Rj2skq=eE1s9n4S5Na"
Encoding Images
The Blurhash algorithm natively supports encoding Image
PixelRGB8
and Image
PixelRGBF
. This library additionally supports encoding a DynamicImage
via conversion to Image
PixelRGB8
.
Default
Encode various image representations to a blurhash using encodeConfigDefault
.
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.
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.
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
.
Custom
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.
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.
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
.
Configuration
encodeConfigDefault :: EncodeConfig Source #
A reasonable default configuration for encoding.
>>>
componentsX encodeConfigDefault == 4
True
>>>
componentsY encodeConfigDefault == 4
True
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 }
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))) |
componentsX :: EncodeConfig -> Int Source #
Number of components along the X axis.
See EncodeConfig
for example use with record update syntax.
componentsY :: EncodeConfig -> Int Source #
Number of components along the Y axis.
See EncodeConfig
for example use with record update syntax.
Errors
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))) |
Decoding To Images
Default
Decode a blurhash to various image representations using decodeConfigDefault
.
:: 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.
:: 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.
Custom
:: DecodeConfig | |
-> ByteString | The blurhash. |
-> Either DecodeError (Image PixelRGB8) |
Decode a blurhash into an Image
PixelRGB8
given a DecodeConfig
decodeLinearWithConfig Source #
:: DecodeConfig | |
-> ByteString | The blurhash |
-> Either DecodeError (Image PixelRGBF) |
Configuration
decodeConfigDefault :: DecodeConfig Source #
A reasonable default configuration for decoding.
>>>
punch decodeConfigDefault == 1
True
>>>
outputWidth decodeConfigDefault == 32
True
>>>
outputHeight decodeConfigDefault == 32
True
data DecodeConfig Source #
Configuration for how to decode a blurhash to an image.
>>>
let myDecodeConfig = decodeConfigDefault { punch = 1.1, outputWidth = 64, outputHeight = 64}
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)))) |
punch :: DecodeConfig -> Float Source #
Adjusts the contrast of the decoded image. Larger values mean more contrast.
See DecodeConfig
for example use with record update syntax.
outputWidth :: DecodeConfig -> Int Source #
Output image pixel width.
See DecodeConfig
for example use with record update syntax.
outputHeight :: DecodeConfig -> Int Source #
Output image pixel height.
See DecodeConfig
for example use with record update syntax.
Errors
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)) |