{-# LANGUAGE DataKinds #-}
-- | The Github Users API, as described at
-- .
module Github.Users (
userInfoFor
,userInfoFor'
,userInfoForR
,userInfoCurrent'
,userInfoCurrentR
,module Github.Data
) where
import Github.Auth
import Github.Data
import Github.Request
-- | The information for a single user, by login name.
-- With authentification
--
-- > userInfoFor' (Just ("github-username", "github-password")) "mike-burns"
userInfoFor' :: Maybe GithubAuth -> Name GithubOwner -> IO (Either Error GithubOwner)
userInfoFor' auth = executeRequestMaybe auth . userInfoForR
-- | The information for a single user, by login name.
--
-- > userInfoFor "mike-burns"
userInfoFor :: Name GithubOwner -> IO (Either Error GithubOwner)
userInfoFor = executeRequest' . userInfoForR
-- | Get a single user.
-- See
userInfoForR :: Name GithubOwner -> GithubRequest k GithubOwner
userInfoForR userName = GithubGet ["users", toPathPart userName] []
-- | Retrieve information about the user associated with the supplied authentication.
--
-- > userInfoCurrent' (GithubOAuth "...")
--
-- TODO: Change to require 'GithubAuth'?
userInfoCurrent' :: Maybe GithubAuth -> IO (Either Error GithubOwner)
userInfoCurrent' auth =
executeRequestMaybe auth . unsafeDropAuthRequirements $ userInfoCurrentR
-- | Get the authenticated user.
-- See
userInfoCurrentR :: GithubRequest 'True GithubOwner
userInfoCurrentR = GithubGet ["user"] []