-- | Users.User
module MSGraphAPI.Users.User (
  get
  , getMe
  -- * types
  , User(..)) where

import GHC.Generics (Generic(..))

-- aeson
import qualified Data.Aeson as A (ToJSON(..), FromJSON(..), genericParseJSON)
-- hoauth
import Network.OAuth.OAuth2.Internal (AccessToken(..))
-- req
import Network.HTTP.Req (Req)
-- text
import Data.Text (Text)

import qualified MSGraphAPI.Internal.Common as MSG (get, aesonOptions)

-- | Representation of a user in the MS Graph API
--
-- https://learn.microsoft.com/en-us/graph/api/resources/users?view=graph-rest-1.0
data User = User {
  User -> Text
uId :: Text
  , User -> Text
uUserPrincipalName :: Text
  , User -> Text
uDisplayName :: Text
                 } deriving (User -> User -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: User -> User -> Bool
$c/= :: User -> User -> Bool
== :: User -> User -> Bool
$c== :: User -> User -> Bool
Eq, Eq User
User -> User -> Bool
User -> User -> Ordering
User -> User -> User
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: User -> User -> User
$cmin :: User -> User -> User
max :: User -> User -> User
$cmax :: User -> User -> User
>= :: User -> User -> Bool
$c>= :: User -> User -> Bool
> :: User -> User -> Bool
$c> :: User -> User -> Bool
<= :: User -> User -> Bool
$c<= :: User -> User -> Bool
< :: User -> User -> Bool
$c< :: User -> User -> Bool
compare :: User -> User -> Ordering
$ccompare :: User -> User -> Ordering
Ord, Int -> User -> ShowS
[User] -> ShowS
User -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: Int -> User -> ShowS
$cshowsPrec :: Int -> User -> ShowS
Show, forall x. Rep User x -> User
forall x. User -> Rep User x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep User x -> User
$cfrom :: forall x. User -> Rep User x
Generic)
instance A.FromJSON User where
  parseJSON :: Value -> Parser User
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (String -> Options
MSG.aesonOptions String
"u")
instance A.ToJSON User


-- | Get user information
--
-- @GET \/users\/{user-id}@
--
-- https://learn.microsoft.com/en-us/graph/api/user-get?view=graph-rest-1.0&tabs=http#request
get :: Text -- ^ user id
    -> AccessToken -> Req User
get :: Text -> AccessToken -> Req User
get Text
uid = forall a.
FromJSON a =>
[Text] -> Option 'Https -> AccessToken -> Req a
MSG.get [Text
"users", Text
uid] forall a. Monoid a => a
mempty

-- | Get information on signed-in user
--
-- Calling the \/me endpoint requires a signed-in user and therefore a delegated permission. Application permissions are not supported when using the \/me endpoint.
--
-- @GET \/me@
--
-- https://learn.microsoft.com/en-us/graph/api/user-get?view=graph-rest-1.0&tabs=http#request-1
getMe :: AccessToken -> Req User
getMe :: AccessToken -> Req User
getMe = forall a.
FromJSON a =>
[Text] -> Option 'Https -> AccessToken -> Req a
MSG.get [Text
"me"] forall a. Monoid a => a
mempty