Copyright | © 2016–present Mark Karpov |
---|---|
License | BSD 3 clause |
Maintainer | Mark Karpov <markkarpov92@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Core types and definitions for flexible generation of identicons. Please see the Graphics.Identicon.Primitive module for a collection of building blocks to code layers of your identicon.
A basic complete example looks like this:
import Codec.Picture import Data.ByteString (ByteString) import Data.Proxy import Data.Word (Word8) import Graphics.Identicon import Graphics.Identicon.Primitive myImageType :: Proxy (Identicon 4 :+ Consumer 4) myImageType = Proxy myImpl = Identicon :+ a where a :: Word8 -> Word8 -> Word8 -> Word8 -> Layer a r g b n = rsym $ onGrid 6 6 n $ circle $ gradientLR (edge . mid) black (PixelRGB8 r g b) myGenerator :: Int -> Int -> ByteString -> Maybe (Image PixelRGB8) myGenerator = renderIdenticon myImageType myImpl
myGenerator
takes the desired width, height, and a hash that should
have at least 4 bytes in it and returns an identicon corresponding to
that hash or Nothing
if the hash has less than 4 bytes in it or when
width/height don't make sense. The identicon has randomly placed circle
with gradient filling changing (horizontally) from black to some color
and back to black. The circle is mirrored 4 times, and every repetition
is rotated by 90°. This identicon consumes 4 bytes and has one layer.
Synopsis
- data Identicon (n :: Nat) = Identicon
- data Consumer (n :: Nat)
- data a :+ b = a :+ b
- newtype Layer = Layer {}
- type family BytesAvailable a :: Nat where ...
- type family BytesConsumed a :: Nat where ...
- type family Implementation a where ...
- type family ToLayer (n :: Nat) where ...
- class Renderable a where
- render :: Proxy a -> Implementation a -> Int -> Int -> ByteString -> (ByteString, Int -> Int -> PixelRGB8)
- class ApplyBytes a where
- applyBytes :: a -> ByteString -> (ByteString, Layer)
- renderIdenticon :: forall a. (Renderable a, KnownNat (BytesAvailable a), BytesAvailable a ~ BytesConsumed a) => Proxy a -> Implementation a -> Int -> Int -> ByteString -> Maybe (Image PixelRGB8)
Basic types
data Identicon (n :: Nat) Source #
Identicon
is a type that represents an identicon consisting of zero
layers. The type is parametrized over a phantom type n
which is a
natural number on the type level that represents the number of bytes that
should be provided to generate this type of identicon. Bytes typically
come from some sort of hash that has a fixed size.
Instances
Renderable (Identicon n) Source # | |
Defined in Graphics.Identicon render :: Proxy (Identicon n) -> Implementation (Identicon n) -> Int -> Int -> ByteString -> (ByteString, Int -> Int -> PixelRGB8) Source # |
data Consumer (n :: Nat) Source #
Consumer
is a type that represents an entity that consumes bytes that
are available for identicon generation. It's parametrized over a phantom
type n
which is a natural number on the type level that represents the
number of bytes that this entity consumes. At this moment, a Consumer
always adds one Layer
to an Identicon
when attached to it. The number
of bytes, specified as type parameter of Identicon
type must be
completely consumed by a collection of consumers attached to it. To
attach a consumer to Identicon
, you use the (
type operator, see
below.:+
)
Instances
(Renderable a, ApplyBytes (ToLayer n)) => Renderable (a :+ Consumer n) Source # | |
Defined in Graphics.Identicon |
The (
type operator is used to attach :+
)Consumer
s to
Identicon
, thus adding layers to it and exhausting the bytes that are
available for identicon generation. An example of identicon that can be
generated from 16 byte hash is shown below:
type Icon = Identicon 16 :+ Consumer 5 :+ Consumer 5 :+ Consumer 6
The identicon above has three layers.
a :+ b infixl 8 |
Instances
(Renderable a, ApplyBytes (ToLayer n)) => Renderable (a :+ Consumer n) Source # | |
Defined in Graphics.Identicon |
Layer
is the basic building block of an identicon. It's a function
that takes the following arguments (in order):
- Width of identicon
- Height of identicon
- Position on X axis
- Position on Y axis
…and returns a PixelRGB8
value. In this library, an identicon is
generated as a “superposition” of several Layers
.
Instances
Monoid Layer Source # | |
Semigroup Layer Source # | |
ApplyBytes Layer Source # | |
Defined in Graphics.Identicon applyBytes :: Layer -> ByteString -> (ByteString, Layer) Source # |
type family BytesAvailable a :: Nat where ... Source #
The BytesAvailable
type function calculates how many bytes are
available for consumption in a given identicon.
BytesAvailable (Identicon n) = n | |
BytesAvailable (x :+ y) = BytesAvailable x |
type family BytesConsumed a :: Nat where ... Source #
The BytesConsumed
type function calculates how many bytes are
consumed in a given identicon.
BytesConsumed (Identicon n) = 0 | |
BytesConsumed (Consumer n) = n | |
BytesConsumed (x :+ y) = BytesConsumed x + BytesConsumed y |
type family Implementation a where ... Source #
The Implementation
type function returns the type of the code which
can implement the given identicon.
Implementation (Identicon n) = Identicon n | |
Implementation (a :+ Consumer n) = Implementation a :+ ToLayer n |
type family ToLayer (n :: Nat) where ... Source #
The ToLayer
type function calculates type that a layer-producing
function should have to consume the given number of bytes n
.
Identicon rendering
class Renderable a where Source #
Identicons that can be rendered as an image implement this class.
:: Proxy a | A |
-> Implementation a | Corresponding implementation |
-> Int | Width in pixels |
-> Int | Height in pixels |
-> ByteString | Bytes to consume |
-> (ByteString, Int -> Int -> PixelRGB8) | The rest of bytes and producing function |
Instances
Renderable (Identicon n) Source # | |
Defined in Graphics.Identicon render :: Proxy (Identicon n) -> Implementation (Identicon n) -> Int -> Int -> ByteString -> (ByteString, Int -> Int -> PixelRGB8) Source # | |
(Renderable a, ApplyBytes (ToLayer n)) => Renderable (a :+ Consumer n) Source # | |
Defined in Graphics.Identicon |
class ApplyBytes a where Source #
Consume bytes from a strict ByteString
and apply them to a function
that takes Word8
until it produces a Layer
.
:: a | Function that produces a layer |
-> ByteString | Bytes to consume |
-> (ByteString, Layer) | The rest of |
Instances
ApplyBytes Layer Source # | |
Defined in Graphics.Identicon applyBytes :: Layer -> ByteString -> (ByteString, Layer) Source # | |
ApplyBytes f => ApplyBytes (Word8 -> f) Source # | |
Defined in Graphics.Identicon applyBytes :: (Word8 -> f) -> ByteString -> (ByteString, Layer) Source # |
:: forall a. (Renderable a, KnownNat (BytesAvailable a), BytesAvailable a ~ BytesConsumed a) | |
=> Proxy a | Type that defines an identicon |
-> Implementation a | Implementation that generates layers |
-> Int | Width in pixels |
-> Int | Height in pixels |
-> ByteString | Collection of bytes to use, should be long enough |
-> Maybe (Image PixelRGB8) | Rendered identicon, or |
Render an identicon. The function returns Nothing
if given
ByteString
is too short or when width or height is lesser than 1.