module OpenAI.V1.Models
(
Model(..)
, ModelObject(..)
, API
) where
import OpenAI.Prelude
import OpenAI.V1.DeletionStatus
import OpenAI.V1.ListOf
newtype Model = Model{ Model -> Text
text :: Text }
deriving newtype (Maybe Model
Value -> Parser [Model]
Value -> Parser Model
(Value -> Parser Model)
-> (Value -> Parser [Model]) -> Maybe Model -> FromJSON Model
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Model
parseJSON :: Value -> Parser Model
$cparseJSONList :: Value -> Parser [Model]
parseJSONList :: Value -> Parser [Model]
$comittedField :: Maybe Model
omittedField :: Maybe Model
FromJSON, String -> Model
(String -> Model) -> IsString Model
forall a. (String -> a) -> IsString a
$cfromString :: String -> Model
fromString :: String -> Model
IsString, Int -> Model -> ShowS
[Model] -> ShowS
Model -> String
(Int -> Model -> ShowS)
-> (Model -> String) -> ([Model] -> ShowS) -> Show Model
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Model -> ShowS
showsPrec :: Int -> Model -> ShowS
$cshow :: Model -> String
show :: Model -> String
$cshowList :: [Model] -> ShowS
showList :: [Model] -> ShowS
Show, Model -> Text
Model -> ByteString
Model -> Builder
(Model -> Text)
-> (Model -> Builder)
-> (Model -> ByteString)
-> (Model -> Text)
-> (Model -> Builder)
-> ToHttpApiData Model
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: Model -> Text
toUrlPiece :: Model -> Text
$ctoEncodedUrlPiece :: Model -> Builder
toEncodedUrlPiece :: Model -> Builder
$ctoHeader :: Model -> ByteString
toHeader :: Model -> ByteString
$ctoQueryParam :: Model -> Text
toQueryParam :: Model -> Text
$ctoEncodedQueryParam :: Model -> Builder
toEncodedQueryParam :: Model -> Builder
ToHttpApiData, [Model] -> Value
[Model] -> Encoding
Model -> Bool
Model -> Value
Model -> Encoding
(Model -> Value)
-> (Model -> Encoding)
-> ([Model] -> Value)
-> ([Model] -> Encoding)
-> (Model -> Bool)
-> ToJSON Model
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Model -> Value
toJSON :: Model -> Value
$ctoEncoding :: Model -> Encoding
toEncoding :: Model -> Encoding
$ctoJSONList :: [Model] -> Value
toJSONList :: [Model] -> Value
$ctoEncodingList :: [Model] -> Encoding
toEncodingList :: [Model] -> Encoding
$comitField :: Model -> Bool
omitField :: Model -> Bool
ToJSON)
data ModelObject = ModelObject
{ ModelObject -> Model
id :: Model
, ModelObject -> POSIXTime
created :: POSIXTime
, ModelObject -> Text
object :: Text
, ModelObject -> Text
owned_by :: Text
} deriving stock ((forall x. ModelObject -> Rep ModelObject x)
-> (forall x. Rep ModelObject x -> ModelObject)
-> Generic ModelObject
forall x. Rep ModelObject x -> ModelObject
forall x. ModelObject -> Rep ModelObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ModelObject -> Rep ModelObject x
from :: forall x. ModelObject -> Rep ModelObject x
$cto :: forall x. Rep ModelObject x -> ModelObject
to :: forall x. Rep ModelObject x -> ModelObject
Generic, Int -> ModelObject -> ShowS
[ModelObject] -> ShowS
ModelObject -> String
(Int -> ModelObject -> ShowS)
-> (ModelObject -> String)
-> ([ModelObject] -> ShowS)
-> Show ModelObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModelObject -> ShowS
showsPrec :: Int -> ModelObject -> ShowS
$cshow :: ModelObject -> String
show :: ModelObject -> String
$cshowList :: [ModelObject] -> ShowS
showList :: [ModelObject] -> ShowS
Show)
deriving anyclass (Maybe ModelObject
Value -> Parser [ModelObject]
Value -> Parser ModelObject
(Value -> Parser ModelObject)
-> (Value -> Parser [ModelObject])
-> Maybe ModelObject
-> FromJSON ModelObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ModelObject
parseJSON :: Value -> Parser ModelObject
$cparseJSONList :: Value -> Parser [ModelObject]
parseJSONList :: Value -> Parser [ModelObject]
$comittedField :: Maybe ModelObject
omittedField :: Maybe ModelObject
FromJSON)
type API =
"models"
:> ( Get '[JSON] (ListOf ModelObject)
:<|> Capture "model" Model
:> Get '[JSON] ModelObject
:<|> Capture "model" Model
:> Delete '[JSON] DeletionStatus
)