--------------------------------------------------------------------
-- |
-- Module    : Network.Gravatar
-- Copyright : (c) Galois, Inc. 2008
-- License   : BSD3
--
-- Maintainer: Don Stewart <dons@galois.com>
-- Stability : provisional
-- Portability:
--
--------------------------------------------------------------------
--
-- Return the URL of a gravatar image - an image associated with an
-- email address.
--
-- Simple use:
--
-- > > gravatar "dons@galois.com"
-- > "http://www.gravatar.com/avatar.php?gravatar_id=f21827076a1d0725c4f4bd5a640102e9"
--
-- Optional arguments to specify the maximum classification rating
-- allowed, a size of the image (between 1 and 80 pixels) and a default url
-- to redirect to are provided by 'gravatarWith'.
--

module Network.Gravatar (
    gravatar, gravatarWith
    ,Rating(..)
    ,Size,size
  ) where

import Data.Digest.OpenSSL.MD5
import Data.List
import Data.Char
import Network.URI
import qualified Data.ByteString.Char8 as S

------------------------------------------------------------------------
-- Implementing the gravatar protocol

-- | Classification ratings for gravatars
data Rating = G | PG | R | X
    deriving (Eq,Ord,Bounded,Enum,Show,Read)

-- | An image size in pixels from 1 to 80.
newtype Size = Size Int
    deriving (Eq,Ord,Show)

-- | A smart constructor for the Size type, ensuring it is between 1 and 80
size :: Int -> Maybe Size
size n | n >= 1 && n <= 80 = Just (Size n)
       | otherwise         = Nothing

------------------------------------------------------------------------

baseURL     = "http://www.gravatar.com/avatar.php?"
gravatar_id = "gravatar_id"

-- | Return the url of a gravatar for an
-- email address (a globally recognized avatar).
--
gravatar :: String -> String
gravatar who = gravatarWith who Nothing Nothing Nothing

-- | Construct the url of a gravatar with optional classification
-- rating to limit to, an optional size in pixels, and optional default
-- url to redirect to, should no image be found.
--
gravatarWith :: String
             -> Maybe Rating
             -> Maybe Size
             -> Maybe String
             -> String
gravatarWith who rating' sz' dflt'
             = concat [baseURL ,gravatar_id ,"=" ,(md5sum (S.pack (clean who))),rating,sz,dflt ]
    where
        clean  = let f = reverse . dropWhile isSpace in f . f
        rating = maybe "" (\r        -> "&rating="++show r) rating'
        sz     = maybe "" (\(Size n) -> "&size="++show n) sz'
        dflt   = maybe "" (\r        -> "&default="++escapeURIString isUnreserved  r) dflt'