module Network.Globus.Auth where

import Data.Aeson
import Data.Aeson.Types
import Data.List qualified as L
import Data.List.NonEmpty (NonEmpty (..))
import Data.List.NonEmpty qualified as NE
import Data.String (IsString)
import Data.Tagged
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Text.Encoding (encodeUtf8)
import Effectful (MonadIO)
import GHC.Generics (Generic)
import Network.Globus.Types
import Network.HTTP.Req as Req


-- | Opaque secret identifying the user. Validate on redirect
newtype State = State Text
  deriving newtype (String -> State
(String -> State) -> IsString State
forall a. (String -> a) -> IsString a
$cfromString :: String -> State
fromString :: String -> State
IsString, Maybe State
Value -> Parser [State]
Value -> Parser State
(Value -> Parser State)
-> (Value -> Parser [State]) -> Maybe State -> FromJSON State
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser State
parseJSON :: Value -> Parser State
$cparseJSONList :: Value -> Parser [State]
parseJSONList :: Value -> Parser [State]
$comittedField :: Maybe State
omittedField :: Maybe State
FromJSON)
  deriving (Int -> State -> ShowS
[State] -> ShowS
State -> String
(Int -> State -> ShowS)
-> (State -> String) -> ([State] -> ShowS) -> Show State
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> State -> ShowS
showsPrec :: Int -> State -> ShowS
$cshow :: State -> String
show :: State -> String
$cshowList :: [State] -> ShowS
showList :: [State] -> ShowS
Show)


-- | The end user must visit this url
authorizationUrl :: Token ClientId -> Uri Redirect -> NonEmpty Scope -> State -> Uri Authorization
authorizationUrl :: Token 'ClientId
-> Uri 'Redirect -> NonEmpty Scope -> State -> Uri 'Authorization
authorizationUrl (Tagged Text
cid) Uri 'Redirect
red NonEmpty Scope
scopes (State Text
st) =
  -- TODO: does the auth url need the security token?
  Uri 'Authorization
authorizeEndpoint{$sel:params:Uri :: Query
params = Query
query}
 where
  query :: Query
  query :: Query
query =
    Text
"client_id" Text -> Text -> Query
forall param a.
(QueryParam param, ToHttpApiData a) =>
Text -> a -> param
=: Text
cid
      Query -> Query -> Query
forall a. Semigroup a => a -> a -> a
<> Text
"response_type" Text -> Text -> Query
forall param a.
(QueryParam param, ToHttpApiData a) =>
Text -> a -> param
=: (Text
"code" :: Text)
      Query -> Query -> Query
forall a. Semigroup a => a -> a -> a
<> Text
"scope" Text -> Text -> Query
forall param a.
(QueryParam param, ToHttpApiData a) =>
Text -> a -> param
=: Text -> [Text] -> Text
Text.intercalate Text
" " (Scope -> Text
scopeText (Scope -> Text) -> [Scope] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty Scope -> [Scope]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty Scope
scopes)
      Query -> Query -> Query
forall a. Semigroup a => a -> a -> a
<> Text
"state" Text -> Text -> Query
forall param a.
(QueryParam param, ToHttpApiData a) =>
Text -> a -> param
=: Text
st
      Query -> Query -> Query
forall a. Semigroup a => a -> a -> a
<> Uri 'Redirect -> Query
forall param. QueryParam param => Uri 'Redirect -> param
redirectUri Uri 'Redirect
red

  authorizeEndpoint :: Uri Authorization
  authorizeEndpoint :: Uri 'Authorization
authorizeEndpoint = Scheme -> Text -> [Text] -> Query -> Uri 'Authorization
forall (a :: Endpoint). Scheme -> Text -> [Text] -> Query -> Uri a
Uri Scheme
Https Text
"auth.globus.org" [Text
"v2", Text
"oauth2", Text
"authorize"] ([(Text, Maybe Text)] -> Query
Query [])


fetchAccessTokens :: (MonadIO m) => Token ClientId -> Token ClientSecret -> Uri Redirect -> Token Exchange -> m (NonEmpty TokenItem)
fetchAccessTokens :: forall (m :: * -> *).
MonadIO m =>
Token 'ClientId
-> Token 'ClientSecret
-> Uri 'Redirect
-> Token 'Exchange
-> m (NonEmpty TokenItem)
fetchAccessTokens (Tagged Text
cid) (Tagged Text
sec) Uri 'Redirect
red (Tagged Text
code) = do
  HttpConfig -> Req (NonEmpty TokenItem) -> m (NonEmpty TokenItem)
