{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE StandaloneDeriving #-}
module Web.ArchLinux.Types
(
Repo (..),
Arch (..),
License (..),
licenseId,
parseLicense,
PackageInformation (..),
PackageFiles (..),
Flagged (..),
ArchLinuxResponse (..),
AurSearch (..),
AurInfo (..),
AurResponseType (..),
AurResponse (..),
)
where
import Data.Aeson
import Data.Char (toUpper)
import Data.Maybe (fromJust, fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time (UTCTime)
import Deriving.Aeson
import Servant.API (ToHttpApiData (..))
type ArchLinuxJSON = CustomJSON '[FieldLabelModifier (StripPrefix "_", CamelToSnake)]
unString :: Value -> Text
unString :: Value -> Text
unString (String Text
x) = Text
x
unString Value
_ = Text
forall a. HasCallStack => a
undefined
toQueryParamViaJSON :: (ToJSON a) => a -> Text
toQueryParamViaJSON :: forall a. ToJSON a => a -> Text
toQueryParamViaJSON = Value -> Text
unString (Value -> Text) -> (a -> Value) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Value -> Value
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Value -> Value) -> (a -> Maybe Value) -> a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe Value
forall a. FromJSON a => ByteString -> Maybe a
decode (ByteString -> Maybe Value)
-> (a -> ByteString) -> a -> Maybe Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. ToJSON a => a -> ByteString
encode
data AurModifier
instance StringModifier AurModifier where
getStringModifier :: String -> String
getStringModifier (String -> Text
T.pack -> Text
t) = Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
eat Text
"Url" Text
"URL" (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
eat Text
"Id" Text
"ID" Text
upper
where
upper :: Text
upper =
case Text -> Maybe (Char, Text)
T.uncons Text
t of
Just (Char
h, Text
s) -> Char -> Text -> Text
T.cons (Char -> Char
toUpper Char
h) Text
s
Maybe (Char, Text)
_ -> String -> Text
forall a. HasCallStack => String -> a
error String
"impossible"
eat :: Text -> Text -> Text -> Text
eat Text
prefix Text
to Text
input = case Text -> Text -> Maybe Text
T.stripPrefix Text
prefix Text
input of
Just Text
x -> Text
to Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x
Maybe Text
_ -> Text
input
type AurJSON = CustomJSON '[FieldLabelModifier (StripPrefix "_", AurModifier)]
data Repo
= Core
| CoreTesting
|
|
| Multilib
| MultilibTesting
| GnomeUnstable
| KDEUnstable
deriving stock (Int -> Repo -> String -> String
[Repo] -> String -> String
Repo -> String
(Int -> Repo -> String -> String)
-> (Repo -> String) -> ([Repo] -> String -> String) -> Show Repo
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Repo -> String -> String
showsPrec :: Int -> Repo -> String -> String
$cshow :: Repo -> String
show :: Repo -> String
$cshowList :: [Repo] -> String -> String
showList :: [Repo] -> String -> String
Show, Repo -> Repo -> Bool
(Repo -> Repo -> Bool) -> (Repo -> Repo -> Bool) -> Eq Repo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Repo -> Repo -> Bool
== :: Repo -> Repo -> Bool
$c/= :: Repo -> Repo -> Bool
/= :: Repo -> Repo -> Bool
Eq, Eq Repo
Eq Repo =>
(Repo -> Repo -> Ordering)
-> (Repo -> Repo -> Bool)
-> (Repo -> Repo -> Bool)
-> (Repo -> Repo -> Bool)
-> (Repo -> Repo -> Bool)
-> (Repo -> Repo -> Repo)
-> (Repo -> Repo -> Repo)
-> Ord Repo
Repo -> Repo -> Bool
Repo -> Repo -> Ordering
Repo -> Repo -> Repo
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
$ccompare :: Repo -> Repo -> Ordering
compare :: Repo -> Repo -> Ordering
$c< :: Repo -> Repo -> Bool
< :: Repo -> Repo -> Bool
$c<= :: Repo -> Repo -> Bool
<= :: Repo -> Repo -> Bool
$c> :: Repo -> Repo -> Bool
> :: Repo -> Repo -> Bool
$c>= :: Repo -> Repo -> Bool
>= :: Repo -> Repo -> Bool
$cmax :: Repo -> Repo -> Repo
max :: Repo -> Repo -> Repo
$cmin :: Repo -> Repo -> Repo
min :: Repo -> Repo -> Repo
Ord, Int -> Repo
Repo -> Int
Repo -> [Repo]
Repo -> Repo
Repo -> Repo -> [Repo]
Repo -> Repo -> Repo -> [Repo]
(Repo -> Repo)
-> (Repo -> Repo)
-> (Int -> Repo)
-> (Repo -> Int)
-> (Repo -> [Repo])
-> (Repo -> Repo -> [Repo])
-> (Repo -> Repo -> [Repo])
-> (Repo -> Repo -> Repo -> [Repo])
-> Enum Repo
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Repo -> Repo
succ :: Repo -> Repo
$cpred :: Repo -> Repo
pred :: Repo -> Repo
$ctoEnum :: Int -> Repo
toEnum :: Int -> Repo
$cfromEnum :: Repo -> Int
fromEnum :: Repo -> Int
$cenumFrom :: Repo -> [Repo]
enumFrom :: Repo -> [Repo]
$cenumFromThen :: Repo -> Repo -> [Repo]
enumFromThen :: Repo -> Repo -> [Repo]
$cenumFromTo :: Repo -> Repo -> [Repo]
enumFromTo :: Repo -> Repo -> [Repo]
$cenumFromThenTo :: Repo -> Repo -> Repo -> [Repo]
enumFromThenTo :: Repo -> Repo -> Repo -> [Repo]
Enum, (forall x. Repo -> Rep Repo x)
-> (forall x. Rep Repo x -> Repo) -> Generic Repo
forall x. Rep Repo x -> Repo
forall x. Repo -> Rep Repo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Repo -> Rep Repo x
from :: forall x. Repo -> Rep Repo x
$cto :: forall x. Rep Repo x -> Repo
to :: forall x. Rep Repo x -> Repo
Generic)
deriving (Maybe Repo
Value -> Parser [Repo]
Value -> Parser Repo
(Value -> Parser Repo)
-> (Value -> Parser [Repo]) -> Maybe Repo -> FromJSON Repo
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Repo
parseJSON :: Value -> Parser Repo
$cparseJSONList :: Value -> Parser [Repo]
parseJSONList :: Value -> Parser [Repo]
$comittedField :: Maybe Repo
omittedField :: Maybe Repo
FromJSON, [Repo] -> Value
[Repo] -> Encoding
Repo -> Bool
Repo -> Value
Repo -> Encoding
(Repo -> Value)
-> (Repo -> Encoding)
-> ([Repo] -> Value)
-> ([Repo] -> Encoding)
-> (Repo -> Bool)
-> ToJSON Repo
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Repo -> Value
toJSON :: Repo -> Value
$ctoEncoding :: Repo -> Encoding
toEncoding :: Repo -> Encoding
$ctoJSONList :: [Repo] -> Value
toJSONList :: [Repo] -> Value
$ctoEncodingList :: [Repo] -> Encoding
toEncodingList :: [Repo] -> Encoding
$comitField :: Repo -> Bool
omitField :: Repo -> Bool
ToJSON) via CustomJSON '[ConstructorTagModifier CamelToKebab] Repo
instance ToHttpApiData Repo where
toQueryParam :: Repo -> Text
toQueryParam (Repo -> Text
forall a. ToJSON a => a -> Text
toQueryParamViaJSON -> Text
x) = case HasCallStack => Text -> Text -> (Text, Text)
Text -> Text -> (Text, Text)
T.breakOn Text
"-" Text
x of
(Text -> Maybe (Char, Text)
T.uncons -> Just (Char
h, Text
s), Text
"") -> Char -> Text -> Text
T.cons (Char -> Char
toUpper Char
h) Text
s
(Text -> Maybe (Char, Text)
T.uncons -> Just (Char
h1, Text
s1), Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'-', Text -> Maybe (Char, Text)
T.uncons -> Just (Char
h2, Text
s2))) ->
Char -> Text -> Text
T.cons (Char -> Char
toUpper Char
h1) Text
s1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text -> Text
T.cons (Char -> Char
toUpper Char
h2) Text
s2
(Text, Text)
_ -> Text
forall a. HasCallStack => a
undefined
data Arch
= Any
| I686
| X86_64
deriving stock (Int -> Arch -> String -> String
[Arch] -> String -> String
Arch -> String
(Int -> Arch -> String -> String)
-> (Arch -> String) -> ([Arch] -> String -> String) -> Show Arch
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Arch -> String -> String
showsPrec :: Int -> Arch -> String -> String
$cshow :: Arch -> String
show :: Arch -> String
$cshowList :: [Arch] -> String -> String
showList :: [Arch] -> String -> String
Show, Arch -> Arch -> Bool
(Arch -> Arch -> Bool) -> (Arch -> Arch -> Bool) -> Eq Arch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Arch -> Arch -> Bool
== :: Arch -> Arch -> Bool
$c/= :: Arch -> Arch -> Bool
/= :: Arch -> Arch -> Bool
Eq, Eq Arch
Eq Arch =>
(Arch -> Arch -> Ordering)
-> (Arch -> Arch -> Bool)
-> (Arch -> Arch -> Bool)
-> (Arch -> Arch -> Bool)
-> (Arch -> Arch -> Bool)
-> (Arch -> Arch -> Arch)
-> (Arch -> Arch -> Arch)
-> Ord Arch
Arch -> Arch -> Bool
Arch -> Arch -> Ordering
Arch -> Arch -> Arch
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
$ccompare :: Arch -> Arch -> Ordering
compare :: Arch -> Arch -> Ordering
$c< :: Arch -> Arch -> Bool
< :: Arch -> Arch -> Bool
$c<= :: Arch -> Arch -> Bool
<= :: Arch -> Arch -> Bool
$c> :: Arch -> Arch -> Bool
> :: Arch -> Arch -> Bool
$c>= :: Arch -> Arch -> Bool
>= :: Arch -> Arch -> Bool
$cmax :: Arch -> Arch -> Arch
max :: Arch -> Arch -> Arch
$cmin :: Arch -> Arch -> Arch
min :: Arch -> Arch -> Arch
Ord, Int -> Arch
Arch -> Int
Arch -> [Arch]
Arch -> Arch
Arch -> Arch -> [Arch]
Arch -> Arch -> Arch -> [Arch]
(Arch -> Arch)
-> (Arch -> Arch)
-> (Int -> Arch)
-> (Arch -> Int)
-> (Arch -> [Arch])
-> (Arch -> Arch -> [Arch])
-> (Arch -> Arch -> [Arch])
-> (Arch -> Arch -> Arch -> [Arch])
-> Enum Arch
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Arch -> Arch
succ :: Arch -> Arch
$cpred :: Arch -> Arch
pred :: Arch -> Arch
$ctoEnum :: Int -> Arch
toEnum :: Int -> Arch
$cfromEnum :: Arch -> Int
fromEnum :: Arch -> Int
$cenumFrom :: Arch -> [Arch]
enumFrom :: Arch -> [Arch]
$cenumFromThen :: Arch -> Arch -> [Arch]
enumFromThen :: Arch -> Arch -> [Arch]
$cenumFromTo :: Arch -> Arch -> [Arch]
enumFromTo :: Arch -> Arch -> [Arch]
$cenumFromThenTo :: Arch -> Arch -> Arch -> [Arch]
enumFromThenTo :: Arch -> Arch -> Arch -> [Arch]
Enum, (forall x. Arch -> Rep Arch x)
-> (forall x. Rep Arch x -> Arch) -> Generic Arch
forall x. Rep Arch x -> Arch
forall x. Arch -> Rep Arch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Arch -> Rep Arch x
from :: forall x. Arch -> Rep Arch x
$cto :: forall x. Rep Arch x -> Arch
to :: forall x. Rep Arch x -> Arch
Generic)
deriving (Maybe Arch
Value -> Parser [Arch]
Value -> Parser Arch
(Value -> Parser Arch)
-> (Value -> Parser [Arch]) -> Maybe Arch -> FromJSON Arch
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Arch
parseJSON :: Value -> Parser Arch
$cparseJSONList :: Value -> Parser [Arch]
parseJSONList :: Value -> Parser [Arch]
$comittedField :: Maybe Arch
omittedField :: Maybe Arch
FromJSON, [Arch] -> Value
[Arch] -> Encoding
Arch -> Bool
Arch -> Value
Arch -> Encoding
(Arch -> Value)
-> (Arch -> Encoding)
-> ([Arch] -> Value)
-> ([Arch] -> Encoding)
-> (Arch -> Bool)
-> ToJSON Arch
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Arch -> Value
toJSON :: Arch -> Value
$ctoEncoding :: Arch -> Encoding
toEncoding :: Arch -> Encoding
$ctoJSONList :: [Arch] -> Value
toJSONList :: [Arch] -> Value
$ctoEncodingList :: [Arch] -> Encoding
toEncodingList :: [Arch] -> Encoding
$comitField :: Arch -> Bool
omitField :: Arch -> Bool
ToJSON) via CustomJSON '[ConstructorTagModifier CamelToSnake] Arch
instance ToHttpApiData Arch where
toQueryParam :: Arch -> Text
toQueryParam = Arch -> Text
forall a. ToJSON a => a -> Text
toQueryParamViaJSON
data License
= AGPL_3_0_only
| AGPL_3_0_or_later
| Apache_2_0
| Artistic_1_0_Perl
| Artistic_2_0
| BSL_1_0
| CC_BY_1_0
| CC_BY_2_0
| CC_BY_2_5
| CC_BY_3_0_AT
| CC_BY_3_0_US
| CC_BY_3_0
| CC_BY_4_0
| CC_BY_NC_1_0
| CC_BY_NC_2_0
| CC_BY_NC_2_5
| CC_BY_NC_3_0
| CC_BY_NC_4_0
| CC_BY_NC_ND_1_0
| CC_BY_NC_ND_2_0
| CC_BY_NC_ND_2_5
| CC_BY_NC_ND_3_0_IGO
| CC_BY_NC_ND_3_0
| CC_BY_NC_ND_4_0
| CC_BY_NC_SA_1_0
| CC_BY_NC_SA_2_0
| CC_BY_NC_SA_2_5
| CC_BY_NC_SA_3_0
| CC_BY_NC_SA_4_0
| CC_BY_ND_1_0
| CC_BY_ND_2_0
| CC_BY_ND_2_5
| CC_BY_ND_3_0
| CC_BY_ND_4_0
| CC_BY_SA_1_0
| CC_BY_SA_2_0_UK
| CC_BY_SA_2_1_JP
| CC_BY_SA_2_5
| CC_BY_SA_3_0_AT
| CC_BY_SA_3_0
| CC_BY_SA_4_0
| CC_PDDC
| CC0_1_0
| CDDL_1_0
| CDDL_1_1
| CPL_1_0
| EPL_1_0
| EPL_2_0
| FSFAP
| GFDL_1_1_invariants_only
| GFDL_1_1_invariants_or_later
| GFDL_1_1_no_invariants_only
| GFDL_1_1_no_invariants_or_later
| GFDL_1_1_only
| GFDL_1_1_or_later
| GFDL_1_2_invariants_only
| GFDL_1_2_invariants_or_later
| GFDL_1_2_no_invariants_only
| GFDL_1_2_no_invariants_or_later
| GFDL_1_2_only
| GFDL_1_2_or_later
| GFDL_1_3_invariants_only
| GFDL_1_3_invariants_or_later
| GFDL_1_3_no_invariants_only
| GFDL_1_3_no_invariants_or_later
| GFDL_1_3_only
| GFDL_1_3_or_later
| GPL_1_0_only
| GPL_1_0_or_later
| GPL_2_0_only
| GPL_2_0_or_later
| GPL_3_0_only
| GPL_3_0_or_later
| LGPL_2_0_only
| LGPL_2_0_or_later
| LGPL_2_1_only
| LGPL_2_1_or_later
| LGPL_3_0_only
| LGPL_3_0_or_later
| LGPLLR
| LPPL_1_0
| LPPL_1_1
| LPPL_1_2
| LPPL_1_3a
| LPPL_1_3c
| MPL_1_0
| MPL_1_1
| MPL_2_0
| PHP_3_0
| PHP_3_01
| PSF_2_0
| Ruby
| Unlicense
| W3C
| WTFPL
| ZPL_1_1
| ZPL_2_0
| ZPL_2_1
| Custom Text
deriving stock (Int -> License -> String -> String
[License] -> String -> String
License -> String
(Int -> License -> String -> String)
-> (License -> String)
-> ([License] -> String -> String)
-> Show License
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> License -> String -> String
showsPrec :: Int -> License -> String -> String
$cshow :: License -> String
show :: License -> String
$cshowList :: [License] -> String -> String
showList :: [License] -> String -> String
Show, License -> License -> Bool
(License -> License -> Bool)
-> (License -> License -> Bool) -> Eq License
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: License -> License -> Bool
== :: License -> License -> Bool
$c/= :: License -> License -> Bool
/= :: License -> License -> Bool
Eq, Eq License
Eq License =>
(License -> License -> Ordering)
-> (License -> License -> Bool)
-> (License -> License -> Bool)
-> (License -> License -> Bool)
-> (License -> License -> Bool)
-> (License -> License -> License)
-> (License -> License -> License)
-> Ord License
License -> License -> Bool
License -> License -> Ordering
License -> License -> License
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
$ccompare :: License -> License -> Ordering
compare :: License -> License -> Ordering
$c< :: License -> License -> Bool
< :: License -> License -> Bool
$c<= :: License -> License -> Bool
<= :: License -> License -> Bool
$c> :: License -> License -> Bool
> :: License -> License -> Bool
$c>= :: License -> License -> Bool
>= :: License -> License -> Bool
$cmax :: License -> License -> License
max :: License -> License -> License
$cmin :: License -> License -> License
min :: License -> License -> License
Ord, (forall x. License -> Rep License x)
-> (forall x. Rep License x -> License) -> Generic License
forall x. Rep License x -> License
forall x. License -> Rep License x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. License -> Rep License x
from :: forall x. License -> Rep License x
$cto :: forall x. Rep License x -> License
to :: forall x. Rep License x -> License
Generic)
licenseId :: License -> Text
licenseId :: License -> Text
licenseId License
AGPL_3_0_only = Text
"AGPL-3.0-only"
licenseId License
AGPL_3_0_or_later = Text
"AGPL-3.0-or-later"
licenseId License
Apache_2_0 = Text
"Apache-2.0"
licenseId License
Artistic_1_0_Perl = Text
"Artistic-1.0-Perl"
licenseId License
Artistic_2_0 = Text
"Artistic-2.0"
licenseId License
BSL_1_0 = Text
"BSL-1.0"
licenseId License
CC_BY_1_0 = Text
"CC-BY-1.0"
licenseId License
CC_BY_2_0 = Text
"CC-BY-2.0"
licenseId License
CC_BY_2_5 = Text
"CC-BY-2.5"
licenseId License
CC_BY_3_0_AT = Text
"CC-BY-3.0-AT"
licenseId License
CC_BY_3_0_US = Text
"CC-BY-3.0-US"
licenseId License
CC_BY_3_0 = Text
"CC-BY-3.0"
licenseId License
CC_BY_4_0 = Text
"CC-BY-4.0"
licenseId License
CC_BY_NC_1_0 = Text
"CC-BY-NC-1.0"
licenseId License
CC_BY_NC_2_0 = Text
"CC-BY-NC-2.0"
licenseId License
CC_BY_NC_2_5 = Text
"CC-BY-NC-2.5"
licenseId License
CC_BY_NC_3_0 = Text
"CC-BY-NC-3.0"
licenseId License
CC_BY_NC_4_0 = Text
"CC-BY-NC-4.0"
licenseId License
CC_BY_NC_ND_1_0 = Text
"CC-BY-NC-ND-1.0"
licenseId License
CC_BY_NC_ND_2_0 = Text
"CC-BY-NC-ND-2.0"
licenseId License
CC_BY_NC_ND_2_5 = Text
"CC-BY-NC-ND-2.5"
licenseId License
CC_BY_NC_ND_3_0_IGO = Text
"CC-BY-NC-ND-3.0-IGO"
licenseId License
CC_BY_NC_ND_3_0 = Text
"CC-BY-NC-ND-3.0"
licenseId License
CC_BY_NC_ND_4_0 = Text
"CC-BY-NC-ND-4.0"
licenseId License
CC_BY_NC_SA_1_0 = Text
"CC-BY-NC-SA-1.0"
licenseId License
CC_BY_NC_SA_2_0 = Text
"CC-BY-NC-SA-2.0"
licenseId License
CC_BY_NC_SA_2_5 = Text
"CC-BY-NC-SA-2.5"
licenseId License
CC_BY_NC_SA_3_0 = Text
"CC-BY-NC-SA-3.0"
licenseId License
CC_BY_NC_SA_4_0 = Text
"CC-BY-NC-SA-4.0"
licenseId License
CC_BY_ND_1_0 = Text
"CC-BY-ND-1.0"
licenseId License
CC_BY_ND_2_0 = Text
"CC-BY-ND-2.0"
licenseId License
CC_BY_ND_2_5 = Text
"CC-BY-ND-2.5"
licenseId License
CC_BY_ND_3_0 = Text
"CC-BY-ND-3.0"
licenseId License
CC_BY_ND_4_0 = Text
"CC-BY-ND-4.0"
licenseId License
CC_BY_SA_1_0 = Text
"CC-BY-SA-1.0"
licenseId License
CC_BY_SA_2_0_UK = Text
"CC-BY-SA-2.0-UK"
licenseId License
CC_BY_SA_2_1_JP = Text
"CC-BY-SA-2.1-JP"
licenseId License
CC_BY_SA_2_5 = Text
"CC-BY-SA-2.5"
licenseId License
CC_BY_SA_3_0_AT = Text
"CC-BY-SA-3.0-AT"
licenseId License
CC_BY_SA_3_0 = Text
"CC-BY-SA-3.0"
licenseId License
CC_BY_SA_4_0 = Text
"CC-BY-SA-4.0"
licenseId License
CC_PDDC = Text
"CC-PDDC"
licenseId License
CC0_1_0 = Text
"CC0-1.0"
licenseId License
CDDL_1_0 = Text
"CDDL-1.0"
licenseId License
CDDL_1_1 = Text
"CDDL-1.1"
licenseId License
CPL_1_0 = Text
"CPL-1.0"
licenseId License
EPL_1_0 = Text
"EPL-1.0"
licenseId License
EPL_2_0 = Text
"EPL-2.0"
licenseId License
FSFAP = Text
"FSFAP"
licenseId License
GFDL_1_1_invariants_only = Text
"GFDL-1.1-invariants-only"
licenseId License
GFDL_1_1_invariants_or_later = Text
"GFDL-1.1-invariants-or-later"
licenseId License
GFDL_1_1_no_invariants_only = Text
"GFDL-1.1-no-invariants-only"
licenseId License
GFDL_1_1_no_invariants_or_later = Text
"GFDL-1.1-no-invariants-or-later"
licenseId License
GFDL_1_1_only = Text
"GFDL-1.1-only"
licenseId License
GFDL_1_1_or_later = Text
"GFDL-1.1-or-later"
licenseId License
GFDL_1_2_invariants_only = Text
"GFDL-1.2-invariants-only"
licenseId License
GFDL_1_2_invariants_or_later = Text
"GFDL-1.2-invariants-or-later"
licenseId License
GFDL_1_2_no_invariants_only = Text
"GFDL-1.2-no-invariants-only"
licenseId License
GFDL_1_2_no_invariants_or_later = Text
"GFDL-1.2-no-invariants-or-later"
licenseId License
GFDL_1_2_only = Text
"GFDL-1.2-only"
licenseId License
GFDL_1_2_or_later = Text
"GFDL-1.2-or-later"
licenseId License
GFDL_1_3_invariants_only = Text
"GFDL-1.3-invariants-only"
licenseId License
GFDL_1_3_invariants_or_later = Text
"GFDL-1.3-invariants-or-later"
licenseId License
GFDL_1_3_no_invariants_only = Text
"GFDL-1.3-no-invariants-only"
licenseId License
GFDL_1_3_no_invariants_or_later = Text
"GFDL-1.3-no-invariants-or-later"
licenseId License
GFDL_1_3_only = Text
"GFDL-1.3-only"
licenseId License
GFDL_1_3_or_later = Text
"GFDL-1.3-or-later"
licenseId License
GPL_1_0_only = Text
"GPL-1.0-only"
licenseId License
GPL_1_0_or_later = Text
"GPL-1.0-or-later"
licenseId License
GPL_2_0_only = Text
"GPL-2.0-only"
licenseId License
GPL_2_0_or_later = Text
"GPL-2.0-or-later"
licenseId License
GPL_3_0_only = Text
"GPL-3.0-only"
licenseId License
GPL_3_0_or_later = Text
"GPL-3.0-or-later"
licenseId License
LGPL_2_0_only = Text
"LGPL-2.0-only"
licenseId License
LGPL_2_0_or_later = Text
"LGPL-2.0-or-later"
licenseId License
LGPL_2_1_only = Text
"LGPL-2.1-only"
licenseId License
LGPL_2_1_or_later = Text
"LGPL-2.1-or-later"
licenseId License
LGPL_3_0_only = Text
"LGPL-3.0-only"
licenseId License
LGPL_3_0_or_later = Text
"LGPL-3.0-or-later"
licenseId License
LGPLLR = Text
"LGPLLR"
licenseId License
LPPL_1_0 = Text
"LPPL-1.0"
licenseId License
LPPL_1_1 = Text
"LPPL-1.1"
licenseId License
LPPL_1_2 = Text
"LPPL-1.2"
licenseId License
LPPL_1_3a = Text
"LPPL-1.3a"
licenseId License
LPPL_1_3c = Text
"LPPL-1.3c"
licenseId License
MPL_1_0 = Text
"MPL-1.0"
licenseId License
MPL_1_1 = Text
"MPL-1.1"
licenseId License
MPL_2_0 = Text
"MPL-2.0"
licenseId License
PHP_3_0 = Text
"PHP-3.0"
licenseId License
PHP_3_01 = Text
"PHP-3.01"
licenseId License
PSF_2_0 = Text
"PSF-2.0"
licenseId License
Ruby = Text
"Ruby"
licenseId License
Unlicense = Text
"Unlicense"
licenseId License
W3C = Text
"W3C"
licenseId License
WTFPL = Text
"WTFPL"
licenseId License
ZPL_1_1 = Text
"ZPL-1.1"
licenseId License
ZPL_2_0 = Text
"ZPL-2.0"
licenseId License
ZPL_2_1 = Text
"ZPL-2.1"
licenseId (Custom Text
x) = Text
"custom:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x
parseLicense :: Text -> License
parseLicense :: Text -> License
parseLicense Text
"AGPL-3.0-only" = License
AGPL_3_0_only
parseLicense Text
"AGPL-3.0-or-later" = License
AGPL_3_0_or_later
parseLicense Text
"Apache-2.0" = License
Apache_2_0
parseLicense Text
"Artistic-1.0-Perl" = License
Artistic_1_0_Perl
parseLicense Text
"Artistic-2.0" = License
Artistic_2_0
parseLicense Text
"BSL-1.0" = License
BSL_1_0
parseLicense Text
"CC-BY-1.0" = License
CC_BY_1_0
parseLicense Text
"CC-BY-2.0" = License
CC_BY_2_0
parseLicense Text
"CC-BY-2.5" = License
CC_BY_2_5
parseLicense Text
"CC-BY-3.0-AT" = License
CC_BY_3_0_AT
parseLicense Text
"CC-BY-3.0-US" = License
CC_BY_3_0_US
parseLicense Text
"CC-BY-3.0" = License
CC_BY_3_0
parseLicense Text
"CC-BY-4.0" = License
CC_BY_4_0
parseLicense Text
"CC-BY-NC-1.0" = License
CC_BY_NC_1_0
parseLicense Text
"CC-BY-NC-2.0" = License
CC_BY_NC_2_0
parseLicense Text
"CC-BY-NC-2.5" = License
CC_BY_NC_2_5
parseLicense Text
"CC-BY-NC-3.0" = License
CC_BY_NC_3_0
parseLicense Text
"CC-BY-NC-4.0" = License
CC_BY_NC_4_0
parseLicense Text
"CC-BY-NC-ND-1.0" = License
CC_BY_NC_ND_1_0
parseLicense Text
"CC-BY-NC-ND-2.0" = License
CC_BY_NC_ND_2_0
parseLicense Text
"CC-BY-NC-ND-2.5" = License
CC_BY_NC_ND_2_5
parseLicense Text
"CC-BY-NC-ND-3.0-IGO" = License
CC_BY_NC_ND_3_0_IGO
parseLicense Text
"CC-BY-NC-ND-3.0" = License
CC_BY_NC_ND_3_0
parseLicense Text
"CC-BY-NC-ND-4.0" = License
CC_BY_NC_ND_4_0
parseLicense Text
"CC-BY-NC-SA-1.0" = License
CC_BY_NC_SA_1_0
parseLicense Text
"CC-BY-NC-SA-2.0" = License
CC_BY_NC_SA_2_0
parseLicense Text
"CC-BY-NC-SA-2.5" = License
CC_BY_NC_SA_2_5
parseLicense Text
"CC-BY-NC-SA-3.0" = License
CC_BY_NC_SA_3_0
parseLicense Text
"CC-BY-NC-SA-4.0" = License
CC_BY_NC_SA_4_0
parseLicense Text
"CC-BY-ND-1.0" = License
CC_BY_ND_1_0
parseLicense Text
"CC-BY-ND-2.0" = License
CC_BY_ND_2_0
parseLicense Text
"CC-BY-ND-2.5" = License
CC_BY_ND_2_5
parseLicense Text
"CC-BY-ND-3.0" = License
CC_BY_ND_3_0
parseLicense Text
"CC-BY-ND-4.0" = License
CC_BY_ND_4_0
parseLicense Text
"CC-BY-SA-1.0" = License
CC_BY_SA_1_0
parseLicense Text
"CC-BY-SA-2.0-UK" = License
CC_BY_SA_2_0_UK
parseLicense Text
"CC-BY-SA-2.1-JP" = License
CC_BY_SA_2_1_JP
parseLicense Text
"CC-BY-SA-2.5" = License
CC_BY_SA_2_5
parseLicense Text
"CC-BY-SA-3.0-AT" = License
CC_BY_SA_3_0_AT
parseLicense Text
"CC-BY-SA-3.0" = License
CC_BY_SA_3_0
parseLicense Text
"CC-BY-SA-4.0" = License
CC_BY_SA_4_0
parseLicense Text
"CC-PDDC" = License
CC_PDDC
parseLicense Text
"CC0-1.0" = License
CC0_1_0
parseLicense Text
"CDDL-1.0" = License
CDDL_1_0
parseLicense Text
"CDDL-1.1" = License
CDDL_1_1
parseLicense Text
"CPL-1.0" = License
CPL_1_0
parseLicense Text
"EPL-1.0" = License
EPL_1_0
parseLicense Text
"EPL-2.0" = License
EPL_2_0
parseLicense Text
"FSFAP" = License
FSFAP
parseLicense Text
"GFDL-1.1-invariants-only" = License
GFDL_1_1_invariants_only
parseLicense Text
"GFDL-1.1-invariants-or-later" = License
GFDL_1_1_invariants_or_later
parseLicense Text
"GFDL-1.1-no-invariants-only" = License
GFDL_1_1_no_invariants_only
parseLicense Text
"GFDL-1.1-no-invariants-or-later" = License
GFDL_1_1_no_invariants_or_later
parseLicense Text
"GFDL-1.1-only" = License
GFDL_1_1_only
parseLicense Text
"GFDL-1.1-or-later" = License
GFDL_1_1_or_later
parseLicense Text
"GFDL-1.2-invariants-only" = License
GFDL_1_2_invariants_only
parseLicense Text
"GFDL-1.2-invariants-or-later" = License
GFDL_1_2_invariants_or_later
parseLicense Text
"GFDL-1.2-no-invariants-only" = License
GFDL_1_2_no_invariants_only
parseLicense Text
"GFDL-1.2-no-invariants-or-later" = License
GFDL_1_2_no_invariants_or_later
parseLicense Text
"GFDL-1.2-only" = License
GFDL_1_2_only
parseLicense Text
"GFDL-1.2-or-later" = License
GFDL_1_2_or_later
parseLicense Text
"GFDL-1.3-invariants-only" = License
GFDL_1_3_invariants_only
parseLicense Text
"GFDL-1.3-invariants-or-later" = License
GFDL_1_3_invariants_or_later
parseLicense Text
"GFDL-1.3-no-invariants-only" = License
GFDL_1_3_no_invariants_only
parseLicense Text
"GFDL-1.3-no-invariants-or-later" = License
GFDL_1_3_no_invariants_or_later
parseLicense Text
"GFDL-1.3-only" = License
GFDL_1_3_only
parseLicense Text
"GFDL-1.3-or-later" = License
GFDL_1_3_or_later
parseLicense Text
"GPL-1.0-only" = License
GPL_1_0_only
parseLicense Text
"GPL-1.0-or-later" = License
GPL_1_0_or_later
parseLicense Text
"GPL-2.0-only" = License
GPL_2_0_only
parseLicense Text
"GPL-2.0-or-later" = License
GPL_2_0_or_later
parseLicense Text
"GPL-3.0-only" = License
GPL_3_0_only
parseLicense Text
"GPL-3.0-or-later" = License
GPL_3_0_or_later
parseLicense Text
"LGPL-2.0-only" = License
LGPL_2_0_only
parseLicense Text
"LGPL-2.0-or-later" = License
LGPL_2_0_or_later
parseLicense Text
"LGPL-2.1-only" = License
LGPL_2_1_only
parseLicense Text
"LGPL-2.1-or-later" = License
LGPL_2_1_or_later
parseLicense Text
"LGPL-3.0-only" = License
LGPL_3_0_only
parseLicense Text
"LGPL-3.0-or-later" = License
LGPL_3_0_or_later
parseLicense Text
"LGPLLR" = License
LGPLLR
parseLicense Text
"LPPL-1.0" = License
LPPL_1_0
parseLicense Text
"LPPL-1.1" = License
LPPL_1_1
parseLicense Text
"LPPL-1.2" = License
LPPL_1_2
parseLicense Text
"LPPL-1.3a" = License
LPPL_1_3a
parseLicense Text
"LPPL-1.3c" = License
LPPL_1_3c
parseLicense Text
"MPL-1.0" = License
MPL_1_0
parseLicense Text
"MPL-1.1" = License
MPL_1_1
parseLicense Text
"MPL-2.0" = License
MPL_2_0
parseLicense Text
"PHP-3.0" = License
PHP_3_0
parseLicense Text
"PHP-3.01" = License
PHP_3_01
parseLicense Text
"PSF-2.0" = License
PSF_2_0
parseLicense Text
"Ruby" = License
Ruby
parseLicense Text
"Unlicense" = License
Unlicense
parseLicense Text
"W3C" = License
W3C
parseLicense Text
"WTFPL" = License
WTFPL
parseLicense Text
"ZPL-1.1" = License
ZPL_1_1
parseLicense Text
"ZPL-2.0" = License
ZPL_2_0
parseLicense Text
"ZPL-2.1" = License
ZPL_2_1
parseLicense Text
x = Text -> License
Custom Text
x
instance ToJSON License where
toJSON :: License -> Value
toJSON License
x = Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ License -> Text
licenseId License
x
instance FromJSON License where
parseJSON :: Value -> Parser License
parseJSON = String -> (Text -> Parser License) -> Value -> Parser License
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"License" ((Text -> Parser License) -> Value -> Parser License)
-> (Text -> Parser License) -> Value -> Parser License
forall a b. (a -> b) -> a -> b
$ \Text
txt -> License -> Parser License
forall a. a -> Parser a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Text -> License
parseLicense Text
txt)
data PackageInformation = PackageInformation
{ PackageInformation -> Text
_pkgname :: Text,
PackageInformation -> Text
_pkgbase :: Text,
PackageInformation -> Repo
_repo :: Repo,
PackageInformation -> Arch
_arch :: Arch,
PackageInformation -> Text
_pkgver :: Text,
PackageInformation -> Text
_pkgrel :: Text,
PackageInformation -> Int
_epoch :: Int,
PackageInformation -> Text
_pkgdesc :: Text,
PackageInformation -> Text
_url :: Text,
PackageInformation -> Text
_filename :: Text,
PackageInformation -> Int
_compressedSize :: Int,
PackageInformation -> Int
_installedSize :: Int,
PackageInformation -> UTCTime
_buildDate :: UTCTime,
PackageInformation -> UTCTime
_lastUpdate :: UTCTime,
PackageInformation -> Maybe UTCTime
_flageDate :: Maybe UTCTime,
PackageInformation -> [Text]
_maintainers :: [Text],
PackageInformation -> Text
_packager :: Text,
PackageInformation -> [Text]
_groups :: [Text],
PackageInformation -> [License]
_licenses :: [License],
PackageInformation -> [Text]
_conflicts :: [Text],
PackageInformation -> [Text]
_provides :: [Text],
PackageInformation -> [Text]
_replaces :: [Text],
PackageInformation -> [Text]
_depends :: [Text],
PackageInformation -> [Text]
_optdepends :: [Text],
PackageInformation -> [Text]
_makedepends :: [Text],
PackageInformation -> [Text]
_checkdepends :: [Text]
}
deriving stock (Int -> PackageInformation -> String -> String
[PackageInformation] -> String -> String
PackageInformation -> String
(Int -> PackageInformation -> String -> String)
-> (PackageInformation -> String)
-> ([PackageInformation] -> String -> String)
-> Show PackageInformation
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PackageInformation -> String -> String
showsPrec :: Int -> PackageInformation -> String -> String
$cshow :: PackageInformation -> String
show :: PackageInformation -> String
$cshowList :: [PackageInformation] -> String -> String
showList :: [PackageInformation] -> String -> String
Show, PackageInformation -> PackageInformation -> Bool
(PackageInformation -> PackageInformation -> Bool)
-> (PackageInformation -> PackageInformation -> Bool)
-> Eq PackageInformation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PackageInformation -> PackageInformation -> Bool
== :: PackageInformation -> PackageInformation -> Bool
$c/= :: PackageInformation -> PackageInformation -> Bool
/= :: PackageInformation -> PackageInformation -> Bool
Eq, Eq PackageInformation
Eq PackageInformation =>
(PackageInformation -> PackageInformation -> Ordering)
-> (PackageInformation -> PackageInformation -> Bool)
-> (PackageInformation -> PackageInformation -> Bool)
-> (PackageInformation -> PackageInformation -> Bool)
-> (PackageInformation -> PackageInformation -> Bool)
-> (PackageInformation -> PackageInformation -> PackageInformation)
-> (PackageInformation -> PackageInformation -> PackageInformation)
-> Ord PackageInformation
PackageInformation -> PackageInformation -> Bool
PackageInformation -> PackageInformation -> Ordering
PackageInformation -> PackageInformation -> PackageInformation
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
$ccompare :: PackageInformation -> PackageInformation -> Ordering
compare :: PackageInformation -> PackageInformation -> Ordering
$c< :: PackageInformation -> PackageInformation -> Bool
< :: PackageInformation -> PackageInformation -> Bool
$c<= :: PackageInformation -> PackageInformation -> Bool
<= :: PackageInformation -> PackageInformation -> Bool
$c> :: PackageInformation -> PackageInformation -> Bool
> :: PackageInformation -> PackageInformation -> Bool
$c>= :: PackageInformation -> PackageInformation -> Bool
>= :: PackageInformation -> PackageInformation -> Bool
$cmax :: PackageInformation -> PackageInformation -> PackageInformation
max :: PackageInformation -> PackageInformation -> PackageInformation
$cmin :: PackageInformation -> PackageInformation -> PackageInformation
min :: PackageInformation -> PackageInformation -> PackageInformation
Ord, (forall x. PackageInformation -> Rep PackageInformation x)
-> (forall x. Rep PackageInformation x -> PackageInformation)
-> Generic PackageInformation
forall x. Rep PackageInformation x -> PackageInformation
forall x. PackageInformation -> Rep PackageInformation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PackageInformation -> Rep PackageInformation x
from :: forall x. PackageInformation -> Rep PackageInformation x
$cto :: forall x. Rep PackageInformation x -> PackageInformation
to :: forall x. Rep PackageInformation x -> PackageInformation
Generic)
deriving (Maybe PackageInformation
Value -> Parser [PackageInformation]
Value -> Parser PackageInformation
(Value -> Parser PackageInformation)
-> (Value -> Parser [PackageInformation])
-> Maybe PackageInformation
-> FromJSON PackageInformation
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PackageInformation
parseJSON :: Value -> Parser PackageInformation
$cparseJSONList :: Value -> Parser [PackageInformation]
parseJSONList :: Value -> Parser [PackageInformation]
$comittedField :: Maybe PackageInformation
omittedField :: Maybe PackageInformation
FromJSON, [PackageInformation] -> Value
[PackageInformation] -> Encoding
PackageInformation -> Bool
PackageInformation -> Value
PackageInformation -> Encoding
(PackageInformation -> Value)
-> (PackageInformation -> Encoding)
-> ([PackageInformation] -> Value)
-> ([PackageInformation] -> Encoding)
-> (PackageInformation -> Bool)
-> ToJSON PackageInformation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: PackageInformation -> Value
toJSON :: PackageInformation -> Value
$ctoEncoding :: PackageInformation -> Encoding
toEncoding :: PackageInformation -> Encoding
$ctoJSONList :: [PackageInformation] -> Value
toJSONList :: [PackageInformation] -> Value
$ctoEncodingList :: [PackageInformation] -> Encoding
toEncodingList :: [PackageInformation] -> Encoding
$comitField :: PackageInformation -> Bool
omitField :: PackageInformation -> Bool
ToJSON) via ArchLinuxJSON PackageInformation
data PackageFiles = PackageFiles
{ PackageFiles -> Text
_pkgname :: Text,
PackageFiles -> Repo
_repo :: Repo,
PackageFiles -> Arch
_arch :: Arch,
PackageFiles -> UTCTime
_pkgLastUpdate :: UTCTime,
PackageFiles -> UTCTime
_filesLastUpdate :: UTCTime,
PackageFiles -> Int
_filesCount :: Int,
PackageFiles -> Int
_dirCount :: Int,
PackageFiles -> [String]
_files :: [FilePath]
}
deriving stock (Int -> PackageFiles -> String -> String
[PackageFiles] -> String -> String
PackageFiles -> String
(Int -> PackageFiles -> String -> String)
-> (PackageFiles -> String)
-> ([PackageFiles] -> String -> String)
-> Show PackageFiles
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PackageFiles -> String -> String
showsPrec :: Int -> PackageFiles -> String -> String
$cshow :: PackageFiles -> String
show :: PackageFiles -> String
$cshowList :: [PackageFiles] -> String -> String
showList :: [PackageFiles] -> String -> String
Show, PackageFiles -> PackageFiles -> Bool
(PackageFiles -> PackageFiles -> Bool)
-> (PackageFiles -> PackageFiles -> Bool) -> Eq PackageFiles
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PackageFiles -> PackageFiles -> Bool
== :: PackageFiles -> PackageFiles -> Bool
$c/= :: PackageFiles -> PackageFiles -> Bool
/= :: PackageFiles -> PackageFiles -> Bool
Eq, Eq PackageFiles
Eq PackageFiles =>
(PackageFiles -> PackageFiles -> Ordering)
-> (PackageFiles -> PackageFiles -> Bool)
-> (PackageFiles -> PackageFiles -> Bool)
-> (PackageFiles -> PackageFiles -> Bool)
-> (PackageFiles -> PackageFiles -> Bool)
-> (PackageFiles -> PackageFiles -> PackageFiles)
-> (PackageFiles -> PackageFiles -> PackageFiles)
-> Ord PackageFiles
PackageFiles -> PackageFiles -> Bool
PackageFiles -> PackageFiles -> Ordering
PackageFiles -> PackageFiles -> PackageFiles
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
$ccompare :: PackageFiles -> PackageFiles -> Ordering
compare :: PackageFiles -> PackageFiles -> Ordering
$c< :: PackageFiles -> PackageFiles -> Bool
< :: PackageFiles -> PackageFiles -> Bool
$c<= :: PackageFiles -> PackageFiles -> Bool
<= :: PackageFiles -> PackageFiles -> Bool
$c> :: PackageFiles -> PackageFiles -> Bool
> :: PackageFiles -> PackageFiles -> Bool
$c>= :: PackageFiles -> PackageFiles -> Bool
>= :: PackageFiles -> PackageFiles -> Bool
$cmax :: PackageFiles -> PackageFiles -> PackageFiles
max :: PackageFiles -> PackageFiles -> PackageFiles
$cmin :: PackageFiles -> PackageFiles -> PackageFiles
min :: PackageFiles -> PackageFiles -> PackageFiles
Ord, (forall x. PackageFiles -> Rep PackageFiles x)
-> (forall x. Rep PackageFiles x -> PackageFiles)
-> Generic PackageFiles
forall x. Rep PackageFiles x -> PackageFiles
forall x. PackageFiles -> Rep PackageFiles x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PackageFiles -> Rep PackageFiles x
from :: forall x. PackageFiles -> Rep PackageFiles x
$cto :: forall x. Rep PackageFiles x -> PackageFiles
to :: forall x. Rep PackageFiles x -> PackageFiles
Generic)
deriving (Maybe PackageFiles
Value -> Parser [PackageFiles]
Value -> Parser PackageFiles
(Value -> Parser PackageFiles)
-> (Value -> Parser [PackageFiles])
-> Maybe PackageFiles
-> FromJSON PackageFiles
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PackageFiles
parseJSON :: Value -> Parser PackageFiles
$cparseJSONList :: Value -> Parser [PackageFiles]
parseJSONList :: Value -> Parser [PackageFiles]
$comittedField :: Maybe PackageFiles
omittedField :: Maybe PackageFiles
FromJSON, [PackageFiles] -> Value
[PackageFiles] -> Encoding
PackageFiles -> Bool
PackageFiles -> Value
PackageFiles -> Encoding
(PackageFiles -> Value)
-> (PackageFiles -> Encoding)
-> ([PackageFiles] -> Value)
-> ([PackageFiles] -> Encoding)
-> (PackageFiles -> Bool)
-> ToJSON PackageFiles
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: PackageFiles -> Value
toJSON :: PackageFiles -> Value
$ctoEncoding :: PackageFiles -> Encoding
toEncoding :: PackageFiles -> Encoding
$ctoJSONList :: [PackageFiles] -> Value
toJSONList :: [PackageFiles] -> Value
$ctoEncodingList :: [PackageFiles] -> Encoding
toEncodingList :: [PackageFiles] -> Encoding
$comitField :: PackageFiles -> Bool
omitField :: PackageFiles -> Bool
ToJSON) via ArchLinuxJSON PackageFiles
data Flagged = Flagged | NotFlagged
deriving stock (Int -> Flagged -> String -> String
[Flagged] -> String -> String
Flagged -> String
(Int -> Flagged -> String -> String)
-> (Flagged -> String)
-> ([Flagged] -> String -> String)
-> Show Flagged
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Flagged -> String -> String
showsPrec :: Int -> Flagged -> String -> String
$cshow :: Flagged -> String
show :: Flagged -> String
$cshowList :: [Flagged] -> String -> String
showList :: [Flagged] -> String -> String
Show, Flagged -> Flagged -> Bool
(Flagged -> Flagged -> Bool)
-> (Flagged -> Flagged -> Bool) -> Eq Flagged
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Flagged -> Flagged -> Bool
== :: Flagged -> Flagged -> Bool
$c/= :: Flagged -> Flagged -> Bool
/= :: Flagged -> Flagged -> Bool
Eq, Eq Flagged
Eq Flagged =>
(Flagged -> Flagged -> Ordering)
-> (Flagged -> Flagged -> Bool)
-> (Flagged -> Flagged -> Bool)
-> (Flagged -> Flagged -> Bool)
-> (Flagged -> Flagged -> Bool)
-> (Flagged -> Flagged -> Flagged)
-> (Flagged -> Flagged -> Flagged)
-> Ord Flagged
Flagged -> Flagged -> Bool
Flagged -> Flagged -> Ordering
Flagged -> Flagged -> Flagged
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
$ccompare :: Flagged -> Flagged -> Ordering
compare :: Flagged -> Flagged -> Ordering
$c< :: Flagged -> Flagged -> Bool
< :: Flagged -> Flagged -> Bool
$c<= :: Flagged -> Flagged -> Bool
<= :: Flagged -> Flagged -> Bool
$c> :: Flagged -> Flagged -> Bool
> :: Flagged -> Flagged -> Bool
$c>= :: Flagged -> Flagged -> Bool
>= :: Flagged -> Flagged -> Bool
$cmax :: Flagged -> Flagged -> Flagged
max :: Flagged -> Flagged -> Flagged
$cmin :: Flagged -> Flagged -> Flagged
min :: Flagged -> Flagged -> Flagged
Ord, Int -> Flagged
Flagged -> Int
Flagged -> [Flagged]
Flagged -> Flagged
Flagged -> Flagged -> [Flagged]
Flagged -> Flagged -> Flagged -> [Flagged]
(Flagged -> Flagged)
-> (Flagged -> Flagged)
-> (Int -> Flagged)
-> (Flagged -> Int)
-> (Flagged -> [Flagged])
-> (Flagged -> Flagged -> [Flagged])
-> (Flagged -> Flagged -> [Flagged])
-> (Flagged -> Flagged -> Flagged -> [Flagged])
-> Enum Flagged
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Flagged -> Flagged
succ :: Flagged -> Flagged
$cpred :: Flagged -> Flagged
pred :: Flagged -> Flagged
$ctoEnum :: Int -> Flagged
toEnum :: Int -> Flagged
$cfromEnum :: Flagged -> Int
fromEnum :: Flagged -> Int
$cenumFrom :: Flagged -> [Flagged]
enumFrom :: Flagged -> [Flagged]
$cenumFromThen :: Flagged -> Flagged -> [Flagged]
enumFromThen :: Flagged -> Flagged -> [Flagged]
$cenumFromTo :: Flagged -> Flagged -> [Flagged]
enumFromTo :: Flagged -> Flagged -> [Flagged]
$cenumFromThenTo :: Flagged -> Flagged -> Flagged -> [Flagged]
enumFromThenTo :: Flagged -> Flagged -> Flagged -> [Flagged]
Enum, (forall x. Flagged -> Rep Flagged x)
-> (forall x. Rep Flagged x -> Flagged) -> Generic Flagged
forall x. Rep Flagged x -> Flagged
forall x. Flagged -> Rep Flagged x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Flagged -> Rep Flagged x
from :: forall x. Flagged -> Rep Flagged x
$cto :: forall x. Rep Flagged x -> Flagged
to :: forall x. Rep Flagged x -> Flagged
Generic)
instance ToHttpApiData Flagged where
toQueryParam :: Flagged -> Text
toQueryParam Flagged
Flagged = Text
"Flagged"
toQueryParam Flagged
NotFlagged = Text
"Not+Flagged"
data ArchLinuxResponse a = ArchLinuxResponse
{ forall a. ArchLinuxResponse a -> Int
_version :: Int,
forall a. ArchLinuxResponse a -> Int
_limit :: Int,
forall a. ArchLinuxResponse a -> Bool
_valid :: Bool,
forall a. ArchLinuxResponse a -> [a]
_results :: [a]
}
deriving stock (Int -> ArchLinuxResponse a -> String -> String
[ArchLinuxResponse a] -> String -> String
ArchLinuxResponse a -> String
(Int -> ArchLinuxResponse a -> String -> String)
-> (ArchLinuxResponse a -> String)
-> ([ArchLinuxResponse a] -> String -> String)
-> Show (ArchLinuxResponse a)
forall a. Show a => Int -> ArchLinuxResponse a -> String -> String
forall a. Show a => [ArchLinuxResponse a] -> String -> String
forall a. Show a => ArchLinuxResponse a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: forall a. Show a => Int -> ArchLinuxResponse a -> String -> String
showsPrec :: Int -> ArchLinuxResponse a -> String -> String
$cshow :: forall a. Show a => ArchLinuxResponse a -> String
show :: ArchLinuxResponse a -> String
$cshowList :: forall a. Show a => [ArchLinuxResponse a] -> String -> String
showList :: [ArchLinuxResponse a] -> String -> String
Show, ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
(ArchLinuxResponse a -> ArchLinuxResponse a -> Bool)
-> (ArchLinuxResponse a -> ArchLinuxResponse a -> Bool)
-> Eq (ArchLinuxResponse a)
forall a.
Eq a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a.
Eq a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
== :: ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
$c/= :: forall a.
Eq a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
/= :: ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
Eq, Eq (ArchLinuxResponse a)
Eq (ArchLinuxResponse a) =>
(ArchLinuxResponse a -> ArchLinuxResponse a -> Ordering)
-> (ArchLinuxResponse a -> ArchLinuxResponse a -> Bool)
-> (ArchLinuxResponse a -> ArchLinuxResponse a -> Bool)
-> (ArchLinuxResponse a -> ArchLinuxResponse a -> Bool)
-> (ArchLinuxResponse a -> ArchLinuxResponse a -> Bool)
-> (ArchLinuxResponse a
-> ArchLinuxResponse a -> ArchLinuxResponse a)
-> (ArchLinuxResponse a
-> ArchLinuxResponse a -> ArchLinuxResponse a)
-> Ord (ArchLinuxResponse a)
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
ArchLinuxResponse a -> ArchLinuxResponse a -> Ordering
ArchLinuxResponse a -> ArchLinuxResponse a -> ArchLinuxResponse a
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
forall a. Ord a => Eq (ArchLinuxResponse a)
forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Ordering
forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> ArchLinuxResponse a
$ccompare :: forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Ordering
compare :: ArchLinuxResponse a -> ArchLinuxResponse a -> Ordering
$c< :: forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
< :: ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
$c<= :: forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
<= :: ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
$c> :: forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
> :: ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
$c>= :: forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
>= :: ArchLinuxResponse a -> ArchLinuxResponse a -> Bool
$cmax :: forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> ArchLinuxResponse a
max :: ArchLinuxResponse a -> ArchLinuxResponse a -> ArchLinuxResponse a
$cmin :: forall a.
Ord a =>
ArchLinuxResponse a -> ArchLinuxResponse a -> ArchLinuxResponse a
min :: ArchLinuxResponse a -> ArchLinuxResponse a -> ArchLinuxResponse a
Ord, (forall a b.
(a -> b) -> ArchLinuxResponse a -> ArchLinuxResponse b)
-> (forall a b. a -> ArchLinuxResponse b -> ArchLinuxResponse a)
-> Functor ArchLinuxResponse
forall a b. a -> ArchLinuxResponse b -> ArchLinuxResponse a
forall a b. (a -> b) -> ArchLinuxResponse a -> ArchLinuxResponse b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> ArchLinuxResponse a -> ArchLinuxResponse b
fmap :: forall a b. (a -> b) -> ArchLinuxResponse a -> ArchLinuxResponse b
$c<$ :: forall a b. a -> ArchLinuxResponse b -> ArchLinuxResponse a
<$ :: forall a b. a -> ArchLinuxResponse b -> ArchLinuxResponse a
Functor, (forall x. ArchLinuxResponse a -> Rep (ArchLinuxResponse a) x)
-> (forall x. Rep (ArchLinuxResponse a) x -> ArchLinuxResponse a)
-> Generic (ArchLinuxResponse a)
forall x. Rep (ArchLinuxResponse a) x -> ArchLinuxResponse a
forall x. ArchLinuxResponse a -> Rep (ArchLinuxResponse a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (ArchLinuxResponse a) x -> ArchLinuxResponse a
forall a x. ArchLinuxResponse a -> Rep (ArchLinuxResponse a) x
$cfrom :: forall a x. ArchLinuxResponse a -> Rep (ArchLinuxResponse a) x
from :: forall x. ArchLinuxResponse a -> Rep (ArchLinuxResponse a) x
$cto :: forall a x. Rep (ArchLinuxResponse a) x -> ArchLinuxResponse a
to :: forall x. Rep (ArchLinuxResponse a) x -> ArchLinuxResponse a
Generic)
deriving via ArchLinuxJSON (ArchLinuxResponse a) instance (FromJSON a) => FromJSON (ArchLinuxResponse a)
deriving via ArchLinuxJSON (ArchLinuxResponse a) instance (ToJSON a) => ToJSON (ArchLinuxResponse a)
data AurSearch = AurSearch
{ AurSearch -> Int
_id :: Int,
AurSearch -> Text
_name :: Text,
AurSearch -> Int
_packageBaseID :: Int,
AurSearch -> Text
_packageBase :: Text,
AurSearch -> Text
_version :: Text,
AurSearch -> Maybe Text
_description :: Maybe Text,
AurSearch -> Maybe Text
_url :: Maybe Text,
AurSearch -> Int
_numVotes :: Int,
AurSearch -> Double
_popularity :: Double,
AurSearch -> Maybe Int
_outOfDate :: Maybe Int,
AurSearch -> Maybe Text
_maintainer :: Maybe Text,
AurSearch -> Int
_firstSubmitted :: Int,
AurSearch -> Int
_lastModified :: Int,
AurSearch -> Text
_urlPath :: Text
}
deriving stock (Int -> AurSearch -> String -> String
[AurSearch] -> String -> String
AurSearch -> String
(Int -> AurSearch -> String -> String)
-> (AurSearch -> String)
-> ([AurSearch] -> String -> String)
-> Show AurSearch
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AurSearch -> String -> String
showsPrec :: Int -> AurSearch -> String -> String
$cshow :: AurSearch -> String
show :: AurSearch -> String
$cshowList :: [AurSearch] -> String -> String
showList :: [AurSearch] -> String -> String
Show, AurSearch -> AurSearch -> Bool
(AurSearch -> AurSearch -> Bool)
-> (AurSearch -> AurSearch -> Bool) -> Eq AurSearch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AurSearch -> AurSearch -> Bool
== :: AurSearch -> AurSearch -> Bool
$c/= :: AurSearch -> AurSearch -> Bool
/= :: AurSearch -> AurSearch -> Bool
Eq, Eq AurSearch
Eq AurSearch =>
(AurSearch -> AurSearch -> Ordering)
-> (AurSearch -> AurSearch -> Bool)
-> (AurSearch -> AurSearch -> Bool)
-> (AurSearch -> AurSearch -> Bool)
-> (AurSearch -> AurSearch -> Bool)
-> (AurSearch -> AurSearch -> AurSearch)
-> (AurSearch -> AurSearch -> AurSearch)
-> Ord AurSearch
AurSearch -> AurSearch -> Bool
AurSearch -> AurSearch -> Ordering
AurSearch -> AurSearch -> AurSearch
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
$ccompare :: AurSearch -> AurSearch -> Ordering
compare :: AurSearch -> AurSearch -> Ordering
$c< :: AurSearch -> AurSearch -> Bool
< :: AurSearch -> AurSearch -> Bool
$c<= :: AurSearch -> AurSearch -> Bool
<= :: AurSearch -> AurSearch -> Bool
$c> :: AurSearch -> AurSearch -> Bool
> :: AurSearch -> AurSearch -> Bool
$c>= :: AurSearch -> AurSearch -> Bool
>= :: AurSearch -> AurSearch -> Bool
$cmax :: AurSearch -> AurSearch -> AurSearch
max :: AurSearch -> AurSearch -> AurSearch
$cmin :: AurSearch -> AurSearch -> AurSearch
min :: AurSearch -> AurSearch -> AurSearch
Ord, (forall x. AurSearch -> Rep AurSearch x)
-> (forall x. Rep AurSearch x -> AurSearch) -> Generic AurSearch
forall x. Rep AurSearch x -> AurSearch
forall x. AurSearch -> Rep AurSearch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AurSearch -> Rep AurSearch x
from :: forall x. AurSearch -> Rep AurSearch x
$cto :: forall x. Rep AurSearch x -> AurSearch
to :: forall x. Rep AurSearch x -> AurSearch
Generic)
deriving (Maybe AurSearch
Value -> Parser [AurSearch]
Value -> Parser AurSearch
(Value -> Parser AurSearch)
-> (Value -> Parser [AurSearch])
-> Maybe AurSearch
-> FromJSON AurSearch
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AurSearch
parseJSON :: Value -> Parser AurSearch
$cparseJSONList :: Value -> Parser [AurSearch]
parseJSONList :: Value -> Parser [AurSearch]
$comittedField :: Maybe AurSearch
omittedField :: Maybe AurSearch
FromJSON, [AurSearch] -> Value
[AurSearch] -> Encoding
AurSearch -> Bool
AurSearch -> Value
AurSearch -> Encoding
(AurSearch -> Value)
-> (AurSearch -> Encoding)
-> ([AurSearch] -> Value)
-> ([AurSearch] -> Encoding)
-> (AurSearch -> Bool)
-> ToJSON AurSearch
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AurSearch -> Value
toJSON :: AurSearch -> Value
$ctoEncoding :: AurSearch -> Encoding
toEncoding :: AurSearch -> Encoding
$ctoJSONList :: [AurSearch] -> Value
toJSONList :: [AurSearch] -> Value
$ctoEncodingList :: [AurSearch] -> Encoding
toEncodingList :: [AurSearch] -> Encoding
$comitField :: AurSearch -> Bool
omitField :: AurSearch -> Bool
ToJSON) via AurJSON AurSearch
data AurInfo = AurInfo
{
AurInfo -> AurSearch
_search :: AurSearch,
AurInfo -> [Text]
_depends :: [Text],
AurInfo -> [Text]
_makedepends :: [Text],
AurInfo -> [Text]
_optdepends :: [Text],
AurInfo -> [Text]
_checkdepends :: [Text],
AurInfo -> [Text]
_conflicts :: [Text],
AurInfo -> [Text]
_provides :: [Text],
AurInfo -> [Text]
_replaces :: [Text],
AurInfo -> [Text]
_groups :: [Text],
AurInfo -> [License]
_licenses :: [License],
AurInfo -> [Text]
_keywords :: [Text]
}
deriving stock (Int -> AurInfo -> String -> String
[AurInfo] -> String -> String
AurInfo -> String
(Int -> AurInfo -> String -> String)
-> (AurInfo -> String)
-> ([AurInfo] -> String -> String)
-> Show AurInfo
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AurInfo -> String -> String
showsPrec :: Int -> AurInfo -> String -> String
$cshow :: AurInfo -> String
show :: AurInfo -> String
$cshowList :: [AurInfo] -> String -> String
showList :: [AurInfo] -> String -> String
Show, AurInfo -> AurInfo -> Bool
(AurInfo -> AurInfo -> Bool)
-> (AurInfo -> AurInfo -> Bool) -> Eq AurInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AurInfo -> AurInfo -> Bool
== :: AurInfo -> AurInfo -> Bool
$c/= :: AurInfo -> AurInfo -> Bool
/= :: AurInfo -> AurInfo -> Bool
Eq, Eq AurInfo
Eq AurInfo =>
(AurInfo -> AurInfo -> Ordering)
-> (AurInfo -> AurInfo -> Bool)
-> (AurInfo -> AurInfo -> Bool)
-> (AurInfo -> AurInfo -> Bool)
-> (AurInfo -> AurInfo -> Bool)
-> (AurInfo -> AurInfo -> AurInfo)
-> (AurInfo -> AurInfo -> AurInfo)
-> Ord AurInfo
AurInfo -> AurInfo -> Bool
AurInfo -> AurInfo -> Ordering
AurInfo -> AurInfo -> AurInfo
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
$ccompare :: AurInfo -> AurInfo -> Ordering
compare :: AurInfo -> AurInfo -> Ordering
$c< :: AurInfo -> AurInfo -> Bool
< :: AurInfo -> AurInfo -> Bool
$c<= :: AurInfo -> AurInfo -> Bool
<= :: AurInfo -> AurInfo -> Bool
$c> :: AurInfo -> AurInfo -> Bool
> :: AurInfo -> AurInfo -> Bool
$c>= :: AurInfo -> AurInfo -> Bool
>= :: AurInfo -> AurInfo -> Bool
$cmax :: AurInfo -> AurInfo -> AurInfo
max :: AurInfo -> AurInfo -> AurInfo
$cmin :: AurInfo -> AurInfo -> AurInfo
min :: AurInfo -> AurInfo -> AurInfo
Ord, (forall x. AurInfo -> Rep AurInfo x)
-> (forall x. Rep AurInfo x -> AurInfo) -> Generic AurInfo
forall x. Rep AurInfo x -> AurInfo
forall x. AurInfo -> Rep AurInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AurInfo -> Rep AurInfo x
from :: forall x. AurInfo -> Rep AurInfo x
$cto :: forall x. Rep AurInfo x -> AurInfo
to :: forall x. Rep AurInfo x -> AurInfo
Generic)
instance FromJSON AurInfo where
parseJSON :: Value -> Parser AurInfo
parseJSON = String -> (Object -> Parser AurInfo) -> Value -> Parser AurInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AurInfo" ((Object -> Parser AurInfo) -> Value -> Parser AurInfo)
-> (Object -> Parser AurInfo) -> Value -> Parser AurInfo
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
AurSearch
_search <- Value -> Parser AurSearch
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser AurSearch) -> Value -> Parser AurSearch
forall a b. (a -> b) -> a -> b
$ Object -> Value
Object Object
o
[Text]
_depends <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Depends"
[Text]
_makedepends <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"MakeDepends"
[Text]
_optdepends <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"OptDepends"
[Text]
_checkdepends <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"CheckDepends"
[Text]
_conflicts <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Conflicts"
[Text]
_provides <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Provides"
[Text]
_replaces <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Replaces"
[Text]
_groups <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Groups"
[License]
_licenses <- [License] -> Maybe [License] -> [License]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [License] -> [License])
-> Parser (Maybe [License]) -> Parser [License]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [License])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"License"
[Text]
_keywords <- [Text] -> Maybe [Text] -> [Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Text] -> [Text]) -> Parser (Maybe [Text]) -> Parser [Text]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Keywords"
AurInfo -> Parser AurInfo
forall a. a -> Parser a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure AurInfo {[Text]
[License]
AurSearch
_search :: AurSearch
$sel:_depends:AurInfo :: [Text]
$sel:_makedepends:AurInfo :: [Text]
$sel:_optdepends:AurInfo :: [Text]
$sel:_checkdepends:AurInfo :: [Text]
$sel:_conflicts:AurInfo :: [Text]
$sel:_provides:AurInfo :: [Text]
$sel:_replaces:AurInfo :: [Text]
$sel:_groups:AurInfo :: [Text]
$sel:_licenses:AurInfo :: [License]
$sel:_keywords:AurInfo :: [Text]
_search :: AurSearch
_depends :: [Text]
_makedepends :: [Text]
_optdepends :: [Text]
_checkdepends :: [Text]
_conflicts :: [Text]
_provides :: [Text]
_replaces :: [Text]
_groups :: [Text]
_licenses :: [License]
_keywords :: [Text]
..}
instance ToJSON AurInfo where
toJSON :: AurInfo -> Value
toJSON AurInfo {[Text]
[License]
AurSearch
_search :: AurInfo -> AurSearch
$sel:_depends:AurInfo :: AurInfo -> [Text]
$sel:_makedepends:AurInfo :: AurInfo -> [Text]
$sel:_optdepends:AurInfo :: AurInfo -> [Text]
$sel:_checkdepends:AurInfo :: AurInfo -> [Text]
$sel:_conflicts:AurInfo :: AurInfo -> [Text]
$sel:_provides:AurInfo :: AurInfo -> [Text]
$sel:_replaces:AurInfo :: AurInfo -> [Text]
$sel:_groups:AurInfo :: AurInfo -> [Text]
$sel:_licenses:AurInfo :: AurInfo -> [License]
$sel:_keywords:AurInfo :: AurInfo -> [Text]
_search :: AurSearch
_depends :: [Text]
_makedepends :: [Text]
_optdepends :: [Text]
_checkdepends :: [Text]
_conflicts :: [Text]
_provides :: [Text]
_replaces :: [Text]
_groups :: [Text]
_licenses :: [License]
_keywords :: [Text]
..} =
Object -> Value
Object (Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$
Value -> Object
unObject (AurSearch -> Value
forall a. ToJSON a => a -> Value
toJSON AurSearch
_search)
Object -> Object -> Object
forall a. Semigroup a => a -> a -> a
<> Value -> Object
unObject
( [Pair] -> Value
object
[ Key
"Depends" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_depends,
Key
"MakeDepends" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_makedepends,
Key
"OptDepends" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_optdepends,
Key
"CheckDepends" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_checkdepends,
Key
"Conflicts" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_conflicts,
Key
"Provides" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_provides,
Key
"Replaces" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_replaces,
Key
"Groups" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_groups,
Key
"License" Key -> [License] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [License]
_licenses,
Key
"Keywords" Key -> [Text] -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Text]
_keywords
]
)
where
unObject :: Value -> Object
unObject (Object Object
o) = Object
o
unObject Value
_ = String -> Object
forall a. HasCallStack => String -> a
error String
"impossible"
data AurResponseType = Search | Multiinfo | Error
deriving stock (Int -> AurResponseType -> String -> String
[AurResponseType] -> String -> String
AurResponseType -> String
(Int -> AurResponseType -> String -> String)
-> (AurResponseType -> String)
-> ([AurResponseType] -> String -> String)
-> Show AurResponseType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AurResponseType -> String -> String
showsPrec :: Int -> AurResponseType -> String -> String
$cshow :: AurResponseType -> String
show :: AurResponseType -> String
$cshowList :: [AurResponseType] -> String -> String
showList :: [AurResponseType] -> String -> String
Show, AurResponseType -> AurResponseType -> Bool
(AurResponseType -> AurResponseType -> Bool)
-> (AurResponseType -> AurResponseType -> Bool)
-> Eq AurResponseType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AurResponseType -> AurResponseType -> Bool
== :: AurResponseType -> AurResponseType -> Bool
$c/= :: AurResponseType -> AurResponseType -> Bool
/= :: AurResponseType -> AurResponseType -> Bool
Eq, Eq AurResponseType
Eq AurResponseType =>
(AurResponseType -> AurResponseType -> Ordering)
-> (AurResponseType -> AurResponseType -> Bool)
-> (AurResponseType -> AurResponseType -> Bool)
-> (AurResponseType -> AurResponseType -> Bool)
-> (AurResponseType -> AurResponseType -> Bool)
-> (AurResponseType -> AurResponseType -> AurResponseType)
-> (AurResponseType -> AurResponseType -> AurResponseType)
-> Ord AurResponseType
AurResponseType -> AurResponseType -> Bool
AurResponseType -> AurResponseType -> Ordering
AurResponseType -> AurResponseType -> AurResponseType
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
$ccompare :: AurResponseType -> AurResponseType -> Ordering
compare :: AurResponseType -> AurResponseType -> Ordering
$c< :: AurResponseType -> AurResponseType -> Bool
< :: AurResponseType -> AurResponseType -> Bool
$c<= :: AurResponseType -> AurResponseType -> Bool
<= :: AurResponseType -> AurResponseType -> Bool
$c> :: AurResponseType -> AurResponseType -> Bool
> :: AurResponseType -> AurResponseType -> Bool
$c>= :: AurResponseType -> AurResponseType -> Bool
>= :: AurResponseType -> AurResponseType -> Bool
$cmax :: AurResponseType -> AurResponseType -> AurResponseType
max :: AurResponseType -> AurResponseType -> AurResponseType
$cmin :: AurResponseType -> AurResponseType -> AurResponseType
min :: AurResponseType -> AurResponseType -> AurResponseType
Ord, Int -> AurResponseType
AurResponseType -> Int
AurResponseType -> [AurResponseType]
AurResponseType -> AurResponseType
AurResponseType -> AurResponseType -> [AurResponseType]
AurResponseType
-> AurResponseType -> AurResponseType -> [AurResponseType]
(AurResponseType -> AurResponseType)
-> (AurResponseType -> AurResponseType)
-> (Int -> AurResponseType)
-> (AurResponseType -> Int)
-> (AurResponseType -> [AurResponseType])
-> (AurResponseType -> AurResponseType -> [AurResponseType])
-> (AurResponseType -> AurResponseType -> [AurResponseType])
-> (AurResponseType
-> AurResponseType -> AurResponseType -> [AurResponseType])
-> Enum AurResponseType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: AurResponseType -> AurResponseType
succ :: AurResponseType -> AurResponseType
$cpred :: AurResponseType -> AurResponseType
pred :: AurResponseType -> AurResponseType
$ctoEnum :: Int -> AurResponseType
toEnum :: Int -> AurResponseType
$cfromEnum :: AurResponseType -> Int
fromEnum :: AurResponseType -> Int
$cenumFrom :: AurResponseType -> [AurResponseType]
enumFrom :: AurResponseType -> [AurResponseType]
$cenumFromThen :: AurResponseType -> AurResponseType -> [AurResponseType]
enumFromThen :: AurResponseType -> AurResponseType -> [AurResponseType]
$cenumFromTo :: AurResponseType -> AurResponseType -> [AurResponseType]
enumFromTo :: AurResponseType -> AurResponseType -> [AurResponseType]
$cenumFromThenTo :: AurResponseType
-> AurResponseType -> AurResponseType -> [AurResponseType]
enumFromThenTo :: AurResponseType
-> AurResponseType -> AurResponseType -> [AurResponseType]
Enum, (forall x. AurResponseType -> Rep AurResponseType x)
-> (forall x. Rep AurResponseType x -> AurResponseType)
-> Generic AurResponseType
forall x. Rep AurResponseType x -> AurResponseType
forall x. AurResponseType -> Rep AurResponseType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AurResponseType -> Rep AurResponseType x
from :: forall x. AurResponseType -> Rep AurResponseType x
$cto :: forall x. Rep AurResponseType x -> AurResponseType
to :: forall x. Rep AurResponseType x -> AurResponseType
Generic)
deriving (Maybe AurResponseType
Value -> Parser [AurResponseType]
Value -> Parser AurResponseType
(Value -> Parser AurResponseType)
-> (Value -> Parser [AurResponseType])
-> Maybe AurResponseType
-> FromJSON AurResponseType
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AurResponseType
parseJSON :: Value -> Parser AurResponseType
$cparseJSONList :: Value -> Parser [AurResponseType]
parseJSONList :: Value -> Parser [AurResponseType]
$comittedField :: Maybe AurResponseType
omittedField :: Maybe AurResponseType
FromJSON, [AurResponseType] -> Value
[AurResponseType] -> Encoding
AurResponseType -> Bool
AurResponseType -> Value
AurResponseType -> Encoding
(AurResponseType -> Value)
-> (AurResponseType -> Encoding)
-> ([AurResponseType] -> Value)
-> ([AurResponseType] -> Encoding)
-> (AurResponseType -> Bool)
-> ToJSON AurResponseType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AurResponseType -> Value
toJSON :: AurResponseType -> Value
$ctoEncoding :: AurResponseType -> Encoding
toEncoding :: AurResponseType -> Encoding
$ctoJSONList :: [AurResponseType] -> Value
toJSONList :: [AurResponseType] -> Value
$ctoEncodingList :: [AurResponseType] -> Encoding
toEncodingList :: [AurResponseType] -> Encoding
$comitField :: AurResponseType -> Bool
omitField :: AurResponseType -> Bool
ToJSON) via CustomJSON '[ConstructorTagModifier CamelToSnake] AurResponseType
data AurResponse a = AurResponse
{ forall a. AurResponse a -> Int
_version :: Int,
forall a. AurResponse a -> AurResponseType
_aurType :: AurResponseType,
forall a. AurResponse a -> Int
_resultCount :: Int,
forall a. AurResponse a -> a
_results :: a,
forall a. AurResponse a -> Maybe Text
_error :: Maybe Text
}
deriving stock (Int -> AurResponse a -> String -> String
[AurResponse a] -> String -> String
AurResponse a -> String
(Int -> AurResponse a -> String -> String)
-> (AurResponse a -> String)
-> ([AurResponse a] -> String -> String)
-> Show (AurResponse a)
forall a. Show a => Int -> AurResponse a -> String -> String
forall a. Show a => [AurResponse a] -> String -> String
forall a. Show a => AurResponse a -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: forall a. Show a => Int -> AurResponse a -> String -> String
showsPrec :: Int -> AurResponse a -> String -> String
$cshow :: forall a. Show a => AurResponse a -> String
show :: AurResponse a -> String
$cshowList :: forall a. Show a => [AurResponse a] -> String -> String
showList :: [AurResponse a] -> String -> String
Show, AurResponse a -> AurResponse a -> Bool
(AurResponse a -> AurResponse a -> Bool)
-> (AurResponse a -> AurResponse a -> Bool) -> Eq (AurResponse a)
forall a. Eq a => AurResponse a -> AurResponse a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => AurResponse a -> AurResponse a -> Bool
== :: AurResponse a -> AurResponse a -> Bool
$c/= :: forall a. Eq a => AurResponse a -> AurResponse a -> Bool
/= :: AurResponse a -> AurResponse a -> Bool
Eq, Eq (AurResponse a)
Eq (AurResponse a) =>
(AurResponse a -> AurResponse a -> Ordering)
-> (AurResponse a -> AurResponse a -> Bool)
-> (AurResponse a -> AurResponse a -> Bool)
-> (AurResponse a -> AurResponse a -> Bool)
-> (AurResponse a -> AurResponse a -> Bool)
-> (AurResponse a -> AurResponse a -> AurResponse a)
-> (AurResponse a -> AurResponse a -> AurResponse a)
-> Ord (AurResponse a)
AurResponse a -> AurResponse a -> Bool
AurResponse a -> AurResponse a -> Ordering
AurResponse a -> AurResponse a -> AurResponse a
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
forall a. Ord a => Eq (AurResponse a)
forall a. Ord a => AurResponse a -> AurResponse a -> Bool
forall a. Ord a => AurResponse a -> AurResponse a -> Ordering
forall a. Ord a => AurResponse a -> AurResponse a -> AurResponse a
$ccompare :: forall a. Ord a => AurResponse a -> AurResponse a -> Ordering
compare :: AurResponse a -> AurResponse a -> Ordering
$c< :: forall a. Ord a => AurResponse a -> AurResponse a -> Bool
< :: AurResponse a -> AurResponse a -> Bool
$c<= :: forall a. Ord a => AurResponse a -> AurResponse a -> Bool
<= :: AurResponse a -> AurResponse a -> Bool
$c> :: forall a. Ord a => AurResponse a -> AurResponse a -> Bool
> :: AurResponse a -> AurResponse a -> Bool
$c>= :: forall a. Ord a => AurResponse a -> AurResponse a -> Bool
>= :: AurResponse a -> AurResponse a -> Bool
$cmax :: forall a. Ord a => AurResponse a -> AurResponse a -> AurResponse a
max :: AurResponse a -> AurResponse a -> AurResponse a
$cmin :: forall a. Ord a => AurResponse a -> AurResponse a -> AurResponse a
min :: AurResponse a -> AurResponse a -> AurResponse a
Ord, (forall a b. (a -> b) -> AurResponse a -> AurResponse b)
-> (forall a b. a -> AurResponse b -> AurResponse a)
-> Functor AurResponse
forall a b. a -> AurResponse b -> AurResponse a
forall a b. (a -> b) -> AurResponse a -> AurResponse b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> AurResponse a -> AurResponse b
fmap :: forall a b. (a -> b) -> AurResponse a -> AurResponse b
$c<$ :: forall a b. a -> AurResponse b -> AurResponse a
<$ :: forall a b. a -> AurResponse b -> AurResponse a
Functor, (forall x. AurResponse a -> Rep (AurResponse a) x)
-> (forall x. Rep (AurResponse a) x -> AurResponse a)
-> Generic (AurResponse a)
forall x. Rep (AurResponse a) x -> AurResponse a
forall x. AurResponse a -> Rep (AurResponse a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (AurResponse a) x -> AurResponse a
forall a x. AurResponse a -> Rep (AurResponse a) x
$cfrom :: forall a x. AurResponse a -> Rep (AurResponse a) x
from :: forall x. AurResponse a -> Rep (AurResponse a) x
$cto :: forall a x. Rep (AurResponse a) x -> AurResponse a
to :: forall x. Rep (AurResponse a) x -> AurResponse a
Generic)
instance (FromJSON a) => FromJSON (AurResponse a) where
parseJSON :: Value -> Parser (AurResponse a)
parseJSON = String
-> (Object -> Parser (AurResponse a))
-> Value
-> Parser (AurResponse a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AurResponse" ((Object -> Parser (AurResponse a))
-> Value -> Parser (AurResponse a))
-> (Object -> Parser (AurResponse a))
-> Value
-> Parser (AurResponse a)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Int
_version <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version"
AurResponseType
_aurType <- Object
o Object -> Key -> Parser AurResponseType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Int
_resultCount <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"resultcount"
a
_results <- Object
o Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"results"
Maybe Text
_error <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"error"
AurResponse a -> Parser (AurResponse a)
forall a. a -> Parser a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure AurResponse {a
Int
Maybe Text
AurResponseType
$sel:_version:AurResponse :: Int
$sel:_aurType:AurResponse :: AurResponseType
$sel:_resultCount:AurResponse :: Int
$sel:_results:AurResponse :: a
$sel:_error:AurResponse :: Maybe Text
_version :: Int
_aurType :: AurResponseType
_resultCount :: Int
_results :: a
_error :: Maybe Text
..}
instance (ToJSON a) => ToJSON (AurResponse a) where
toJSON :: AurResponse a -> Value
toJSON AurResponse {a
Int
Maybe Text
AurResponseType
$sel:_version:AurResponse :: forall a. AurResponse a -> Int
$sel:_aurType:AurResponse :: forall a. AurResponse a -> AurResponseType
$sel:_resultCount:AurResponse :: forall a. AurResponse a -> Int
$sel:_results:AurResponse :: forall a. AurResponse a -> a
$sel:_error:AurResponse :: forall a. AurResponse a -> Maybe Text
_version :: Int
_aurType :: AurResponseType
_resultCount :: Int
_results :: a
_error :: Maybe Text
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"version" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
_version,
Key
"type" Key -> AurResponseType -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AurResponseType
_aurType,
Key
"resultcount" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
_resultCount,
Key
"results" Key -> a -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= a
_results
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> case Maybe Text
_error of
Just Text
err -> [Key
"error" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
err]
Maybe Text
_ -> []