| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.Libravatar
Description
Libravatar is a decentralized avatar delivery system. Instead of relying on a single centralized provider, it can use DNS records to detect the host of the avatar image. There is a server implementation which anyone can run and host their avatars and there are client libraries for many languages, all free-as-in-freedom software.
This module is a Haskell client library for Libravatar.
Note that this library doesn't actually fetch the image over HTTP. That part
 is left to the various HTTP client packages, such as http-client. What
 this library does is construct the image URL, possibly using DNS queries
 when needed for the decentralization. You can then fetch the image over HTTP
 or use the URL in your web app's HTML page templates, in which case the
 user's web brower will be downloading the image.
Now let's see how it works.
{-# LANGUAGE OverloadedStrings #-}
import Data.Default.Class (def)
import Network.LibravatarExamples:
Email, HTTP, default fallback image (the libravatar logo), default size (80):
>>>avatarUrl (Email "john@doe.org") def>>>{ optSecure = False>>>, optDefault = ImgLibravatarLogo>>>, optSize = DefaultSize>>>}Just "http://cdn.libravatar.org/avatar/bc6a715808d9aae0ddeefb1e47e482a6"
Email, HTTPS, default fallback image, size 100. But now use an email with a domain which has SRV records for avatars:
>>>avatarUrl (Email "fr33domlover@rel4tion.org") def>>>{ optSecure = True>>>, optDefault = ImgLibravatarLogo>>>, optSize = Size 100>>>}Just "https://avatars.rel4tion.org:5679/avatar/e9e9ccabc2a166b1783bd7f4f9ceb376?s=100"
OpenID, HTTPS, specified fallback (special value "retro"), default size (80):
>>>avatarUrl (OpenID "https://examplibre.org/accounts/xyz/id") def>>>{ optSecure = True>>>, optDefault = ImgSpecial SpecialRetro>>>, optSize = DefaultSize>>>}Just "https://seccdn.libravatar.org/avatar/c2cbc5f5a1784fa7105380e550360d73f15c4c1f9c7ca1ac436c45a33027fcd7?d=retro"
(Note that the 2nd example uses dummy SRV records created by the author, and he isn't really running a Libravatar provider. This is just an example, the specific URL here will probably result with 404.)
- data UserAddress
- data SpecialImage
- data DefaultImage
- data Size- = Size Int
- | DefaultSize
 
- data AvatarOptions
- optSecure :: AvatarOptions -> Bool
- optDefault :: AvatarOptions -> DefaultImage
- optSize :: AvatarOptions -> Size
- optTryGravatar :: AvatarOptions -> Bool
- avatarUrl :: UserAddress -> AvatarOptions -> IO (Maybe Text)
Documentation
data UserAddress Source #
User address for which to generate an avatar URL. Email or OpenID.
Constructors
| Email Text | For example  | 
| OpenID Text | For example  | 
data SpecialImage Source #
Special values available for the default image. The comments briefly explain the origin of the image/technique.
Constructors
| SpecialMysteryPerson | A very simple outline of a person (constant image, does not vary by user address). Sometimes referred to as “mystery man”. | 
| SpecialIdenticon | Geometric pattern based on a user address hash. Origin: A visual representation of a hash value, usually of an IP address, that serves to identify a user of a computer system as a form of avatar while protecting the users' privacy. | 
| SpecialMonsterID | A generated monster image with different colors, faces, etc. Origin: A method to generate a unique monster image based upon a certain identifier (IP address, email address, etc.). It can be used to automatically provide personal avatar images in blog comments or other community services. | 
| SpecialWavatar | A generated face with differing features and backgrounds. Origin: Wavatars is a Wordpress plugin that will generate and assign icons to the visitors leaving comments at your site. The icons are based on email, so a given visitor will get the same icon each time they comment. It livens up comment threads and gives people memorable “faces” to aid in following conversation threads. It’s also fun. | 
| SpecialRetro | A generated, 8-bit arcade-style pixelated face. Origin: I don't know :P | 
data DefaultImage Source #
What to do if the user's address isn't found in the Libravatar server's database.
Constructors
| ImgLibravatarLogo | Don't specify a default image, let the server send its default image, which is the Libravatar logo (the orange butterfly). | 
| ImgNotFound | Return HTTP 404 error (i.e. file not found) instead of an image. | 
| ImgSpecial SpecialImage | Use one of the available special images or image generators. | 
| ImgCustom Text | Use the given image URL as the default. | 
Instances
Image size in pixels.
Constructors
| Size Int | Use the given size. Acceptable values are between 1 and 512. Note that this library doesn't check the size you pass here, so make sure you pass a size within that range. | 
| DefaultSize | Use the default size, which is 80 pixels. | 
data AvatarOptions Source #
Avatar details in addition to the user address itself. Define by starting
 with defOpts and override fields using record syntax.
Instances
optSecure :: AvatarOptions -> Bool Source #
Whether the avatar URL should be secure (use HTTPS).
optDefault :: AvatarOptions -> DefaultImage Source #
What to do if the user address isn't found in the Libravatar database.
optSize :: AvatarOptions -> Size Source #
Image size in pixels.
optTryGravatar :: AvatarOptions -> Bool Source #
If an image is not found in the Libravatar database, it can first
 redirect to gravatar in case the image exists there, and only then
 honour the optDefault parameter. This option sets whether Libravatar
 should try gravatar or go straight to the optDefault when an image
 isn't found.
avatarUrl :: UserAddress -> AvatarOptions -> IO (Maybe Text) Source #
Return a URL to the avatar image.
If an error occurs, return Nothing. Currently, this happens only if the
 user address fails to be parsed.
See examples at the top of the page.