forall (m :: * -> *) a. MonadIO m => HttpConfig -> Req a -> m a
runReq HttpConfig
defaultHttpConfig (Req (NonEmpty TokenItem) -> m (NonEmpty TokenItem))
-> Req (NonEmpty TokenItem) -> m (NonEmpty TokenItem)
forall a b. (a -> b) -> a -> b
$ do
    JsonResponse TokenResponse
res <-
      POST
-> Url 'Https
-> NoReqBody
-> Proxy (JsonResponse TokenResponse)
-> Option 'Https
-> Req (JsonResponse TokenResponse)
forall (m :: * -> *) method body response (scheme :: Scheme).
(MonadHttp m, HttpMethod method, HttpBody body,
 HttpResponse response,
 HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) =>
method
-> Url scheme
-> body
-> Proxy response
-> Option scheme
-> m response
req POST
POST Url 'Https
tokenEndpoint NoReqBody
NoReqBody Proxy (JsonResponse TokenResponse)
forall a. Proxy (JsonResponse a)
jsonResponse (Option 'Https -> Req (JsonResponse TokenResponse))
-> Option 'Https -> Req (JsonResponse TokenResponse)
forall a b. (a -> b) -> a -> b
$
        Text
"grant_type" Text -> Text -> Option 'Https
forall param a.
(QueryParam param, ToHttpApiData a) =>
Text -> a -> param
=: (Text
"authorization_code" :: Text)
          Option 'Https -> Option 'Https -> Option 'Https
forall a. Semigroup a => a -> a -> a
<> Text
"code" Text -> Text -> Option 'Https
forall param a.
(QueryParam param, ToHttpApiData a) =>
Text -> a -> param
=: Text
code
          Option 'Https -> Option 'Https -> Option 'Https
forall a. Semigroup a => a -> a -> a
<> Uri 'Redirect -> Option 'Https
forall param. QueryParam param => Uri 'Redirect -> param
redirectUri Uri 'Redirect
red
          -- TODO: is this the correct basic auth?
          Option 'Https -> Option 'Https -> Option 'Https
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString -> Option 'Https
basicAuth (Text -> ByteString
encodeUtf8 Text
cid) (Text -> ByteString
encodeUtf8 Text
sec)

    -- liftIO $ print $ responseBody res
    let TokenResponse NonEmpty TokenItem
toks = JsonResponse TokenResponse
-> HttpResponseBody (JsonResponse TokenResponse)
forall response.
HttpResponse response =>
response -> HttpResponseBody response
responseBody JsonResponse TokenResponse
res :: TokenResponse
    NonEmpty TokenItem -> Req (NonEmpty TokenItem)
forall a. a -> Req a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NonEmpty TokenItem
toks
 where
  tokenEndpoint :: Req.Url 'Https
  tokenEndpoint :: Url 'Https
tokenEndpoint = Text -> Url 'Https
https Text
"auth.globus.org" Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"v2" Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"oauth2" Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"token"


redirectUri :: (QueryParam param) => Uri Redirect -> param
redirectUri :: forall param. QueryParam param => Uri 'Redirect -> param
redirectUri Uri 'Redirect
red = Text
"redirect_uri" Text -> Text -> param
forall param a.
(QueryParam param, ToHttpApiData a) =>
Text -> a -> param
=: Uri 'Redirect -> Text
forall (a :: Endpoint). Uri a -> Text
renderUri Uri 'Redirect
red


-- | fetchAccessTokens returns a non-empty list matching the scopes
newtype TokenResponse = TokenResponse (NonEmpty TokenItem)
  deriving (Int -> TokenResponse -> ShowS
[TokenResponse] -> ShowS
TokenResponse -> String
(Int -> TokenResponse -> ShowS)
-> (TokenResponse -> String)
-> ([TokenResponse] -> ShowS)
-> Show TokenResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TokenResponse -> ShowS
showsPrec :: Int -> TokenResponse -> ShowS
$cshow :: TokenResponse -> String
show :: TokenResponse -> String
$cshowList :: [TokenResponse] -> ShowS
showList :: [TokenResponse] -> ShowS
Show)


instance FromJSON TokenResponse where
  parseJSON :: Value -> Parser TokenResponse
parseJSON = String
-> (Object -> Parser TokenResponse)
-> Value
-> Parser TokenResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TokenResponse" ((Object -> Parser TokenResponse) -> Value -> Parser TokenResponse)
-> (Object -> Parser TokenResponse)
-> Value
-> Parser TokenResponse
forall a b. (a -> b) -> a -> b
$ \Object
m -> do
    TokenItem
token <- Value -> Parser TokenItem
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser TokenItem) -> Value -> Parser TokenItem
forall a b. (a -> b) -> a -> b
$ Object -> Value
Object Object
m :: Parser TokenItem
    [TokenItem]
