{-# LANGUAGE DataKinds #-} ----------------------------------------------------------------------------- -- | -- License : BSD-3-Clause -- Maintainer : Oleg Grenrus -- -- The Github Users API, as described at -- . module GitHub.Endpoints.Users ( userInfoFor, userInfoFor', userInfoForR, ownerInfoForR, userInfoCurrent', userInfoCurrentR, module GitHub.Data, ) where 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 Auth -> Name User -> IO (Either Error User) userInfoFor' auth = executeRequestMaybe auth . userInfoForR -- | The information for a single user, by login name. -- -- > userInfoFor "mike-burns" userInfoFor :: Name User -> IO (Either Error User) userInfoFor = executeRequest' . userInfoForR -- | Query a single user. -- See userInfoForR :: Name User -> Request k User userInfoForR user = Query ["users", toPathPart user] [] -- | Query a single user or an organization. -- See ownerInfoForR :: Name Owner -> Request k Owner ownerInfoForR owner = Query ["users", toPathPart owner] [] -- | Retrieve information about the user associated with the supplied authentication. -- -- > userInfoCurrent' (OAuth "...") userInfoCurrent' :: Auth -> IO (Either Error User) userInfoCurrent' auth = executeRequest auth $ userInfoCurrentR -- | Query the authenticated user. -- See userInfoCurrentR :: Request 'True User userInfoCurrentR = Query ["user"] []