{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
module Hercules.API.Repos.Repo where
import Data.OpenApi qualified as O3
import Hercules.API.Accounts.Account (Account)
import Hercules.API.Prelude
data Repo = Repo
{ Repo -> Id Repo
id :: Id Repo,
Repo -> Id Account
ownerId :: Id Account,
Repo -> Text
siteSlug :: Text,
Repo -> Text
slug :: Text,
Repo -> Text
displayName :: Text,
Repo -> Maybe Text
imageURL :: Maybe Text,
Repo -> Bool
isPublic :: Bool,
Repo -> Maybe Text
defaultBranch :: Maybe Text,
Repo -> Text
httpURL :: Text,
Repo -> Text
sshURL :: Text,
Repo -> Bool
isInstalled :: Bool,
Repo -> Bool
isInstallable :: Bool
}
deriving ((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, Int -> Repo -> ShowS
[Repo] -> ShowS
Repo -> String
(Int -> Repo -> ShowS)
-> (Repo -> String) -> ([Repo] -> ShowS) -> Show Repo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Repo -> ShowS
showsPrec :: Int -> Repo -> ShowS
$cshow :: Repo -> String
show :: Repo -> String
$cshowList :: [Repo] -> ShowS
showList :: [Repo] -> ShowS
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)
deriving anyclass (Repo -> ()
(Repo -> ()) -> NFData Repo
forall a. (a -> ()) -> NFData a
$crnf :: Repo -> ()
rnf :: Repo -> ()
NFData, [Repo] -> Value
[Repo] -> Encoding
Repo -> Value
Repo -> Encoding
(Repo -> Value)
-> (Repo -> Encoding)
-> ([Repo] -> Value)
-> ([Repo] -> Encoding)
-> ToJSON Repo
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> 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
ToJSON, Value -> Parser [Repo]
Value -> Parser Repo
(Value -> Parser Repo) -> (Value -> Parser [Repo]) -> FromJSON Repo
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser Repo
parseJSON :: Value -> Parser Repo
$cparseJSONList :: Value -> Parser [Repo]
parseJSONList :: Value -> Parser [Repo]
FromJSON, Proxy Repo -> Declare (Definitions Schema) NamedSchema
(Proxy Repo -> Declare (Definitions Schema) NamedSchema)
-> ToSchema Repo
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy Repo -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy Repo -> Declare (Definitions Schema) NamedSchema
ToSchema, Typeable Repo
Typeable Repo =>
(Proxy Repo -> Declare (Definitions Schema) NamedSchema)
-> ToSchema Repo
Proxy Repo -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a =>
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
$cdeclareNamedSchema :: Proxy Repo -> Declare (Definitions Schema) NamedSchema
declareNamedSchema :: Proxy Repo -> Declare (Definitions Schema) NamedSchema
O3.ToSchema)