other <- Object
m Object -> Key -> Parser [TokenItem]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"other_tokens"
    TokenResponse -> Parser TokenResponse
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TokenResponse -> Parser TokenResponse)
-> TokenResponse -> Parser TokenResponse
forall a b. (a -> b) -> a -> b
$ NonEmpty TokenItem -> TokenResponse
TokenResponse (NonEmpty TokenItem -> TokenResponse)
-> NonEmpty TokenItem -> TokenResponse
forall a b. (a -> b) -> a -> b
$ TokenItem
token TokenItem -> [TokenItem] -> NonEmpty TokenItem
forall a. a -> [a] -> NonEmpty a
:| [TokenItem]
other


data TokenItem = TokenItem
  { TokenItem -> Scopes
scope :: Scopes
  , TokenItem -> Token 'Access
access_token :: Token Access
  , TokenItem -> Int
expires_in :: Int
  , -- , resource_server :: Text -- "transfer.api.globus.org"
    -- , tokenType :: Text -- "Bearer"
    TokenItem -> State
state :: State
    -- , refresh_token :: Token Refresh
    -- id_token :: Token Identity
  }
  deriving ((forall x. TokenItem -> Rep TokenItem x)
-> (forall x. Rep TokenItem x -> TokenItem) -> Generic TokenItem
forall x. Rep TokenItem x -> TokenItem
forall x. TokenItem -> Rep TokenItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TokenItem -> Rep TokenItem x
from :: forall x. TokenItem -> Rep TokenItem x
$cto :: forall x. Rep TokenItem x -> TokenItem
to :: forall x. Rep TokenItem x -> TokenItem
Generic, Maybe TokenItem
Value -> Parser [TokenItem]
Value -> Parser TokenItem
(Value -> Parser TokenItem)
-> (Value -> Parser [TokenItem])
-> Maybe TokenItem
-> FromJSON TokenItem
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser TokenItem
parseJSON :: Value -> Parser TokenItem
$cparseJSONList :: Value -> Parser [TokenItem]
parseJSONList :: Value -> Parser [TokenItem]
$comittedField :: Maybe TokenItem
omittedField :: Maybe TokenItem
FromJSON, Int -> TokenItem -> ShowS
[TokenItem] -> ShowS
TokenItem -> String
(Int -> TokenItem -> ShowS)
-> (TokenItem -> String)
-> ([TokenItem] -> ShowS)
-> Show TokenItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TokenItem -> ShowS
showsPrec :: Int -> TokenItem -> ShowS
$cshow :: TokenItem -> String
show :: TokenItem -> String
$cshowList :: [TokenItem] -> ShowS
showList :: [TokenItem] -> ShowS
Show)


scopeToken :: Scope -> NonEmpty TokenItem -> Maybe (Token Access)
scopeToken :: Scope -> NonEmpty TokenItem -> Maybe (Token 'Access)
scopeToken Scope
s NonEmpty TokenItem
ts = do
  TokenItem
item <- (TokenItem -> Bool) -> [TokenItem] -> Maybe TokenItem
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
L.find (\TokenItem
i -> Scopes -> Bool
hasScope TokenItem
i.scope) ([TokenItem] -> Maybe TokenItem) -> [TokenItem] -> Maybe TokenItem
forall a b. (a -> b) -> a -> b
$ NonEmpty TokenItem -> [TokenItem]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty TokenItem
ts
  Token 'Access -> Maybe (Token 'Access)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TokenItem
item.access_token
 where
  hasScope :: Scopes -> Bool
