{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DerivingStrategies #-} module Hercules.API.Repos.SimpleRepo where import Data.OpenApi qualified as O3 import Hercules.API.Accounts.SimpleAccount (SimpleAccount) import Hercules.API.Prelude import Hercules.API.Repos.Repo (Repo) data SimpleRepo = SimpleRepo { SimpleRepo -> Id Repo id :: Id Repo, SimpleRepo -> Name Repo name :: Name Repo, SimpleRepo -> SimpleAccount owner :: SimpleAccount, SimpleRepo -> Text displayName :: Text, SimpleRepo -> Maybe Text imageURL :: Maybe Text, SimpleRepo -> Bool isPublic :: Bool } deriving ((forall x. SimpleRepo -> Rep SimpleRepo x) -> (forall x. Rep SimpleRepo x -> SimpleRepo) -> Generic SimpleRepo forall x. Rep SimpleRepo x -> SimpleRepo forall x. SimpleRepo -> Rep SimpleRepo x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. SimpleRepo -> Rep SimpleRepo x from :: forall x. SimpleRepo -> Rep SimpleRepo x $cto :: forall x. Rep SimpleRepo x -> SimpleRepo to :: forall x. Rep SimpleRepo x -> SimpleRepo Generic, Int -> SimpleRepo -> ShowS [SimpleRepo] -> ShowS SimpleRepo -> String (Int -> SimpleRepo -> ShowS) -> (SimpleRepo -> String) -> ([SimpleRepo] -> ShowS) -> Show SimpleRepo forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> SimpleRepo -> ShowS showsPrec :: Int -> SimpleRepo -> ShowS $cshow :: SimpleRepo -> String show :: SimpleRepo -> String $cshowList :: [SimpleRepo] -> ShowS showList :: [SimpleRepo] -> ShowS Show, SimpleRepo -> SimpleRepo -> Bool (SimpleRepo -> SimpleRepo -> Bool) -> (SimpleRepo -> SimpleRepo -> Bool) -> Eq SimpleRepo forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: SimpleRepo -> SimpleRepo -> Bool == :: SimpleRepo -> SimpleRepo -> Bool $c/= :: SimpleRepo -> SimpleRepo -> Bool /= :: SimpleRepo -> SimpleRepo -> Bool Eq) deriving anyclass (SimpleRepo -> () (SimpleRepo -> ()) -> NFData SimpleRepo forall a. (a -> ()) -> NFData a $crnf :: SimpleRepo -> () rnf :: SimpleRepo -> () NFData, [SimpleRepo] -> Value [SimpleRepo] -> Encoding SimpleRepo -> Value SimpleRepo -> Encoding (SimpleRepo -> Value) -> (SimpleRepo -> Encoding) -> ([SimpleRepo] -> Value) -> ([SimpleRepo] -> Encoding) -> ToJSON SimpleRepo forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a $ctoJSON :: SimpleRepo -> Value toJSON :: SimpleRepo -> Value $ctoEncoding :: SimpleRepo -> Encoding toEncoding :: SimpleRepo -> Encoding $ctoJSONList :: [SimpleRepo] -> Value toJSONList :: [SimpleRepo] -> Value $ctoEncodingList :: [SimpleRepo] -> Encoding toEncodingList :: [SimpleRepo] -> Encoding ToJSON, Value -> Parser [SimpleRepo] Value -> Parser SimpleRepo (Value -> Parser SimpleRepo) -> (Value -> Parser [SimpleRepo]) -> FromJSON SimpleRepo forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a $cparseJSON :: Value -> Parser SimpleRepo parseJSON :: Value -> Parser SimpleRepo $cparseJSONList :: Value -> Parser [SimpleRepo] parseJSONList :: Value -> Parser [SimpleRepo] FromJSON, Proxy SimpleRepo -> Declare (Definitions Schema) NamedSchema (Proxy SimpleRepo -> Declare (Definitions Schema) NamedSchema) -> ToSchema SimpleRepo forall a. (Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a $cdeclareNamedSchema :: Proxy SimpleRepo -> Declare (Definitions Schema) NamedSchema declareNamedSchema :: Proxy SimpleRepo -> Declare (Definitions Schema) NamedSchema ToSchema, Typeable SimpleRepo Typeable SimpleRepo => (Proxy SimpleRepo -> Declare (Definitions Schema) NamedSchema) -> ToSchema SimpleRepo Proxy SimpleRepo -> Declare (Definitions Schema) NamedSchema forall a. Typeable a => (Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a $cdeclareNamedSchema :: Proxy SimpleRepo -> Declare (Definitions Schema) NamedSchema declareNamedSchema :: Proxy SimpleRepo -> Declare (Definitions Schema) NamedSchema O3.ToSchema)