{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Yesod.Auth.GoogleEmail2
{-# DEPRECATED "Google+ is being shut down, please migrate to Google Sign-in https://pbrisbin.com/posts/googleemail2_deprecation/" #-}
(
authGoogleEmail
, authGoogleEmailSaveToken
, forwardUrl
, Token(..)
, getUserAccessToken
, getPerson
, Person(..)
, Name(..)
, Gender(..)
, PersonImage(..)
, resizePersonImage
, RelationshipStatus(..)
, PersonURI(..)
, PersonURIType(..)
, Organization(..)
, OrganizationType(..)
, Place(..)
, Email(..)
, EmailType(..)
, pid
) where
import Yesod.Auth (Auth, AuthHandler,
AuthPlugin (AuthPlugin),
AuthRoute, Creds (Creds),
Route (PluginR), YesodAuth,
logoutDest, runHttpRequest,
setCredsRedirect)
import qualified Yesod.Auth.Message as Msg
import Yesod.Core (HandlerSite, MonadHandler,
TypedContent, addMessage,
getRouteToParent, getUrlRender,
getYesod, invalidArgs, liftIO,
liftSubHandler, lookupGetParam,
lookupSession, notFound, redirect,
setSession, toHtml, whamlet, (.:))
import Blaze.ByteString.Builder (fromByteString, toByteString)
import Control.Applicative ((<$>), (<*>))
import Control.Arrow (second)
import Control.Monad (unless, when)
import Control.Monad.IO.Class (MonadIO)
import qualified Crypto.Nonce as Nonce
import Data.Aeson ((.:?))
import qualified Data.Aeson as A
#if MIN_VERSION_aeson(1,0,0)
import qualified Data.Aeson.Text as A
#else
import qualified Data.Aeson.Encode as A
#endif
import Data.Aeson.Parser (json')
import Data.Aeson.Types (FromJSON (parseJSON), parseEither,
parseMaybe, withObject, withText)
import Data.Conduit
import Data.Conduit.Attoparsec (sinkParser)
import Data.Maybe (fromMaybe)
import Data.Monoid (mappend)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TL
import Network.HTTP.Client (Manager, requestHeaders,
responseBody, urlEncodedBody)
import qualified Network.HTTP.Client as HTTP
import Network.HTTP.Client.Conduit (Request, bodyReaderSource)
import Network.HTTP.Conduit (http)
import Network.HTTP.Types (renderQueryText)
import System.IO.Unsafe (unsafePerformIO)
#if MIN_VERSION_aeson(2, 0, 0)
import qualified Data.Aeson.Key
import qualified Data.Aeson.KeyMap
#else
import qualified Data.HashMap.Strict as M
#endif
pid :: Text
pid :: Text
pid = Text
"googleemail2"
forwardUrl :: AuthRoute
forwardUrl :: AuthRoute
forwardUrl = Text -> Texts -> AuthRoute
PluginR Text
pid [Text
"forward"]
csrfKey :: Text
csrfKey :: Text
csrfKey = Text
"_GOOGLE_CSRF_TOKEN"
getCsrfToken :: MonadHandler m => m (Maybe Text)
getCsrfToken :: m (Maybe Text)
getCsrfToken = Text -> m (Maybe Text)
forall (m :: * -> *). MonadHandler m => Text -> m (Maybe Text)
lookupSession Text
csrfKey
accessTokenKey :: Text
accessTokenKey :: Text
accessTokenKey = Text
"_GOOGLE_ACCESS_TOKEN"
getUserAccessToken :: MonadHandler m => m (Maybe Token)
getUserAccessToken :: m (Maybe Token)
getUserAccessToken = (Text -> Token) -> Maybe Text -> Maybe Token
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Text
t -> Text -> Text -> Token
Token Text
t Text
"Bearer") (Maybe Text -> Maybe Token) -> m (Maybe Text) -> m (Maybe Token)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> m (Maybe Text)
forall (m :: * -> *). MonadHandler m => Text -> m (Maybe Text)
lookupSession Text
accessTokenKey
getCreateCsrfToken :: MonadHandler m => m Text
getCreateCsrfToken :: m Text
getCreateCsrfToken = do
Maybe Text
mtoken <- m (Maybe Text)
forall (m :: * -> *). MonadHandler m => m (Maybe Text)
getCsrfToken
case Maybe Text
mtoken of
Just Text
token -> Text -> m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
token
Maybe Text
Nothing -> do
Text
token <- Generator -> m Text
forall (m :: * -> *). MonadIO m => Generator -> m Text
Nonce.nonce128urlT Generator
defaultNonceGen
Text -> Text -> m ()
forall (m :: * -> *). MonadHandler m => Text -> Text -> m ()
setSession Text
csrfKey Text
token
Text -> m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
token
authGoogleEmail :: YesodAuth m
=> Text
-> Text
-> AuthPlugin m
authGoogleEmail :: Text -> Text -> AuthPlugin m
authGoogleEmail = Bool -> Text -> Text -> AuthPlugin m
forall m. YesodAuth m => Bool -> Text -> Text -> AuthPlugin m
authPlugin Bool
False
authGoogleEmailSaveToken :: YesodAuth m
=> Text
-> Text
-> AuthPlugin m
authGoogleEmailSaveToken :: Text -> Text -> AuthPlugin m
authGoogleEmailSaveToken = Bool -> Text -> Text -> AuthPlugin m
forall m. YesodAuth m => Bool -> Text -> Text -> AuthPlugin m
authPlugin Bool
True
authPlugin :: YesodAuth m
=> Bool
-> Text
-> Text
-> AuthPlugin m
authPlugin :: Bool -> Text -> Text -> AuthPlugin m
authPlugin Bool
storeToken Text
clientID Text
clientSecret =
Text
-> (Text -> Texts -> AuthHandler m TypedContent)
-> ((AuthRoute -> Route m) -> WidgetFor m ())
-> AuthPlugin m
forall master.
Text
-> (Text -> Texts -> AuthHandler master TypedContent)
-> ((AuthRoute -> Route master) -> WidgetFor master ())
-> AuthPlugin master
AuthPlugin Text
pid Text -> Texts -> AuthHandler m TypedContent
forall site.
YesodAuth site =>
Text -> Texts -> AuthHandler site TypedContent
dispatch (AuthRoute -> Route m) -> WidgetFor m ()
forall site.
YesodAuth site =>
(AuthRoute -> Route site) -> WidgetFor site ()
login
where
complete :: AuthRoute
complete = Text -> Texts -> AuthRoute
PluginR Text
pid [Text
"complete"]
getDest :: MonadHandler m
=> (Route Auth -> Route (HandlerSite m))
-> m Text
getDest :: (AuthRoute -> Route (HandlerSite m)) -> m Text
getDest AuthRoute -> Route (HandlerSite m)
tm = do
Text
csrf <- m Text
forall (m :: * -> *). MonadHandler m => m Text
getCreateCsrfToken
Route (HandlerSite m) -> Text
render <- m (Route (HandlerSite m) -> Text)
forall (m :: * -> *).
MonadHandler m =>
m (Route (HandlerSite m) -> Text)
getUrlRender
let qs :: [(Text, Maybe Text)]
qs = ((Text, Text) -> (Text, Maybe Text))
-> [(Text, Text)] -> [(Text, Maybe Text)]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> Maybe Text) -> (Text, Text) -> (Text, Maybe Text)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second Text -> Maybe Text
forall a. a -> Maybe a
Just)
[ (Text
"scope", Text
"email profile")
, (Text
"state", Text
csrf)
, (Text
"redirect_uri", Route (HandlerSite m) -> Text
render (Route (HandlerSite m) -> Text) -> Route (HandlerSite m) -> Text
forall a b. (a -> b) -> a -> b
$ AuthRoute -> Route (HandlerSite m)
tm AuthRoute
complete)
, (Text
"response_type", Text
"code")
, (Text
"client_id", Text
clientID)
, (Text
"access_type", Text
"offline")
]
Text -> m Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> m Text) -> Text -> m Text
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decodeUtf8
(ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
toByteString
(Builder -> ByteString) -> Builder -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Builder
fromByteString ByteString
"https://accounts.google.com/o/oauth2/auth"
Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`Data.Monoid.mappend` Bool -> [(Text, Maybe Text)] -> Builder
renderQueryText Bool
True [(Text, Maybe Text)]
qs
login :: (AuthRoute -> Route site) -> WidgetFor site ()
login AuthRoute -> Route site
tm = do
[whamlet|<a href=@{tm forwardUrl}>_{Msg.LoginGoogle}|]
dispatch :: YesodAuth site
=> Text
-> [Text]
-> AuthHandler site TypedContent
dispatch :: Text -> Texts -> AuthHandler site TypedContent
dispatch Text
"GET" [Text
"forward"] = do
AuthRoute -> Route site
tm <- m (AuthRoute -> Route site)
forall (m :: * -> *).
MonadHandler m =>
m (Route (SubHandlerSite m) -> Route (HandlerSite m))
getRouteToParent
(AuthRoute -> Route (HandlerSite m)) -> m Text
forall (m :: * -> *).
MonadHandler m =>
(AuthRoute -> Route (HandlerSite m)) -> m Text
getDest AuthRoute -> Route site
AuthRoute -> Route (HandlerSite m)
tm m Text -> (Text -> m TypedContent) -> m TypedContent
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> m TypedContent
forall (m :: * -> *) url a.
(MonadHandler m, RedirectUrl (HandlerSite m) url) =>
url -> m a
redirect
dispatch Text
"GET" [Text
"complete"] = do
Maybe Text
mstate <- Text -> m (Maybe Text)
forall (m :: * -> *). MonadHandler m => Text -> m (Maybe Text)
lookupGetParam Text
"state"
case Maybe Text
mstate of
Maybe Text
Nothing -> Texts -> m ()
forall (m :: * -> *) a. MonadHandler m => Texts -> m a
invalidArgs [Text
"CSRF state from Google is missing"]
Just Text
state -> do
Maybe Text
mtoken <- m (Maybe Text)
forall (m :: * -> *). MonadHandler m => m (Maybe Text)
getCsrfToken
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
state Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe Text
mtoken) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ Texts -> m ()
forall (m :: * -> *) a. MonadHandler m => Texts -> m a
invalidArgs [Text
"Invalid CSRF token from Google"]
Maybe Text
mcode <- Text -> m (Maybe Text)
forall (m :: * -> *). MonadHandler m => Text -> m (Maybe Text)
lookupGetParam Text
"code"
Text
code <-
case Maybe Text
mcode of
Maybe Text
Nothing -> do
Maybe Text
merr <- Text -> m (Maybe Text)
forall (m :: * -> *). MonadHandler m => Text -> m (Maybe Text)
lookupGetParam Text
"error"
case Maybe Text
merr of
Maybe Text
Nothing -> Texts -> m Text
forall (m :: * -> *) a. MonadHandler m => Texts -> m a
invalidArgs [Text
"Missing code paramter"]
Just Text
err -> do
site
master <- m site
forall (m :: * -> *). MonadHandler m => m (HandlerSite m)
getYesod
let msg :: Text
msg =
case Text
err of
Text
"access_denied" -> Text
"Access denied"
Text
_ -> Text
"Unknown error occurred: " Text -> Text -> Text
`T.append` Text
err
Text -> Markup -> m ()
forall (m :: * -> *). MonadHandler m => Text -> Markup -> m ()
addMessage Text
"error" (Markup -> m ()) -> Markup -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> Markup
forall a. ToMarkup a => a -> Markup
toHtml Text
msg
Route site -> m Text
forall (m :: * -> *) url a.
(MonadHandler m, RedirectUrl (HandlerSite m) url) =>
url -> m a
redirect (Route site -> m Text) -> Route site -> m Text
forall a b. (a -> b) -> a -> b
$ site -> Route site
forall master. YesodAuth master => master -> Route master
logoutDest site
master
Just Text
c -> Text -> m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
c
Route site -> Text
render <- m (Route site -> Text)
forall (m :: * -> *).
MonadHandler m =>
m (Route (HandlerSite m) -> Text)
getUrlRender
AuthRoute -> Route site
tm <- m (AuthRoute -> Route site)
forall (m :: * -> *).
MonadHandler m =>
m (Route (SubHandlerSite m) -> Route (HandlerSite m))
getRouteToParent
Request
req' <- IO Request -> m Request
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Request -> m Request) -> IO Request -> m Request
forall a b. (a -> b) -> a -> b
$
String -> IO Request
forall (m :: * -> *). MonadThrow m => String -> m Request
HTTP.parseUrlThrow
String
"https://accounts.google.com/o/oauth2/token"
let req :: Request
req =
[(ByteString, ByteString)] -> Request -> Request
urlEncodedBody
[ (ByteString
"code", Text -> ByteString
encodeUtf8 Text
code)
, (ByteString
"client_id", Text -> ByteString
encodeUtf8 Text
clientID)
, (ByteString
"client_secret", Text -> ByteString
encodeUtf8 Text
clientSecret)
, (ByteString
"redirect_uri", Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Route site -> Text
render (Route site -> Text) -> Route site -> Text
forall a b. (a -> b) -> a -> b
$ AuthRoute -> Route site
tm AuthRoute
complete)
, (ByteString
"grant_type", ByteString
"authorization_code")
]
Request
req'
{ requestHeaders :: RequestHeaders
requestHeaders = []
}
Value
value <- Request -> AuthHandler site Value
forall site. Request -> AuthHandler site Value
makeHttpRequest Request
req
token :: Token
token@(Token Text
accessToken' Text
tokenType') <-
case (Value -> Parser Token) -> Value -> Either String Token
forall a b. (a -> Parser b) -> a -> Either String b
parseEither Value -> Parser Token
forall a. FromJSON a => Value -> Parser a
parseJSON Value
value of
Left String
e -> String -> m Token
forall a. HasCallStack => String -> a
error String
e
Right Token
t -> Token -> m Token
forall (m :: * -> *) a. Monad m => a -> m a
return Token
t
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text
tokenType' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"Bearer") (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> m ()
forall a. HasCallStack => String -> a
error (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Unknown token type: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
tokenType'
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
storeToken (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> m ()
forall (m :: * -> *). MonadHandler m => Text -> Text -> m ()
setSession Text
accessTokenKey Text
accessToken'
Request
personValReq <- Token -> m Request
forall (m :: * -> *). MonadIO m => Token -> m Request
personValueRequest Token
token
Value
personValue <- Request -> AuthHandler site Value
forall site. Request -> AuthHandler site Value
makeHttpRequest Request
personValReq
Person
person <- case (Value -> Parser Person) -> Value -> Either String Person
forall a b. (a -> Parser b) -> a -> Either String b
parseEither Value -> Parser Person
forall a. FromJSON a => Value -> Parser a
parseJSON Value
personValue of
Left String
e -> String -> m Person
forall a. HasCallStack => String -> a
error String
e
Right Person
x -> Person -> m Person
forall (m :: * -> *) a. Monad m => a -> m a
return Person
x
Text
email <-
case (Email -> Text) -> [Email] -> Texts
forall a b. (a -> b) -> [a] -> [b]
map Email -> Text
emailValue ([Email] -> Texts) -> [Email] -> Texts
forall a b. (a -> b) -> a -> b
$ (Email -> Bool) -> [Email] -> [Email]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Email
e -> Email -> EmailType
emailType Email
e EmailType -> EmailType -> Bool
forall a. Eq a => a -> a -> Bool
== EmailType
EmailAccount) ([Email] -> [Email]) -> [Email] -> [Email]
forall a b. (a -> b) -> a -> b
$ Person -> [Email]
personEmails Person
person of
[Text
e] -> Text -> m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
e
[] -> String -> m Text
forall a. HasCallStack => String -> a
error String
"No account email"
Texts
x -> String -> m Text
forall a. HasCallStack => String -> a
error (String -> m Text) -> String -> m Text
forall a b. (a -> b) -> a -> b
$ String
"Too many account emails: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Texts -> String
forall a. Show a => a -> String
show Texts
x
Creds (HandlerSite m) -> m TypedContent
forall (m :: * -> *).
(MonadHandler m, YesodAuth (HandlerSite m)) =>
Creds (HandlerSite m) -> m TypedContent
setCredsRedirect (Creds (HandlerSite m) -> m TypedContent)
-> Creds (HandlerSite m) -> m TypedContent
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [(Text, Text)] -> Creds site
forall master. Text -> Text -> [(Text, Text)] -> Creds master
Creds Text
pid Text
email ([(Text, Text)] -> Creds site) -> [(Text, Text)] -> Creds site
forall a b. (a -> b) -> a -> b
$ Value -> [(Text, Text)]
allPersonInfo Value
personValue
dispatch Text
_ Texts
_ = m TypedContent
forall (m :: * -> *) a. MonadHandler m => m a
notFound
makeHttpRequest :: Request -> AuthHandler site A.Value
makeHttpRequest :: Request -> AuthHandler site Value
makeHttpRequest Request
req =
SubHandlerFor (SubHandlerSite m) (HandlerSite m) Value -> m Value
forall (m :: * -> *) a.
MonadHandler m =>
SubHandlerFor (SubHandlerSite m) (HandlerSite m) a -> m a
liftSubHandler (SubHandlerFor (SubHandlerSite m) (HandlerSite m) Value -> m Value)
-> SubHandlerFor (SubHandlerSite m) (HandlerSite m) Value
-> m Value
forall a b. (a -> b) -> a -> b
$ Request
-> (Response BodyReader -> SubHandlerFor Auth site Value)
-> SubHandlerFor Auth site Value
forall master (m :: * -> *) a.
(YesodAuth master, MonadHandler m, HandlerSite m ~ master,
MonadUnliftIO m) =>
Request -> (Response BodyReader -> m a) -> m a
runHttpRequest Request
req ((Response BodyReader -> SubHandlerFor Auth site Value)
-> SubHandlerFor Auth site Value)
-> (Response BodyReader -> SubHandlerFor Auth site Value)
-> SubHandlerFor Auth site Value
forall a b. (a -> b) -> a -> b
$ \Response BodyReader
res ->
ConduitT () Void (SubHandlerFor Auth site) Value
-> SubHandlerFor Auth site Value
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void (SubHandlerFor Auth site) Value
-> SubHandlerFor Auth site Value)
-> ConduitT () Void (SubHandlerFor Auth site) Value
-> SubHandlerFor Auth site Value
forall a b. (a -> b) -> a -> b
$ BodyReader -> ConduitM () ByteString (SubHandlerFor Auth site) ()
forall (m :: * -> *) i.
MonadIO m =>
BodyReader -> ConduitM i ByteString m ()
bodyReaderSource (Response BodyReader -> BodyReader
forall body. Response body -> body
responseBody Response BodyReader
res) ConduitM () ByteString (SubHandlerFor Auth site) ()
-> ConduitM ByteString Void (SubHandlerFor Auth site) Value
-> ConduitT () Void (SubHandlerFor Auth site) Value
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| Parser ByteString Value
-> ConduitM ByteString Void (SubHandlerFor Auth site) Value
forall a (m :: * -> *) b o.
(AttoparsecInput a, MonadThrow m) =>
Parser a b -> ConduitT a o m b
sinkParser Parser ByteString Value
json'
getPerson :: MonadHandler m => Manager -> Token -> m (Maybe Person)
getPerson :: Manager -> Token -> m (Maybe Person)
getPerson Manager
manager Token
token = SubHandlerFor (SubHandlerSite m) (HandlerSite m) (Maybe Person)
-> m (Maybe Person)
forall (m :: * -> *) a.
MonadHandler m =>
SubHandlerFor (SubHandlerSite m) (HandlerSite m) a -> m a
liftSubHandler (SubHandlerFor (SubHandlerSite m) (HandlerSite m) (Maybe Person)
-> m (Maybe Person))
-> SubHandlerFor (SubHandlerSite m) (HandlerSite m) (Maybe Person)
-> m (Maybe Person)
forall a b. (a -> b) -> a -> b
$ (Value -> Parser Person) -> Value -> Maybe Person
forall a b. (a -> Parser b) -> a -> Maybe b
parseMaybe Value -> Parser Person
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Maybe Person)
-> SubHandlerFor (SubHandlerSite m) (HandlerSite m) Value
-> SubHandlerFor (SubHandlerSite m) (HandlerSite m) (Maybe Person)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
Request
req <- Token -> SubHandlerFor (SubHandlerSite m) (HandlerSite m) Request
forall (m :: * -> *). MonadIO m => Token -> m Request
personValueRequest Token
token
Response
(ConduitM
()
ByteString
(SubHandlerFor (SubHandlerSite m) (HandlerSite m))
())
res <- Request
-> Manager
-> SubHandlerFor
(SubHandlerSite m)
(HandlerSite m)
(Response
(ConduitM
()
ByteString
(SubHandlerFor (SubHandlerSite m) (HandlerSite m))
()))
forall (m :: * -> *) i.
MonadResource m =>
Request -> Manager -> m (Response (ConduitM i ByteString m ()))
http Request
req Manager
manager
ConduitT
() Void (SubHandlerFor (SubHandlerSite m) (HandlerSite m)) Value
-> SubHandlerFor (SubHandlerSite m) (HandlerSite m) Value
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT
() Void (SubHandlerFor (SubHandlerSite m) (HandlerSite m)) Value
-> SubHandlerFor (SubHandlerSite m) (HandlerSite m) Value)
-> ConduitT
() Void (SubHandlerFor (SubHandlerSite m) (HandlerSite m)) Value
-> SubHandlerFor (SubHandlerSite m) (HandlerSite m) Value
forall a b. (a -> b) -> a -> b
$ Response
(ConduitM
()
ByteString
(SubHandlerFor (SubHandlerSite m) (HandlerSite m))
())
-> ConduitM
() ByteString (SubHandlerFor (SubHandlerSite m) (HandlerSite m)) ()
forall body. Response body -> body
responseBody Response
(ConduitM
()
ByteString
(SubHandlerFor (SubHandlerSite m) (HandlerSite m))
())
res ConduitM
() ByteString (SubHandlerFor (SubHandlerSite m) (HandlerSite m)) ()
-> ConduitM
ByteString
Void
(SubHandlerFor (SubHandlerSite m) (HandlerSite m))
Value
-> ConduitT
() Void (SubHandlerFor (SubHandlerSite m) (HandlerSite m)) Value
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| Parser ByteString Value
-> ConduitM
ByteString
Void
(SubHandlerFor (SubHandlerSite m) (HandlerSite m))
Value
forall a (m :: * -> *) b o.
(AttoparsecInput a, MonadThrow m) =>
Parser a b -> ConduitT a o m b
sinkParser Parser ByteString Value
json'
)
personValueRequest :: MonadIO m => Token -> m Request
personValueRequest :: Token -> m Request
personValueRequest Token
token = do
Request
req2' <- IO Request -> m Request
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
(IO Request -> m Request) -> IO Request -> m Request
forall a b. (a -> b) -> a -> b
$ String -> IO Request
forall (m :: * -> *). MonadThrow m => String -> m Request
HTTP.parseUrlThrow String
"https://www.googleapis.com/plus/v1/people/me"
Request -> m Request
forall (m :: * -> *) a. Monad m => a -> m a
return Request
req2'
{ requestHeaders :: RequestHeaders
requestHeaders =
[ (HeaderName
"Authorization", Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
"Bearer " Text -> Text -> Text
forall a. Monoid a => a -> a -> a
`mappend` Token -> Text
accessToken Token
token)
]
}
data Token = Token { Token -> Text
accessToken :: Text
, Token -> Text
tokenType :: Text
} deriving (Int -> Token -> String -> String
[Token] -> String -> String
Token -> String
(Int -> Token -> String -> String)
-> (Token -> String) -> ([Token] -> String -> String) -> Show Token
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Token] -> String -> String
$cshowList :: [Token] -> String -> String
show :: Token -> String
$cshow :: Token -> String
showsPrec :: Int -> Token -> String -> String
$cshowsPrec :: Int -> Token -> String -> String
Show, Token -> Token -> Bool
(Token -> Token -> Bool) -> (Token -> Token -> Bool) -> Eq Token
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Token -> Token -> Bool
$c/= :: Token -> Token -> Bool
== :: Token -> Token -> Bool
$c== :: Token -> Token -> Bool
Eq)
instance FromJSON Token where
parseJSON :: Value -> Parser Token
parseJSON = String -> (Object -> Parser Token) -> Value -> Parser Token
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Tokens" ((Object -> Parser Token) -> Value -> Parser Token)
-> (Object -> Parser Token) -> Value -> Parser Token
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> Text -> Token
Token
(Text -> Text -> Token) -> Parser Text -> Parser (Text -> Token)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Control.Applicative.<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"access_token"
Parser (Text -> Token) -> Parser Text -> Parser Token
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Control.Applicative.<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"token_type"
data Gender = Male | Female | OtherGender deriving (Int -> Gender -> String -> String
[Gender] -> String -> String
Gender -> String
(Int -> Gender -> String -> String)
-> (Gender -> String)
-> ([Gender] -> String -> String)
-> Show Gender
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Gender] -> String -> String
$cshowList :: [Gender] -> String -> String
show :: Gender -> String
$cshow :: Gender -> String
showsPrec :: Int -> Gender -> String -> String
$cshowsPrec :: Int -> Gender -> String -> String
Show, Gender -> Gender -> Bool
(Gender -> Gender -> Bool)
-> (Gender -> Gender -> Bool) -> Eq Gender
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Gender -> Gender -> Bool
$c/= :: Gender -> Gender -> Bool
== :: Gender -> Gender -> Bool
$c== :: Gender -> Gender -> Bool
Eq)
instance FromJSON Gender where
parseJSON :: Value -> Parser Gender
parseJSON = String -> (Text -> Parser Gender) -> Value -> Parser Gender
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Gender" ((Text -> Parser Gender) -> Value -> Parser Gender)
-> (Text -> Parser Gender) -> Value -> Parser Gender
forall a b. (a -> b) -> a -> b
$ \Text
t -> Gender -> Parser Gender
forall (m :: * -> *) a. Monad m => a -> m a
return (Gender -> Parser Gender) -> Gender -> Parser Gender
forall a b. (a -> b) -> a -> b
$ case Text
t of
Text
"male" -> Gender
Male
Text
"female" -> Gender
Female
Text
_ -> Gender
OtherGender
data PersonURI =
PersonURI { PersonURI -> Maybe Text
uriLabel :: Maybe Text
, PersonURI -> Maybe Text
uriValue :: Maybe Text
, PersonURI -> Maybe PersonURIType
uriType :: Maybe PersonURIType
} deriving (Int -> PersonURI -> String -> String
[PersonURI] -> String -> String
PersonURI -> String
(Int -> PersonURI -> String -> String)
-> (PersonURI -> String)
-> ([PersonURI] -> String -> String)
-> Show PersonURI
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PersonURI] -> String -> String
$cshowList :: [PersonURI] -> String -> String
show :: PersonURI -> String
$cshow :: PersonURI -> String
showsPrec :: Int -> PersonURI -> String -> String
$cshowsPrec :: Int -> PersonURI -> String -> String
Show, PersonURI -> PersonURI -> Bool
(PersonURI -> PersonURI -> Bool)
-> (PersonURI -> PersonURI -> Bool) -> Eq PersonURI
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PersonURI -> PersonURI -> Bool
$c/= :: PersonURI -> PersonURI -> Bool
== :: PersonURI -> PersonURI -> Bool
$c== :: PersonURI -> PersonURI -> Bool
Eq)
instance FromJSON PersonURI where
parseJSON :: Value -> Parser PersonURI
parseJSON = String -> (Object -> Parser PersonURI) -> Value -> Parser PersonURI
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PersonURI" ((Object -> Parser PersonURI) -> Value -> Parser PersonURI)
-> (Object -> Parser PersonURI) -> Value -> Parser PersonURI
forall a b. (a -> b) -> a -> b
$ \Object
o -> Maybe Text -> Maybe Text -> Maybe PersonURIType -> PersonURI
PersonURI (Maybe Text -> Maybe Text -> Maybe PersonURIType -> PersonURI)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe PersonURIType -> PersonURI)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"label"
Parser (Maybe Text -> Maybe PersonURIType -> PersonURI)
-> Parser (Maybe Text) -> Parser (Maybe PersonURIType -> PersonURI)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"value"
Parser (Maybe PersonURIType -> PersonURI)
-> Parser (Maybe PersonURIType) -> Parser PersonURI
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe PersonURIType)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"type"
data PersonURIType = OtherProfile
| Contributor
| Website
| OtherURI
| PersonURIType Text
deriving (Int -> PersonURIType -> String -> String
[PersonURIType] -> String -> String
PersonURIType -> String
(Int -> PersonURIType -> String -> String)
-> (PersonURIType -> String)
-> ([PersonURIType] -> String -> String)
-> Show PersonURIType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PersonURIType] -> String -> String
$cshowList :: [PersonURIType] -> String -> String
show :: PersonURIType -> String
$cshow :: PersonURIType -> String
showsPrec :: Int -> PersonURIType -> String -> String
$cshowsPrec :: Int -> PersonURIType -> String -> String
Show, PersonURIType -> PersonURIType -> Bool
(PersonURIType -> PersonURIType -> Bool)
-> (PersonURIType -> PersonURIType -> Bool) -> Eq PersonURIType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PersonURIType -> PersonURIType -> Bool
$c/= :: PersonURIType -> PersonURIType -> Bool
== :: PersonURIType -> PersonURIType -> Bool
$c== :: PersonURIType -> PersonURIType -> Bool
Eq)
instance FromJSON PersonURIType where
parseJSON :: Value -> Parser PersonURIType
parseJSON = String
-> (Text -> Parser PersonURIType) -> Value -> Parser PersonURIType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"PersonURIType" ((Text -> Parser PersonURIType) -> Value -> Parser PersonURIType)
-> (Text -> Parser PersonURIType) -> Value -> Parser PersonURIType
forall a b. (a -> b) -> a -> b
$ \Text
t -> PersonURIType -> Parser PersonURIType
forall (m :: * -> *) a. Monad m => a -> m a
return (PersonURIType -> Parser PersonURIType)
-> PersonURIType -> Parser PersonURIType
forall a b. (a -> b) -> a -> b
$ case Text
t of
Text
"otherProfile" -> PersonURIType
OtherProfile
Text
"contributor" -> PersonURIType
Contributor
Text
"website" -> PersonURIType
Website
Text
"other" -> PersonURIType
OtherURI
Text
_ -> Text -> PersonURIType
PersonURIType Text
t
data Organization =
Organization { Organization -> Maybe Text
orgName :: Maybe Text
, Organization -> Maybe Text
orgTitle :: Maybe Text
, Organization -> Maybe OrganizationType
orgType :: Maybe OrganizationType
, Organization -> Maybe Text
orgStartDate :: Maybe Text
, Organization -> Maybe Text
orgEndDate :: Maybe Text
, Organization -> Maybe Bool
orgPrimary :: Maybe Bool
} deriving (Int -> Organization -> String -> String
[Organization] -> String -> String
Organization -> String
(Int -> Organization -> String -> String)
-> (Organization -> String)
-> ([Organization] -> String -> String)
-> Show Organization
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Organization] -> String -> String
$cshowList :: [Organization] -> String -> String
show :: Organization -> String
$cshow :: Organization -> String
showsPrec :: Int -> Organization -> String -> String
$cshowsPrec :: Int -> Organization -> String -> String
Show, Organization -> Organization -> Bool
(Organization -> Organization -> Bool)
-> (Organization -> Organization -> Bool) -> Eq Organization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Organization -> Organization -> Bool
$c/= :: Organization -> Organization -> Bool
== :: Organization -> Organization -> Bool
$c== :: Organization -> Organization -> Bool
Eq)
instance FromJSON Organization where
parseJSON :: Value -> Parser Organization
parseJSON = String
-> (Object -> Parser Organization) -> Value -> Parser Organization
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Organization" ((Object -> Parser Organization) -> Value -> Parser Organization)
-> (Object -> Parser Organization) -> Value -> Parser Organization
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Maybe Text
-> Maybe Text
-> Maybe OrganizationType
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Organization
Organization (Maybe Text
-> Maybe Text
-> Maybe OrganizationType
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Organization)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe OrganizationType
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Organization)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name"
Parser
(Maybe Text
-> Maybe OrganizationType
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Organization)
-> Parser (Maybe Text)
-> Parser
(Maybe OrganizationType
-> Maybe Text -> Maybe Text -> Maybe Bool -> Organization)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"title"
Parser
(Maybe OrganizationType
-> Maybe Text -> Maybe Text -> Maybe Bool -> Organization)
-> Parser (Maybe OrganizationType)
-> Parser (Maybe Text -> Maybe Text -> Maybe Bool -> Organization)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe OrganizationType)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"type"
Parser (Maybe Text -> Maybe Text -> Maybe Bool -> Organization)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Bool -> Organization)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"startDate"
Parser (Maybe Text -> Maybe Bool -> Organization)
-> Parser (Maybe Text) -> Parser (Maybe Bool -> Organization)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"endDate"
Parser (Maybe Bool -> Organization)
-> Parser (Maybe Bool) -> Parser Organization
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"primary"
data OrganizationType = Work
| School
| OrganizationType Text
deriving (Int -> OrganizationType -> String -> String
[OrganizationType] -> String -> String
OrganizationType -> String
(Int -> OrganizationType -> String -> String)
-> (OrganizationType -> String)
-> ([OrganizationType] -> String -> String)
-> Show OrganizationType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [OrganizationType] -> String -> String
$cshowList :: [OrganizationType] -> String -> String
show :: OrganizationType -> String
$cshow :: OrganizationType -> String
showsPrec :: Int -> OrganizationType -> String -> String
$cshowsPrec :: Int -> OrganizationType -> String -> String
Show, OrganizationType -> OrganizationType -> Bool
(OrganizationType -> OrganizationType -> Bool)
-> (OrganizationType -> OrganizationType -> Bool)
-> Eq OrganizationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OrganizationType -> OrganizationType -> Bool
$c/= :: OrganizationType -> OrganizationType -> Bool
== :: OrganizationType -> OrganizationType -> Bool
$c== :: OrganizationType -> OrganizationType -> Bool
Eq)
instance FromJSON OrganizationType where
parseJSON :: Value -> Parser OrganizationType
parseJSON = String
-> (Text -> Parser OrganizationType)
-> Value
-> Parser OrganizationType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"OrganizationType" ((Text -> Parser OrganizationType)
-> Value -> Parser OrganizationType)
-> (Text -> Parser OrganizationType)
-> Value
-> Parser OrganizationType
forall a b. (a -> b) -> a -> b
$ \Text
t -> OrganizationType -> Parser OrganizationType
forall (m :: * -> *) a. Monad m => a -> m a
return (OrganizationType -> Parser OrganizationType)
-> OrganizationType -> Parser OrganizationType
forall a b. (a -> b) -> a -> b
$ case Text
t of
Text
"work" -> OrganizationType
Work
Text
"school" -> OrganizationType
School
Text
_ -> Text -> OrganizationType
OrganizationType Text
t
data Place =
Place {
Place -> Maybe Text
placeValue :: Maybe Text
, Place -> Maybe Bool
placePrimary :: Maybe Bool
} deriving (Int -> Place -> String -> String
[Place] -> String -> String
Place -> String
(Int -> Place -> String -> String)
-> (Place -> String) -> ([Place] -> String -> String) -> Show Place
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Place] -> String -> String
$cshowList :: [Place] -> String -> String
show :: Place -> String
$cshow :: Place -> String
showsPrec :: Int -> Place -> String -> String
$cshowsPrec :: Int -> Place -> String -> String
Show, Place -> Place -> Bool
(Place -> Place -> Bool) -> (Place -> Place -> Bool) -> Eq Place
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Place -> Place -> Bool
$c/= :: Place -> Place -> Bool
== :: Place -> Place -> Bool
$c== :: Place -> Place -> Bool
Eq)
instance FromJSON Place where
parseJSON :: Value -> Parser Place
parseJSON = String -> (Object -> Parser Place) -> Value -> Parser Place
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Place" ((Object -> Parser Place) -> Value -> Parser Place)
-> (Object -> Parser Place) -> Value -> Parser Place
forall a b. (a -> b) -> a -> b
$ \Object
o -> Maybe Text -> Maybe Bool -> Place
Place (Maybe Text -> Maybe Bool -> Place)
-> Parser (Maybe Text) -> Parser (Maybe Bool -> Place)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"value") Parser (Maybe Bool -> Place) -> Parser (Maybe Bool) -> Parser Place
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"primary")
data Name =
Name {
Name -> Maybe Text
nameFormatted :: Maybe Text
, Name -> Maybe Text
nameFamily :: Maybe Text
, Name -> Maybe Text
nameGiven :: Maybe Text
, Name -> Maybe Text
nameMiddle :: Maybe Text
, Name -> Maybe Text
nameHonorificPrefix :: Maybe Text
, Name -> Maybe Text
nameHonorificSuffix :: Maybe Text
} deriving (Int -> Name -> String -> String
[Name] -> String -> String
Name -> String
(Int -> Name -> String -> String)
-> (Name -> String) -> ([Name] -> String -> String) -> Show Name
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Name] -> String -> String
$cshowList :: [Name] -> String -> String
show :: Name -> String
$cshow :: Name -> String
showsPrec :: Int -> Name -> String -> String
$cshowsPrec :: Int -> Name -> String -> String
Show, Name -> Name -> Bool
(Name -> Name -> Bool) -> (Name -> Name -> Bool) -> Eq Name
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c== :: Name -> Name -> Bool
Eq)
instance FromJSON Name where
parseJSON :: Value -> Parser Name
parseJSON = String -> (Object -> Parser Name) -> Value -> Parser Name
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Name" ((Object -> Parser Name) -> Value -> Parser Name)
-> (Object -> Parser Name) -> Value -> Parser Name
forall a b. (a -> b) -> a -> b
$ \Object
o -> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Name
Name (Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Name)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Name)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"formatted"
Parser
(Maybe Text
-> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Name)
-> Parser (Maybe Text)
-> Parser
(Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"familyName"
Parser
(Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Name)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Text -> Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"givenName"
Parser (Maybe Text -> Maybe Text -> Maybe Text -> Name)
-> Parser (Maybe Text) -> Parser (Maybe Text -> Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"middleName"
Parser (Maybe Text -> Maybe Text -> Name)
-> Parser (Maybe Text) -> Parser (Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"honorificPrefix"
Parser (Maybe Text -> Name) -> Parser (Maybe Text) -> Parser Name
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"honorificSuffix"
data RelationshipStatus = Single
| InRelationship
| Engaged
| Married
| Complicated
| OpenRelationship
| Widowed
| DomesticPartnership
| CivilUnion
| RelationshipStatus Text
deriving (Int -> RelationshipStatus -> String -> String
[RelationshipStatus] -> String -> String
RelationshipStatus -> String
(Int -> RelationshipStatus -> String -> String)
-> (RelationshipStatus -> String)
-> ([RelationshipStatus] -> String -> String)
-> Show RelationshipStatus
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RelationshipStatus] -> String -> String
$cshowList :: [RelationshipStatus] -> String -> String
show :: RelationshipStatus -> String
$cshow :: RelationshipStatus -> String
showsPrec :: Int -> RelationshipStatus -> String -> String
$cshowsPrec :: Int -> RelationshipStatus -> String -> String
Show, RelationshipStatus -> RelationshipStatus -> Bool
(RelationshipStatus -> RelationshipStatus -> Bool)
-> (RelationshipStatus -> RelationshipStatus -> Bool)
-> Eq RelationshipStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationshipStatus -> RelationshipStatus -> Bool
$c/= :: RelationshipStatus -> RelationshipStatus -> Bool
== :: RelationshipStatus -> RelationshipStatus -> Bool
$c== :: RelationshipStatus -> RelationshipStatus -> Bool
Eq)
instance FromJSON RelationshipStatus where
parseJSON :: Value -> Parser RelationshipStatus
parseJSON = String
-> (Text -> Parser RelationshipStatus)
-> Value
-> Parser RelationshipStatus
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"RelationshipStatus" ((Text -> Parser RelationshipStatus)
-> Value -> Parser RelationshipStatus)
-> (Text -> Parser RelationshipStatus)
-> Value
-> Parser RelationshipStatus
forall a b. (a -> b) -> a -> b
$ \Text
t -> RelationshipStatus -> Parser RelationshipStatus
forall (m :: * -> *) a. Monad m => a -> m a
return (RelationshipStatus -> Parser RelationshipStatus)
-> RelationshipStatus -> Parser RelationshipStatus
forall a b. (a -> b) -> a -> b
$ case Text
t of
Text
"single" -> RelationshipStatus
Single
Text
"in_a_relationship" -> RelationshipStatus
InRelationship
Text
"engaged" -> RelationshipStatus
Engaged
Text
"married" -> RelationshipStatus
Married
Text
"its_complicated" -> RelationshipStatus
Complicated
Text
"open_relationship" -> RelationshipStatus
OpenRelationship
Text
"widowed" -> RelationshipStatus
Widowed
Text
"in_domestic_partnership" -> RelationshipStatus
DomesticPartnership
Text
"in_civil_union" -> RelationshipStatus
CivilUnion
Text
_ -> Text -> RelationshipStatus
RelationshipStatus Text
t
newtype PersonImage = PersonImage { PersonImage -> Text
imageUri :: Text } deriving (Int -> PersonImage -> String -> String
[PersonImage] -> String -> String
PersonImage -> String
(Int -> PersonImage -> String -> String)
-> (PersonImage -> String)
-> ([PersonImage] -> String -> String)
-> Show PersonImage
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PersonImage] -> String -> String
$cshowList :: [PersonImage] -> String -> String
show :: PersonImage -> String
$cshow :: PersonImage -> String
showsPrec :: Int -> PersonImage -> String -> String
$cshowsPrec :: Int -> PersonImage -> String -> String
Show, PersonImage -> PersonImage -> Bool
(PersonImage -> PersonImage -> Bool)
-> (PersonImage -> PersonImage -> Bool) -> Eq PersonImage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PersonImage -> PersonImage -> Bool
$c/= :: PersonImage -> PersonImage -> Bool
== :: PersonImage -> PersonImage -> Bool
$c== :: PersonImage -> PersonImage -> Bool
Eq)
instance FromJSON PersonImage where
parseJSON :: Value -> Parser PersonImage
parseJSON = String
-> (Object -> Parser PersonImage) -> Value -> Parser PersonImage
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PersonImage" ((Object -> Parser PersonImage) -> Value -> Parser PersonImage)
-> (Object -> Parser PersonImage) -> Value -> Parser PersonImage
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> PersonImage
PersonImage (Text -> PersonImage) -> Parser Text -> Parser PersonImage
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
resizePersonImage :: PersonImage -> Int -> PersonImage
resizePersonImage :: PersonImage -> Int -> PersonImage
resizePersonImage (PersonImage Text
uri) Int
size =
Text -> PersonImage
PersonImage (Text -> PersonImage) -> Text -> PersonImage
forall a b. (a -> b) -> a -> b
$ Text
uri Text -> Text -> Text
forall a. Monoid a => a -> a -> a
`mappend` Text
"?sz=" Text -> Text -> Text
forall a. Monoid a => a -> a -> a
`mappend` String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
size)
data Person = Person
{ Person -> Text
personId :: Text
, Person -> Maybe Text
personDisplayName :: Maybe Text
, Person -> Maybe Name
personName :: Maybe Name
, Person -> Maybe Text
personNickname :: Maybe Text
, Person -> Maybe Text
personBirthday :: Maybe Text
, Person -> Maybe Gender
personGender :: Maybe Gender
, Person -> Maybe Text
personProfileUri :: Maybe Text
, Person -> Maybe PersonImage
personImage :: Maybe PersonImage
, Person -> Maybe Text
personAboutMe :: Maybe Text
, Person -> Maybe RelationshipStatus
personRelationshipStatus :: Maybe RelationshipStatus
, Person -> [PersonURI]
personUris :: [PersonURI]
, Person -> [Organization]
personOrganizations :: [Organization]
, Person -> [Place]
personPlacesLived :: [Place]
, Person -> Maybe Text
personTagline :: Maybe Text
, Person -> Maybe Bool
personIsPlusUser :: Maybe Bool
, Person -> Maybe Text
personBraggingRights :: Maybe Text
, Person -> Maybe Int
personPlusOneCount :: Maybe Int
, Person -> Maybe Int
personCircledByCount :: Maybe Int
, Person -> Maybe Bool
personVerified :: Maybe Bool
, Person -> Maybe Text
personLanguage :: Maybe Text
, Person -> [Email]
personEmails :: [Email]
, Person -> Maybe Text
personDomain :: Maybe Text
, Person -> Maybe Text
personOccupation :: Maybe Text
, Person -> Maybe Text
personSkills :: Maybe Text
} deriving (Int -> Person -> String -> String
[Person] -> String -> String
Person -> String
(Int -> Person -> String -> String)
-> (Person -> String)
-> ([Person] -> String -> String)
-> Show Person
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Person] -> String -> String
$cshowList :: [Person] -> String -> String
show :: Person -> String
$cshow :: Person -> String
showsPrec :: Int -> Person -> String -> String
$cshowsPrec :: Int -> Person -> String -> String
Show, Person -> Person -> Bool
(Person -> Person -> Bool)
-> (Person -> Person -> Bool) -> Eq Person
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Person -> Person -> Bool
$c/= :: Person -> Person -> Bool
== :: Person -> Person -> Bool
$c== :: Person -> Person -> Bool
Eq)
instance FromJSON Person where
parseJSON :: Value -> Parser Person
parseJSON = String -> (Object -> Parser Person) -> Value -> Parser Person
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Person" ((Object -> Parser Person) -> Value -> Parser Person)
-> (Object -> Parser Person) -> Value -> Parser Person
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Text
-> Maybe Text
-> Maybe Name
-> Maybe Text
-> Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person
Person (Text
-> Maybe Text
-> Maybe Name
-> Maybe Text
-> Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser Text
-> Parser
(Maybe Text
-> Maybe Name
-> Maybe Text
-> Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser
(Maybe Text
-> Maybe Name
-> Maybe Text
-> Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Text)
-> Parser
(Maybe Name
-> Maybe Text
-> Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"displayName"
Parser
(Maybe Name
-> Maybe Text
-> Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Name)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Name)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name"
Parser
(Maybe Text
-> Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"nickname"
Parser
(Maybe Text
-> Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Text)
-> Parser
(Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"birthday"
Parser
(Maybe Gender
-> Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Gender)
-> Parser
(Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Gender)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"gender"
Parser
(Maybe Text
-> Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Text)
-> Parser
(Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"url")
Parser
(Maybe PersonImage
-> Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe PersonImage)
-> Parser
(Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe PersonImage)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"image"
Parser
(Maybe Text
-> Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Text)
-> Parser
(Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"aboutMe"
Parser
(Maybe RelationshipStatus
-> [PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe RelationshipStatus)
-> Parser
([PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe RelationshipStatus)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"relationshipStatus"
Parser
([PersonURI]
-> [Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser [PersonURI]
-> Parser
([Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (([PersonURI] -> Maybe [PersonURI] -> [PersonURI]
forall a. a -> Maybe a -> a
fromMaybe []) (Maybe [PersonURI] -> [PersonURI])
-> Parser (Maybe [PersonURI]) -> Parser [PersonURI]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser (Maybe [PersonURI])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"urls"))
Parser
([Organization]
-> [Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser [Organization]
-> Parser
([Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (([Organization] -> Maybe [Organization] -> [Organization]
forall a. a -> Maybe a -> a
fromMaybe []) (Maybe [Organization] -> [Organization])
-> Parser (Maybe [Organization]) -> Parser [Organization]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser (Maybe [Organization])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"organizations"))
Parser
([Place]
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser [Place]
-> Parser
(Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (([Place] -> Maybe [Place] -> [Place]
forall a. a -> Maybe a -> a
fromMaybe []) (Maybe [Place] -> [Place])
-> Parser (Maybe [Place]) -> Parser [Place]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser (Maybe [Place])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"placesLived"))
Parser
(Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Text)
-> Parser
(Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"tagline"
Parser
(Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Bool)
-> Parser
(Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"isPlusUser"
Parser
(Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Text)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"braggingRights"
Parser
(Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"plusOneCount"
Parser
(Maybe Int
-> Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Int)
-> Parser
(Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"circledByCount"
Parser
(Maybe Bool
-> Maybe Text
-> [Email]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Person)
-> Parser (Maybe Bool)
-> Parser
(Maybe Text
-> [Email] -> Maybe Text -> Maybe Text -> Maybe Text -> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"verified"
Parser
(Maybe Text
-> [Email] -> Maybe Text -> Maybe Text -> Maybe Text -> Person)
-> Parser (Maybe Text)
-> Parser
([Email] -> Maybe Text -> Maybe Text -> Maybe Text -> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"language"
Parser
([Email] -> Maybe Text -> Maybe Text -> Maybe Text -> Person)
-> Parser [Email]
-> Parser (Maybe Text -> Maybe Text -> Maybe Text -> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (([Email] -> Maybe [Email] -> [Email]
forall a. a -> Maybe a -> a
fromMaybe []) (Maybe [Email] -> [Email])
-> Parser (Maybe [Email]) -> Parser [Email]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser (Maybe [Email])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"emails"))
Parser (Maybe Text -> Maybe Text -> Maybe Text -> Person)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Text -> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"domain"
Parser (Maybe Text -> Maybe Text -> Person)
-> Parser (Maybe Text) -> Parser (Maybe Text -> Person)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"occupation"
Parser (Maybe Text -> Person)
-> Parser (Maybe Text) -> Parser Person
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"skills"
data Email = Email
{ Email -> Text
emailValue :: Text
, Email -> EmailType
emailType :: EmailType
}
deriving (Int -> Email -> String -> String
[Email] -> String -> String
Email -> String
(Int -> Email -> String -> String)
-> (Email -> String) -> ([Email] -> String -> String) -> Show Email
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Email] -> String -> String
$cshowList :: [Email] -> String -> String
show :: Email -> String
$cshow :: Email -> String
showsPrec :: Int -> Email -> String -> String
$cshowsPrec :: Int -> Email -> String -> String
Show, Email -> Email -> Bool
(Email -> Email -> Bool) -> (Email -> Email -> Bool) -> Eq Email
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Email -> Email -> Bool
$c/= :: Email -> Email -> Bool
== :: Email -> Email -> Bool
$c== :: Email -> Email -> Bool
Eq)
instance FromJSON Email where
parseJSON :: Value -> Parser Email
parseJSON = String -> (Object -> Parser Email) -> Value -> Parser Email
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Email" ((Object -> Parser Email) -> Value -> Parser Email)
-> (Object -> Parser Email) -> Value -> Parser Email
forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> EmailType -> Email
Email
(Text -> EmailType -> Email)
-> Parser Text -> Parser (EmailType -> Email)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"value"
Parser (EmailType -> Email) -> Parser EmailType -> Parser Email
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser EmailType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
data EmailType = EmailAccount
| EmailHome
| EmailWork
| EmailOther
| EmailType Text
deriving (Int -> EmailType -> String -> String
[EmailType] -> String -> String
EmailType -> String
(Int -> EmailType -> String -> String)
-> (EmailType -> String)
-> ([EmailType] -> String -> String)
-> Show EmailType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EmailType] -> String -> String
$cshowList :: [EmailType] -> String -> String
show :: EmailType -> String
$cshow :: EmailType -> String
showsPrec :: Int -> EmailType -> String -> String
$cshowsPrec :: Int -> EmailType -> String -> String
Show, EmailType -> EmailType -> Bool
(EmailType -> EmailType -> Bool)
-> (EmailType -> EmailType -> Bool) -> Eq EmailType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmailType -> EmailType -> Bool
$c/= :: EmailType -> EmailType -> Bool
== :: EmailType -> EmailType -> Bool
$c== :: EmailType -> EmailType -> Bool
Eq)
instance FromJSON EmailType where
parseJSON :: Value -> Parser EmailType
parseJSON = String -> (Text -> Parser EmailType) -> Value -> Parser EmailType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"EmailType" ((Text -> Parser EmailType) -> Value -> Parser EmailType)
-> (Text -> Parser EmailType) -> Value -> Parser EmailType
forall a b. (a -> b) -> a -> b
$ \Text
t -> EmailType -> Parser EmailType
forall (m :: * -> *) a. Monad m => a -> m a
return (EmailType -> Parser EmailType) -> EmailType -> Parser EmailType
forall a b. (a -> b) -> a -> b
$ case Text
t of
Text
"account" -> EmailType
EmailAccount
Text
"home" -> EmailType
EmailHome
Text
"work" -> EmailType
EmailWork
Text
"other" -> EmailType
EmailOther
Text
_ -> Text -> EmailType
EmailType Text
t
allPersonInfo :: A.Value -> [(Text, Text)]
allPersonInfo :: Value -> [(Text, Text)]
allPersonInfo (A.Object Object
o) = ((Key, Value) -> (Text, Text)) -> [(Key, Value)] -> [(Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map (Key, Value) -> (Text, Text)
enc ([(Key, Value)] -> [(Text, Text)])
-> [(Key, Value)] -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Object -> [(Key, Value)]
forall v. KeyMap v -> [(Key, v)]
mapToList Object
o
where
enc :: (Key, Value) -> (Text, Text)
enc (Key
key, A.String Text
s) = (Key -> Text
keyToText Key
key, Text
s)
enc (Key
key, Value
v) = (Key -> Text
keyToText Key
key, Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Builder -> Text
TL.toLazyText (Builder -> Text) -> Builder -> Text
forall a b. (a -> b) -> a -> b
$ Value -> Builder
forall a. ToJSON a => a -> Builder
A.encodeToTextBuilder Value
v)
#if MIN_VERSION_aeson(2, 0, 0)
keyToText :: Key -> Text
keyToText = Key -> Text
Data.Aeson.Key.toText
mapToList :: KeyMap v -> [(Key, v)]
mapToList = KeyMap v -> [(Key, v)]
forall v. KeyMap v -> [(Key, v)]
Data.Aeson.KeyMap.toList
#else
keyToText = id
mapToList = M.toList
#endif
allPersonInfo Value
_ = []
defaultNonceGen :: Nonce.Generator
defaultNonceGen :: Generator
defaultNonceGen = IO Generator -> Generator
forall a. IO a -> a
unsafePerformIO (IO Generator
forall (m :: * -> *). MonadIO m => m Generator
Nonce.new)
{-# NOINLINE defaultNonceGen #-}