hasScope (Scopes NonEmpty Scope
ss) = Scope
s Scope -> NonEmpty Scope -> Bool
forall a. Eq a => a -> NonEmpty a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` NonEmpty Scope
ss


-- | You MUST include the OpenId Scope for this to work
fetchUserInfo :: (MonadIO m) => Token OpenId -> m UserInfoResponse
fetchUserInfo :: forall (m :: * -> *).
MonadIO m =>
Token 'OpenId -> m UserInfoResponse
fetchUserInfo Token 'OpenId
to =
  HttpConfig -> Req UserInfoResponse -> m UserInfoResponse
forall (m :: * -> *) a. MonadIO m => HttpConfig -> Req a -> m a
runReq HttpConfig
defaultHttpConfig (Req UserInfoResponse -> m UserInfoResponse)
-> Req UserInfoResponse -> m UserInfoResponse
forall a b. (a -> b) -> a -> b
$ do
    JsonResponse UserInfoResponse
res <-
      POST
-> Url 'Https
-> NoReqBody
-> Proxy (JsonResponse UserInfoResponse)
-> Option 'Https
-> Req (JsonResponse UserInfoResponse)
forall (m :: * -> *) method body response (scheme :: Scheme).
(MonadHttp m, HttpMethod method, HttpBody body,
 HttpResponse response,
 HttpBodyAllowed (AllowsBody method) (ProvidesBody body)) =>
method
-> Url scheme
-> body
-> Proxy response
-> Option scheme
-> m response
req POST
POST Url 'Https
endpoint NoReqBody
NoReqBody Proxy (JsonResponse UserInfoResponse)
forall a. Proxy (JsonResponse a)
jsonResponse (Option 'Https -> Req (JsonResponse UserInfoResponse))
-> Option 'Https -> Req (JsonResponse UserInfoResponse)
forall a b. (a -> b) -> a -> b
$
        Token 'OpenId -> Option 'Https
identityAuth Token 'OpenId
to
    UserInfoResponse -> Req UserInfoResponse
forall a. a -> Req a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UserInfoResponse -> Req UserInfoResponse)
-> UserInfoResponse -> Req UserInfoResponse
forall a b. (a -> b) -> a -> b
$ JsonResponse UserInfoResponse
-> HttpResponseBody (JsonResponse UserInfoResponse)
forall response.
HttpResponse response =>
response -> HttpResponseBody response
responseBody JsonResponse UserInfoResponse
res
 where
  endpoint :: Req.Url 'Https
  endpoint :: Url 'Https
endpoint = Text -> Url 'Https
https Text
"auth.globus.org" Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"v2" Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"oauth2" Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"userinfo"


identityAuth :: Token OpenId -> Option Https
identityAuth :: Token 'OpenId -> Option 'Https
identityAuth (Tagged Text
oid) = ByteString -> Option 'Https
oAuth2Bearer (Text -> ByteString
encodeUtf8 Text
oid)


--  where
--   tokenEndpoint :: Req.Url 'Https
--   tokenEndpoint = https "auth.globus.org" /: "v2" /: "oauth2" /: "token"
--
data UserInfoResponse = UserInfoResponse
  { UserInfoResponse -> UserInfo
info :: UserInfo
  , UserInfoResponse -> Maybe UserEmail
email :: Maybe UserEmail
  , UserInfoResponse -> Maybe UserProfile
profile :: Maybe UserProfile
  }


instance FromJSON UserInfoResponse where
  parseJSON :: Value -> Parser UserInfoResponse
parseJSON = String
-> (Object -> Parser UserInfoResponse)
-> Value
-> Parser UserInfoResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UserInfo" ((Object -> Parser UserInfoResponse)
 -> Value -> Parser UserInfoResponse)
-> (Object -> Parser UserInfoResponse)
-> Value
-> Parser UserInfoResponse
forall a b. (a -> b) -> a -> b
$ \Object
m -> do
    UserInfo
info <- Value -> Parser UserInfo
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser UserInfo) -> Value -> Parser UserInfo
forall a b. (a -> b) -> a -> b
$ Object -> Value
Object Object
m
    Maybe UserEmail
email <- Object
m Object -> Key -> Parser (Maybe UserEmail)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"email"
    Maybe UserProfile
profile <- Value -> Parser (Maybe UserProfile)
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser (Maybe UserProfile))
-> Value -> Parser (Maybe UserProfile)
forall a b. (a -> b) -> a -> b
$ Object -> Value
Object Object
m
    UserInfoResponse -> Parser UserInfoResponse
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UserInfoResponse -> Parser UserInfoResponse)
-> UserInfoResponse -> Parser UserInfoResponse
forall a b. (a -> b) -> a -> b
$ UserInfoResponse{UserInfo
$sel:info:UserInfoResponse :: UserInfo
info :: UserInfo
info, Maybe UserEmail
$sel:email:UserInfoResponse :: Maybe UserEmail
email :: Maybe UserEmail
email, Maybe UserProfile
$sel:profile:UserInfoResponse :: Maybe UserProfile
profile :: Maybe UserProfile
profile}


data UserInfo = UserInfo
  { UserInfo -> Text
sub :: Text
  , UserInfo -> Int
last_authentication :: Int
  -- , identity_set :: Value
  }
  deriving ((forall x. UserInfo -> Rep UserInfo x)
-> (forall x. Rep UserInfo x -> UserInfo) -> Generic UserInfo
forall x. Rep UserInfo x -> UserInfo
forall x. UserInfo -> Rep UserInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UserInfo -> Rep UserInfo x
from :: forall x. UserInfo -> Rep UserInfo x
$cto :: forall x. Rep UserInfo x -> UserInfo
to :: forall x. Rep UserInfo x -> UserInfo
Generic, Maybe UserInfo
Value -> Parser [UserInfo]
Value -> Parser UserInfo
(Value -> Parser UserInfo)
-> (Value -> Parser [UserInfo])
-> Maybe UserInfo
-> FromJSON UserInfo
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UserInfo
parseJSON :: Value -> Parser UserInfo
$cparseJSONList :: Value -> Parser [UserInfo]
parseJSONList :: Value -> Parser [UserInfo]
$comittedField :: Maybe UserInfo
omittedField :: Maybe UserInfo
FromJSON, Int -> UserInfo -> ShowS
[UserInfo] -> ShowS
UserInfo -> String
(Int -> UserInfo -> ShowS)
-> (UserInfo -> String) -> ([UserInfo] -> ShowS) -> Show UserInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserInfo -> ShowS
showsPrec :: Int -> UserInfo -> ShowS
$cshow :: UserInfo -> String
show :: UserInfo -> String
$cshowList :: [UserInfo] -> ShowS
showList :: [UserInfo] -> ShowS
Show)


newtype UserEmail = UserEmail Text
  deriving newtype (Maybe UserEmail
Value -> Parser [UserEmail]
Value -> Parser UserEmail
(Value -> Parser UserEmail)
-> (Value -> Parser [UserEmail])
-> Maybe UserEmail
-> FromJSON UserEmail
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UserEmail
parseJSON :: Value -> Parser UserEmail
$cparseJSONList :: Value -> Parser [UserEmail]
parseJSONList :: Value -> Parser [UserEmail]
$comittedField :: Maybe UserEmail
omittedField :: Maybe UserEmail
FromJSON, Int -> UserEmail -> ShowS
[UserEmail] -> ShowS
UserEmail -> String
(Int -> UserEmail -> ShowS)
-> (UserEmail -> String)
-> ([UserEmail] -> ShowS)
-> Show UserEmail
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserEmail -> ShowS
showsPrec :: Int -> UserEmail -> ShowS
$cshow :: UserEmail -> String
show :: UserEmail -> String
$cshowList :: [UserEmail] -> ShowS
showList :: [UserEmail] -> ShowS
Show, UserEmail -> UserEmail -> Bool
(UserEmail -> UserEmail -> Bool)
-> (UserEmail -> UserEmail -> Bool) -> Eq UserEmail
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UserEmail -> UserEmail -> Bool
== :: UserEmail -> UserEmail -> Bool
$c/= :: UserEmail -> UserEmail -> Bool
/= :: UserEmail -> UserEmail -> Bool
Eq)


data UserProfile = UserProfile
  { UserProfile -> Text
name :: Text
  , UserProfile -> Text
organization :: Text
  , UserProfile -> Text
preferred_username :: Text
  , UserProfile -> Text
identity_provider :: Text
  , UserProfile -> Text
identity_provider_display_name :: Text
  }
  deriving ((forall x. UserProfile -> Rep UserProfile x)
-> (forall x. Rep UserProfile x -> UserProfile)
-> Generic UserProfile
forall x. Rep UserProfile x -> UserProfile
forall x. UserProfile -> Rep UserProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UserProfile -> Rep UserProfile x
from :: forall x. UserProfile -> Rep UserProfile x
$cto :: forall x. Rep UserProfile x -> UserProfile
to :: forall x. Rep UserProfile x -> UserProfile
Generic, Maybe UserProfile
Value -> Parser [UserProfile]
Value -> Parser UserProfile
(Value -> Parser UserProfile)
-> (Value -> Parser [UserProfile])
-> Maybe UserProfile
-> FromJSON UserProfile
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UserProfile
parseJSON :: Value -> Parser UserProfile
$cparseJSONList :: Value -> Parser [UserProfile]
parseJSONList :: Value -> Parser [UserProfile]
$comittedField :: Maybe UserProfile
omittedField :: Maybe UserProfile
FromJSON, Int -> UserProfile -> ShowS
[UserProfile] -> ShowS
UserProfile -> String
(Int -> UserProfile -> ShowS)
-> (UserProfile -> String)
-> ([UserProfile] -> ShowS)
-> Show UserProfile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserProfile -> ShowS
showsPrec :: Int -> UserProfile -> ShowS
$cshow :: UserProfile -> String
show :: UserProfile -> String
$cshowList :: [UserProfile] -> ShowS
showList :: [UserProfile] -> ShowS
Show)