| Copyright | (c) 2021 berberman |
|---|---|
| License | MIT |
| Maintainer | berberman <berberman@yandex.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Web.ArchLinux.API
Contents
Description
Arch Linux official repositories APIs and AUR APIs.
These two kinds of APIs are distinguished by APIClient.
Functions over them return APIClient parametrize by corresponding APIType.
Overall, there are five APIs available, refer to https://wiki.archlinux.org/index.php/Official_repositories_web_interface and https://wiki.archlinux.org/index.php/Aurweb_RPC_interface.
Synopsis
- newtype APIClient (k :: APIType) a = APIClient {
- unWrapClientM :: ClientM a
- data APIType
- class HasBaseUrl (k :: APIType) where
- runAPIClient :: forall s a. HasBaseUrl s => Manager -> APIClient s a -> IO (Either ClientError a)
- runAPIClient' :: HasBaseUrl s => APIClient s a -> IO (Either ClientError a)
- data SearchOptions = SearchOptions {}
- emptySearchOptions :: SearchOptions
- getPackageDetails :: Repo -> Arch -> Text -> APIClient 'ArchLinux PackageInformation
- getPackageFiles :: Repo -> Arch -> Text -> APIClient 'ArchLinux PackageFiles
- searchPackage :: SearchOptions -> APIClient 'ArchLinux (ArchLinuxResponse PackageInformation)
- data AurSearchType
- searchAur :: AurSearchType -> Text -> APIClient 'Aur (AurResponse [AurSearch])
- getAurInfo :: [Text] -> APIClient 'Aur (AurResponse [AurInfo])
API Client
newtype APIClient (k :: APIType) a Source #
Constructors
| APIClient | |
Fields
| |
Instances
| MonadError ClientError (APIClient k) Source # | |
Defined in Web.ArchLinux.API Methods throwError :: ClientError -> APIClient k a # catchError :: APIClient k a -> (ClientError -> APIClient k a) -> APIClient k a # | |
| MonadReader ClientEnv (APIClient k) Source # | |
| MonadIO (APIClient k) Source # | |
Defined in Web.ArchLinux.API | |
| Applicative (APIClient k) Source # | |
Defined in Web.ArchLinux.API | |
| Functor (APIClient k) Source # | |
| Monad (APIClient k) Source # | |
| MonadCatch (APIClient k) Source # | |
Defined in Web.ArchLinux.API | |
| MonadThrow (APIClient k) Source # | |
Defined in Web.ArchLinux.API Methods throwM :: (HasCallStack, Exception e) => e -> APIClient k a # | |
| RunClient (APIClient k) Source # | |
Defined in Web.ArchLinux.API Methods runRequestAcceptStatus :: Maybe [Status] -> Request -> APIClient k Response # throwClientError :: ClientError -> APIClient k a # | |
| Generic (APIClient k a) Source # | |
| type Rep (APIClient k a) Source # | |
Defined in Web.ArchLinux.API | |
class HasBaseUrl (k :: APIType) where Source #
Methods
getBaseUrl :: BaseUrl Source #
Instances
| HasBaseUrl 'ArchLinux Source # | |
Defined in Web.ArchLinux.API Methods getBaseUrl :: BaseUrl Source # | |
| HasBaseUrl 'Aur Source # | |
Defined in Web.ArchLinux.API Methods getBaseUrl :: BaseUrl Source # | |
runAPIClient :: forall s a. HasBaseUrl s => Manager -> APIClient s a -> IO (Either ClientError a) Source #
Runs APIClient.
It calls getBaseUrl, then creates ClientEnv, finally calls runClientM.
runAPIClient' :: HasBaseUrl s => APIClient s a -> IO (Either ClientError a) Source #
Like runAPIClient, but creates a Manager.
Arch Linux official
data SearchOptions Source #
Options available in searching packages in Arch Linux official repositories.
See searchPackage.
Constructors
| SearchOptions | |
Fields
| |
Instances
emptySearchOptions :: SearchOptions Source #
An empty options value for convenient.
For example,
let options =
emptySearchOptions
& nameOrDescription ?~ "kea"
& targetRepositories .~ [Extra, ExtraTesting]
searchPackage optionssearchs packages whose names or descriptions contain kea, from Extra or Extra-Testing.
Arguments
| :: Repo | official repository |
| -> Arch | arch |
| -> Text | exact name |
| -> APIClient 'ArchLinux PackageInformation |
Gets details of an exact package.
Gets files list of an exact package.
searchPackage :: SearchOptions -> APIClient 'ArchLinux (ArchLinuxResponse PackageInformation) Source #
Searches packages.
See SearchOptions and emptySearchOptions.
AUR
data AurSearchType Source #
Searches packages in AUR by what?
Instances
Arguments
| :: AurSearchType | search type |
| -> Text | search argument |
| -> APIClient 'Aur (AurResponse [AurSearch]) |
Searches packages in AUR.
Arguments
| :: [Text] | exact names |
| -> APIClient 'Aur (AurResponse [AurInfo]) |
Gets details of a set of packages in AUR.