module OpenAI.V1.VectorStores.FileCounts
(
FileCounts(..)
) where
import OpenAI.Prelude
data FileCounts = FileCounts
{ FileCounts -> Natural
in_progress :: Natural
, FileCounts -> Natural
completed :: Natural
, FileCounts -> Natural
failed :: Natural
, FileCounts -> Natural
cancelled :: Natural
, FileCounts -> Natural
total :: Natural
} deriving stock ((forall x. FileCounts -> Rep FileCounts x)
-> (forall x. Rep FileCounts x -> FileCounts) -> Generic FileCounts
forall x. Rep FileCounts x -> FileCounts
forall x. FileCounts -> Rep FileCounts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FileCounts -> Rep FileCounts x
from :: forall x. FileCounts -> Rep FileCounts x
$cto :: forall x. Rep FileCounts x -> FileCounts
to :: forall x. Rep FileCounts x -> FileCounts
Generic, Int -> FileCounts -> ShowS
[FileCounts] -> ShowS
FileCounts -> String
(Int -> FileCounts -> ShowS)
-> (FileCounts -> String)
-> ([FileCounts] -> ShowS)
-> Show FileCounts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileCounts -> ShowS
showsPrec :: Int -> FileCounts -> ShowS
$cshow :: FileCounts -> String
show :: FileCounts -> String
$cshowList :: [FileCounts] -> ShowS
showList :: [FileCounts] -> ShowS
Show)
deriving anyclass (Maybe FileCounts
Value -> Parser [FileCounts]
Value -> Parser FileCounts
(Value -> Parser FileCounts)
-> (Value -> Parser [FileCounts])
-> Maybe FileCounts
-> FromJSON FileCounts
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FileCounts
parseJSON :: Value -> Parser FileCounts
$cparseJSONList :: Value -> Parser [FileCounts]
parseJSONList :: Value -> Parser [FileCounts]
$comittedField :: Maybe FileCounts
omittedField :: Maybe FileCounts
FromJSON)