arch-web-0.1.1: Arch Linux official and AUR web interface binding
Copyright(c) 2021 berberman
LicenseMIT
Maintainerberberman <berberman@yandex.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Web.ArchLinux.API

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

API Client

newtype APIClient (k :: APIType) a Source #

A wrapper of ClientM, with BaseUrl reflected to type level phantom APIType.

Constructors

APIClient 

Fields

Instances

Instances details
MonadReader ClientEnv (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Methods

ask :: APIClient k ClientEnv #

local :: (ClientEnv -> ClientEnv) -> APIClient k a -> APIClient k a #

reader :: (ClientEnv -> a) -> APIClient k a #

MonadError ClientError (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Monad (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Methods

(>>=) :: APIClient k a -> (a -> APIClient k b) -> APIClient k b #

(>>) :: APIClient k a -> APIClient k b -> APIClient k b #

return :: a -> APIClient k a #

Functor (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Methods

fmap :: (a -> b) -> APIClient k a -> APIClient k b #

(<$) :: a -> APIClient k b -> APIClient k a #

Applicative (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Methods

pure :: a -> APIClient k a #

(<*>) :: APIClient k (a -> b) -> APIClient k a -> APIClient k b #

liftA2 :: (a -> b -> c) -> APIClient k a -> APIClient k b -> APIClient k c #

(*>) :: APIClient k a -> APIClient k b -> APIClient k b #

(<*) :: APIClient k a -> APIClient k b -> APIClient k a #

MonadIO (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Methods

liftIO :: IO a -> APIClient k a #

MonadThrow (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Methods

throwM :: Exception e => e -> APIClient k a #

MonadCatch (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Methods

catch :: Exception e => APIClient k a -> (e -> APIClient k a) -> APIClient k a #

RunClient (APIClient k) Source # 
Instance details

Defined in Web.ArchLinux.API

Generic (APIClient k a) Source # 
Instance details

Defined in Web.ArchLinux.API

Associated Types

type Rep (APIClient k a) :: Type -> Type #

Methods

from :: APIClient k a -> Rep (APIClient k a) x #

to :: Rep (APIClient k a) x -> APIClient k a #

type Rep (APIClient k a) Source # 
Instance details

Defined in Web.ArchLinux.API

type Rep (APIClient k a) = Rep (ClientM a)

data APIType Source #

Two types of APIs.

Constructors

ArchLinux 
Aur 

class HasBaseUrl (k :: APIType) where Source #

Class to reify BaseUrl from APIType.

Instances

Instances details
HasBaseUrl 'ArchLinux Source # 
Instance details

Defined in Web.ArchLinux.API

HasBaseUrl 'Aur Source # 
Instance details

Defined in Web.ArchLinux.API

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.

Arch Linux official

data SearchOptions Source #

Options available in searching packages in Arch Linux official repositories.

See searchPackage.

Instances

Instances details
Eq SearchOptions Source # 
Instance details

Defined in Web.ArchLinux.API

Ord SearchOptions Source # 
Instance details

Defined in Web.ArchLinux.API

Show SearchOptions Source # 
Instance details

Defined in Web.ArchLinux.API

Generic SearchOptions Source # 
Instance details

Defined in Web.ArchLinux.API

Associated Types

type Rep SearchOptions :: Type -> Type #

type Rep SearchOptions Source # 
Instance details

Defined in Web.ArchLinux.API

type Rep SearchOptions = D1 ('MetaData "SearchOptions" "Web.ArchLinux.API" "arch-web-0.1.1-FGfWYMQa1XYL1VkWgNy0Rg" 'False) (C1 ('MetaCons "SearchOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_nameOrDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_exactName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "_targetDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_targetRepositories") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Repo]))) :*: ((S1 ('MetaSel ('Just "_targetArchitectures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Arch]) :*: S1 ('MetaSel ('Just "_targetMaintianer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "_targetPackager") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_isFlagged") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Flagged))))))

emptySearchOptions :: SearchOptions Source #

An empty options value for convenient.

For example,

let options =
      emptySearchOptions
        & nameOrDescription ?~ "kea"
        & targetRepositories .~ [Community, CommunityTesting]
searchPackage options

searchs packages whose names or descriptions contain kea, from Community or Community-Testing.

getPackageDetails Source #

Arguments

:: Repo

official repository

-> Arch

arch

-> Text

exact name

-> APIClient 'ArchLinux PackageInformation 

Gets details of an exact package.

getPackageFiles Source #

Arguments

:: Repo

official repository

-> Arch

arch

-> Text

exact name

-> APIClient 'ArchLinux PackageFiles 

Gets files list of an exact package.

AUR

data AurSearchType Source #

Searches packages in AUR by what?

Instances

Instances details
Enum AurSearchType Source # 
Instance details

Defined in Web.ArchLinux.API

Eq AurSearchType Source # 
Instance details

Defined in Web.ArchLinux.API

Ord AurSearchType Source # 
Instance details

Defined in Web.ArchLinux.API

Show AurSearchType Source # 
Instance details

Defined in Web.ArchLinux.API

Generic AurSearchType Source # 
Instance details

Defined in Web.ArchLinux.API

Associated Types

type Rep AurSearchType :: Type -> Type #

type Rep AurSearchType Source # 
Instance details

Defined in Web.ArchLinux.API

type Rep AurSearchType = D1 ('MetaData "AurSearchType" "Web.ArchLinux.API" "arch-web-0.1.1-FGfWYMQa1XYL1VkWgNy0Rg" 'False) ((C1 ('MetaCons "ByName" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ByNameOrDesc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ByMaintainer" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ByDepends" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ByMakedepends" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ByOptdepends" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ByCheckdepends" 'PrefixI 'False) (U1 :: Type -> Type))))

searchAur Source #

Arguments

:: AurSearchType

search type

-> Text

search argument

-> APIClient 'Aur (AurResponse [AurSearch]) 

Searches packages in AUR.

getAurInfo Source #

Arguments

:: [Text]

exact names

-> APIClient 'Aur (AurResponse [AurInfo]) 

Gets details of a set of packages in AUR.