module OpenAI.V1.FineTuning.Jobs
(
FineTuningJobID(..)
, CreateFineTuningJob(..)
, _CreateFineTuningJob
, JobObject(..)
, EventObject(..)
, CheckpointObject(..)
, AutoOr(..)
, Hyperparameters(..)
, WAndB(..)
, Integration(..)
, Status(..)
, Level(..)
, Metrics(..)
, API
) where
import OpenAI.Prelude
import OpenAI.V1.AutoOr
import OpenAI.V1.Error
import OpenAI.V1.Files (FileID)
import OpenAI.V1.Models (Model)
import OpenAI.V1.ListOf
newtype FineTuningJobID = FineTuningJobID{ FineTuningJobID -> Text
text :: Text }
deriving newtype (Maybe FineTuningJobID
Value -> Parser [FineTuningJobID]
Value -> Parser FineTuningJobID
(Value -> Parser FineTuningJobID)
-> (Value -> Parser [FineTuningJobID])
-> Maybe FineTuningJobID
-> FromJSON FineTuningJobID
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FineTuningJobID
parseJSON :: Value -> Parser FineTuningJobID
$cparseJSONList :: Value -> Parser [FineTuningJobID]
parseJSONList :: Value -> Parser [FineTuningJobID]
$comittedField :: Maybe FineTuningJobID
omittedField :: Maybe FineTuningJobID
FromJSON, String -> FineTuningJobID
(String -> FineTuningJobID) -> IsString FineTuningJobID
forall a. (String -> a) -> IsString a
$cfromString :: String -> FineTuningJobID
fromString :: String -> FineTuningJobID
IsString, Int -> FineTuningJobID -> ShowS
[FineTuningJobID] -> ShowS
FineTuningJobID -> String
(Int -> FineTuningJobID -> ShowS)
-> (FineTuningJobID -> String)
-> ([FineTuningJobID] -> ShowS)
-> Show FineTuningJobID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FineTuningJobID -> ShowS
showsPrec :: Int -> FineTuningJobID -> ShowS
$cshow :: FineTuningJobID -> String
show :: FineTuningJobID -> String
$cshowList :: [FineTuningJobID] -> ShowS
showList :: [FineTuningJobID] -> ShowS
Show, FineTuningJobID -> Text
FineTuningJobID -> ByteString
FineTuningJobID -> Builder
(FineTuningJobID -> Text)
-> (FineTuningJobID -> Builder)
-> (FineTuningJobID -> ByteString)
-> (FineTuningJobID -> Text)
-> (FineTuningJobID -> Builder)
-> ToHttpApiData FineTuningJobID
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: FineTuningJobID -> Text
toUrlPiece :: FineTuningJobID -> Text
$ctoEncodedUrlPiece :: FineTuningJobID -> Builder
toEncodedUrlPiece :: FineTuningJobID -> Builder
$ctoHeader :: FineTuningJobID -> ByteString
toHeader :: FineTuningJobID -> ByteString
$ctoQueryParam :: FineTuningJobID -> Text
toQueryParam :: FineTuningJobID -> Text
$ctoEncodedQueryParam :: FineTuningJobID -> Builder
toEncodedQueryParam :: FineTuningJobID -> Builder
ToHttpApiData, [FineTuningJobID] -> Value
[FineTuningJobID] -> Encoding
FineTuningJobID -> Bool
FineTuningJobID -> Value
FineTuningJobID -> Encoding
(FineTuningJobID -> Value)
-> (FineTuningJobID -> Encoding)
-> ([FineTuningJobID] -> Value)
-> ([FineTuningJobID] -> Encoding)
-> (FineTuningJobID -> Bool)
-> ToJSON FineTuningJobID
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: FineTuningJobID -> Value
toJSON :: FineTuningJobID -> Value
$ctoEncoding :: FineTuningJobID -> Encoding
toEncoding :: FineTuningJobID -> Encoding
$ctoJSONList :: [FineTuningJobID] -> Value
toJSONList :: [FineTuningJobID] -> Value
$ctoEncodingList :: [FineTuningJobID] -> Encoding
toEncodingList :: [FineTuningJobID] -> Encoding
$comitField :: FineTuningJobID -> Bool
omitField :: FineTuningJobID -> Bool
ToJSON)
data Hyperparameters = Hyperparameters
{ Hyperparameters -> Maybe (AutoOr Natural)
batch_size :: Maybe (AutoOr Natural)
, Hyperparameters -> Maybe (AutoOr Double)
learning_rate_multiplier :: Maybe (AutoOr Double)
, Hyperparameters -> Maybe (AutoOr Natural)
n_epochs :: Maybe (AutoOr Natural)
} deriving stock ((forall x. Hyperparameters -> Rep Hyperparameters x)
-> (forall x. Rep Hyperparameters x -> Hyperparameters)
-> Generic Hyperparameters
forall x. Rep Hyperparameters x -> Hyperparameters
forall x. Hyperparameters -> Rep Hyperparameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Hyperparameters -> Rep Hyperparameters x
from :: forall x. Hyperparameters -> Rep Hyperparameters x
$cto :: forall x. Rep Hyperparameters x -> Hyperparameters
to :: forall x. Rep Hyperparameters x -> Hyperparameters
Generic, Int -> Hyperparameters -> ShowS
[Hyperparameters] -> ShowS
Hyperparameters -> String
(Int -> Hyperparameters -> ShowS)
-> (Hyperparameters -> String)
-> ([Hyperparameters] -> ShowS)
-> Show Hyperparameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hyperparameters -> ShowS
showsPrec :: Int -> Hyperparameters -> ShowS
$cshow :: Hyperparameters -> String
show :: Hyperparameters -> String
$cshowList :: [Hyperparameters] -> ShowS
showList :: [Hyperparameters] -> ShowS
Show)
deriving anyclass (Maybe Hyperparameters
Value -> Parser [Hyperparameters]
Value -> Parser Hyperparameters
(Value -> Parser Hyperparameters)
-> (Value -> Parser [Hyperparameters])
-> Maybe Hyperparameters
-> FromJSON Hyperparameters
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Hyperparameters
parseJSON :: Value -> Parser Hyperparameters
$cparseJSONList :: Value -> Parser [Hyperparameters]
parseJSONList :: Value -> Parser [Hyperparameters]
$comittedField :: Maybe Hyperparameters
omittedField :: Maybe Hyperparameters
FromJSON, [Hyperparameters] -> Value
[Hyperparameters] -> Encoding
Hyperparameters -> Bool
Hyperparameters -> Value
Hyperparameters -> Encoding
(Hyperparameters -> Value)
-> (Hyperparameters -> Encoding)
-> ([Hyperparameters] -> Value)
-> ([Hyperparameters] -> Encoding)
-> (Hyperparameters -> Bool)
-> ToJSON Hyperparameters
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Hyperparameters -> Value
toJSON :: Hyperparameters -> Value
$ctoEncoding :: Hyperparameters -> Encoding
toEncoding :: Hyperparameters -> Encoding
$ctoJSONList :: [Hyperparameters] -> Value
toJSONList :: [Hyperparameters] -> Value
$ctoEncodingList :: [Hyperparameters] -> Encoding
toEncodingList :: [Hyperparameters] -> Encoding
$comitField :: Hyperparameters -> Bool
omitField :: Hyperparameters -> Bool
ToJSON)
data WAndB = WAndB
{ WAndB -> Text
project :: Text
, WAndB -> Maybe Text
name :: Maybe Text
, WAndB -> Maybe Text
entity :: Maybe Text
, WAndB -> Maybe (Vector Text)
tags :: Maybe (Vector Text)
} deriving stock ((forall x. WAndB -> Rep WAndB x)
-> (forall x. Rep WAndB x -> WAndB) -> Generic WAndB
forall x. Rep WAndB x -> WAndB
forall x. WAndB -> Rep WAndB x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WAndB -> Rep WAndB x
from :: forall x. WAndB -> Rep WAndB x
$cto :: forall x. Rep WAndB x -> WAndB
to :: forall x. Rep WAndB x -> WAndB
Generic, Int -> WAndB -> ShowS
[WAndB] -> ShowS
WAndB -> String
(Int -> WAndB -> ShowS)
-> (WAndB -> String) -> ([WAndB] -> ShowS) -> Show WAndB
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WAndB -> ShowS
showsPrec :: Int -> WAndB -> ShowS
$cshow :: WAndB -> String
show :: WAndB -> String
$cshowList :: [WAndB] -> ShowS
showList :: [WAndB] -> ShowS
Show)
deriving anyclass (Maybe WAndB
Value -> Parser [WAndB]
Value -> Parser WAndB
(Value -> Parser WAndB)
-> (Value -> Parser [WAndB]) -> Maybe WAndB -> FromJSON WAndB
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser WAndB
parseJSON :: Value -> Parser WAndB
$cparseJSONList :: Value -> Parser [WAndB]
parseJSONList :: Value -> Parser [WAndB]
$comittedField :: Maybe WAndB
omittedField :: Maybe WAndB
FromJSON, [WAndB] -> Value
[WAndB] -> Encoding
WAndB -> Bool
WAndB -> Value
WAndB -> Encoding
(WAndB -> Value)
-> (WAndB -> Encoding)
-> ([WAndB] -> Value)
-> ([WAndB] -> Encoding)
-> (WAndB -> Bool)
-> ToJSON WAndB
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: WAndB -> Value
toJSON :: WAndB -> Value
$ctoEncoding :: WAndB -> Encoding
toEncoding :: WAndB -> Encoding
$ctoJSONList :: [WAndB] -> Value
toJSONList :: [WAndB] -> Value
$ctoEncodingList :: [WAndB] -> Encoding
toEncodingList :: [WAndB] -> Encoding
$comitField :: WAndB -> Bool
omitField :: WAndB -> Bool
ToJSON)
data Integration = Integration_WAndB{ Integration -> WAndB
wandb :: WAndB }
deriving stock ((forall x. Integration -> Rep Integration x)
-> (forall x. Rep Integration x -> Integration)
-> Generic Integration
forall x. Rep Integration x -> Integration
forall x. Integration -> Rep Integration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Integration -> Rep Integration x
from :: forall x. Integration -> Rep Integration x
$cto :: forall x. Rep Integration x -> Integration
to :: forall x. Rep Integration x -> Integration
Generic, Int -> Integration -> ShowS
[Integration] -> ShowS
Integration -> String
(Int -> Integration -> ShowS)
-> (Integration -> String)
-> ([Integration] -> ShowS)
-> Show Integration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Integration -> ShowS
showsPrec :: Int -> Integration -> ShowS
$cshow :: Integration -> String
show :: Integration -> String
$cshowList :: [Integration] -> ShowS
showList :: [Integration] -> ShowS
Show)
integrationOptions :: Options
integrationOptions :: Options
integrationOptions = Options
aesonOptions
{ sumEncoding =
TaggedObject{ tagFieldName = "type", contentsFieldName = "" }
, tagSingleConstructors = True
, constructorTagModifier = stripPrefix "Integration_"
}
instance FromJSON Integration where
parseJSON :: Value -> Parser Integration
parseJSON = Options -> Value -> Parser Integration
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
integrationOptions
instance ToJSON Integration where
toJSON :: Integration -> Value
toJSON = Options -> Integration -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
integrationOptions
data CreateFineTuningJob = CreateFineTuningJob
{ CreateFineTuningJob -> Model
model :: Model
, CreateFineTuningJob -> FileID
training_file :: FileID
, CreateFineTuningJob -> Maybe Hyperparameters
hyperparameters :: Maybe Hyperparameters
, CreateFineTuningJob -> Maybe Text
suffix :: Maybe Text
, CreateFineTuningJob -> Maybe FileID
validation_file :: Maybe FileID
, CreateFineTuningJob -> Maybe (Vector Integration)
integrations :: Maybe (Vector Integration)
, CreateFineTuningJob -> Maybe Integer
seed :: Maybe Integer
} deriving stock ((forall x. CreateFineTuningJob -> Rep CreateFineTuningJob x)
-> (forall x. Rep CreateFineTuningJob x -> CreateFineTuningJob)
-> Generic CreateFineTuningJob
forall x. Rep CreateFineTuningJob x -> CreateFineTuningJob
forall x. CreateFineTuningJob -> Rep CreateFineTuningJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CreateFineTuningJob -> Rep CreateFineTuningJob x
from :: forall x. CreateFineTuningJob -> Rep CreateFineTuningJob x
$cto :: forall x. Rep CreateFineTuningJob x -> CreateFineTuningJob
to :: forall x. Rep CreateFineTuningJob x -> CreateFineTuningJob
Generic, Int -> CreateFineTuningJob -> ShowS
[CreateFineTuningJob] -> ShowS
CreateFineTuningJob -> String
(Int -> CreateFineTuningJob -> ShowS)
-> (CreateFineTuningJob -> String)
-> ([CreateFineTuningJob] -> ShowS)
-> Show CreateFineTuningJob
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateFineTuningJob -> ShowS
showsPrec :: Int -> CreateFineTuningJob -> ShowS
$cshow :: CreateFineTuningJob -> String
show :: CreateFineTuningJob -> String
$cshowList :: [CreateFineTuningJob] -> ShowS
showList :: [CreateFineTuningJob] -> ShowS
Show)
deriving anyclass ([CreateFineTuningJob] -> Value
[CreateFineTuningJob] -> Encoding
CreateFineTuningJob -> Bool
CreateFineTuningJob -> Value
CreateFineTuningJob -> Encoding
(CreateFineTuningJob -> Value)
-> (CreateFineTuningJob -> Encoding)
-> ([CreateFineTuningJob] -> Value)
-> ([CreateFineTuningJob] -> Encoding)
-> (CreateFineTuningJob -> Bool)
-> ToJSON CreateFineTuningJob
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CreateFineTuningJob -> Value
toJSON :: CreateFineTuningJob -> Value
$ctoEncoding :: CreateFineTuningJob -> Encoding
toEncoding :: CreateFineTuningJob -> Encoding
$ctoJSONList :: [CreateFineTuningJob] -> Value
toJSONList :: [CreateFineTuningJob] -> Value
$ctoEncodingList :: [CreateFineTuningJob] -> Encoding
toEncodingList :: [CreateFineTuningJob] -> Encoding
$comitField :: CreateFineTuningJob -> Bool
omitField :: CreateFineTuningJob -> Bool
ToJSON)
_CreateFineTuningJob :: CreateFineTuningJob
_CreateFineTuningJob :: CreateFineTuningJob
_CreateFineTuningJob = CreateFineTuningJob
{ $sel:hyperparameters:CreateFineTuningJob :: Maybe Hyperparameters
hyperparameters = Maybe Hyperparameters
forall a. Maybe a
Nothing
, $sel:suffix:CreateFineTuningJob :: Maybe Text
suffix = Maybe Text
forall a. Maybe a
Nothing
, $sel:validation_file:CreateFineTuningJob :: Maybe FileID
validation_file = Maybe FileID
forall a. Maybe a
Nothing
, $sel:integrations:CreateFineTuningJob :: Maybe (Vector Integration)
integrations = Maybe (Vector Integration)
forall a. Maybe a
Nothing
, $sel:seed:CreateFineTuningJob :: Maybe Integer
seed = Maybe Integer
forall a. Maybe a
Nothing
}
data Status
= Validating_Files
| Queued
| Running
| Succeeded
| Failed
| Cancelled
deriving stock ((forall x. Status -> Rep Status x)
-> (forall x. Rep Status x -> Status) -> Generic Status
forall x. Rep Status x -> Status
forall x. Status -> Rep Status x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Status -> Rep Status x
from :: forall x. Status -> Rep Status x
$cto :: forall x. Rep Status x -> Status
to :: forall x. Rep Status x -> Status
Generic, Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
(Int -> Status -> ShowS)
-> (Status -> String) -> ([Status] -> ShowS) -> Show Status
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Status -> ShowS
showsPrec :: Int -> Status -> ShowS
$cshow :: Status -> String
show :: Status -> String
$cshowList :: [Status] -> ShowS
showList :: [Status] -> ShowS
Show)
instance FromJSON Status where
parseJSON :: Value -> Parser Status
parseJSON = Options -> Value -> Parser Status
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
data JobObject = JobObject
{ JobObject -> FineTuningJobID
id :: FineTuningJobID
, JobObject -> POSIXTime
created_at :: POSIXTime
, JobObject -> Maybe Error
error :: Maybe Error
, JobObject -> Maybe Model
fine_tuned_model :: Maybe Model
, JobObject -> Maybe POSIXTime
finished_at :: Maybe POSIXTime
, JobObject -> Hyperparameters
hyperparameters :: Hyperparameters
, JobObject -> Model
model :: Model
, JobObject -> Text
object :: Text
, JobObject -> Text
organization_id :: Text
, JobObject -> Vector FileID
result_files :: Vector FileID
, JobObject -> Status
status :: Status
, JobObject -> Maybe Natural
trained_tokens :: Maybe Natural
, JobObject -> FileID
training_file :: FileID
, JobObject -> Maybe FileID
validation_file :: Maybe FileID
, JobObject -> Maybe (Vector Integration)
integrations :: Maybe (Vector Integration)
, JobObject -> Integer
seed :: Integer
, JobObject -> Maybe POSIXTime
estimated_finish :: Maybe POSIXTime
} deriving stock ((forall x. JobObject -> Rep JobObject x)
-> (forall x. Rep JobObject x -> JobObject) -> Generic JobObject
forall x. Rep JobObject x -> JobObject
forall x. JobObject -> Rep JobObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. JobObject -> Rep JobObject x
from :: forall x. JobObject -> Rep JobObject x
$cto :: forall x. Rep JobObject x -> JobObject
to :: forall x. Rep JobObject x -> JobObject
Generic, Int -> JobObject -> ShowS
[JobObject] -> ShowS
JobObject -> String
(Int -> JobObject -> ShowS)
-> (JobObject -> String)
-> ([JobObject] -> ShowS)
-> Show JobObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> JobObject -> ShowS
showsPrec :: Int -> JobObject -> ShowS
$cshow :: JobObject -> String
show :: JobObject -> String
$cshowList :: [JobObject] -> ShowS
showList :: [JobObject] -> ShowS
Show)
deriving anyclass (Maybe JobObject
Value -> Parser [JobObject]
Value -> Parser JobObject
(Value -> Parser JobObject)
-> (Value -> Parser [JobObject])
-> Maybe JobObject
-> FromJSON JobObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser JobObject
parseJSON :: Value -> Parser JobObject
$cparseJSONList :: Value -> Parser [JobObject]
parseJSONList :: Value -> Parser [JobObject]
$comittedField :: Maybe JobObject
omittedField :: Maybe JobObject
FromJSON)
data Level = Info | Warn | Error
deriving stock ((forall x. Level -> Rep Level x)
-> (forall x. Rep Level x -> Level) -> Generic Level
forall x. Rep Level x -> Level
forall x. Level -> Rep Level x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Level -> Rep Level x
from :: forall x. Level -> Rep Level x
$cto :: forall x. Rep Level x -> Level
to :: forall x. Rep Level x -> Level
Generic, Int -> Level -> ShowS
[Level] -> ShowS
Level -> String
(Int -> Level -> ShowS)
-> (Level -> String) -> ([Level] -> ShowS) -> Show Level
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Level -> ShowS
showsPrec :: Int -> Level -> ShowS
$cshow :: Level -> String
show :: Level -> String
$cshowList :: [Level] -> ShowS
showList :: [Level] -> ShowS
Show)
instance FromJSON Level where
parseJSON :: Value -> Parser Level
parseJSON = Options -> Value -> Parser Level
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions
data EventObject = EventObject
{ EventObject -> Text
id :: Text
, EventObject -> POSIXTime
created_at :: POSIXTime
, EventObject -> Level
level :: Level
, EventObject -> Text
message :: Text
, EventObject -> Text
object :: Text
} deriving stock ((forall x. EventObject -> Rep EventObject x)
-> (forall x. Rep EventObject x -> EventObject)
-> Generic EventObject
forall x. Rep EventObject x -> EventObject
forall x. EventObject -> Rep EventObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. EventObject -> Rep EventObject x
from :: forall x. EventObject -> Rep EventObject x
$cto :: forall x. Rep EventObject x -> EventObject
to :: forall x. Rep EventObject x -> EventObject
Generic, Int -> EventObject -> ShowS
[EventObject] -> ShowS
EventObject -> String
(Int -> EventObject -> ShowS)
-> (EventObject -> String)
-> ([EventObject] -> ShowS)
-> Show EventObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EventObject -> ShowS
showsPrec :: Int -> EventObject -> ShowS
$cshow :: EventObject -> String
show :: EventObject -> String
$cshowList :: [EventObject] -> ShowS
showList :: [EventObject] -> ShowS
Show)
deriving anyclass (Maybe EventObject
Value -> Parser [EventObject]
Value -> Parser EventObject
(Value -> Parser EventObject)
-> (Value -> Parser [EventObject])
-> Maybe EventObject
-> FromJSON EventObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser EventObject
parseJSON :: Value -> Parser EventObject
$cparseJSONList :: Value -> Parser [EventObject]
parseJSONList :: Value -> Parser [EventObject]
$comittedField :: Maybe EventObject
omittedField :: Maybe EventObject
FromJSON)
data Metrics = Metrics
{ Metrics -> Double
step :: Double
, Metrics -> Double
train_loss :: Double
, Metrics -> Double
train_mean_token_accuracy :: Double
, Metrics -> Double
valid_loss :: Double
, Metrics -> Double
valid_mean_token_accuracy :: Double
, Metrics -> Double
full_valid_loss :: Double
, Metrics -> Double
full_valid_mean_token_accuracy :: Double
} deriving stock ((forall x. Metrics -> Rep Metrics x)
-> (forall x. Rep Metrics x -> Metrics) -> Generic Metrics
forall x. Rep Metrics x -> Metrics
forall x. Metrics -> Rep Metrics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Metrics -> Rep Metrics x
from :: forall x. Metrics -> Rep Metrics x
$cto :: forall x. Rep Metrics x -> Metrics
to :: forall x. Rep Metrics x -> Metrics
Generic, Int -> Metrics -> ShowS
[Metrics] -> ShowS
Metrics -> String
(Int -> Metrics -> ShowS)
-> (Metrics -> String) -> ([Metrics] -> ShowS) -> Show Metrics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Metrics -> ShowS
showsPrec :: Int -> Metrics -> ShowS
$cshow :: Metrics -> String
show :: Metrics -> String
$cshowList :: [Metrics] -> ShowS
showList :: [Metrics] -> ShowS
Show)
deriving anyclass (Maybe Metrics
Value -> Parser [Metrics]
Value -> Parser Metrics
(Value -> Parser Metrics)
-> (Value -> Parser [Metrics]) -> Maybe Metrics -> FromJSON Metrics
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Metrics
parseJSON :: Value -> Parser Metrics
$cparseJSONList :: Value -> Parser [Metrics]
parseJSONList :: Value -> Parser [Metrics]
$comittedField :: Maybe Metrics
omittedField :: Maybe Metrics
FromJSON)
data CheckpointObject = CheckpointObject
{ CheckpointObject -> Text
id :: Text
, CheckpointObject -> POSIXTime
created_at :: POSIXTime
, CheckpointObject -> Text
fine_tuned_model_checkpoint :: Text
, CheckpointObject -> Natural
step_number :: Natural
, CheckpointObject -> Metrics
metrics :: Metrics
, CheckpointObject -> FineTuningJobID
fine_tuning_job_id :: FineTuningJobID
, CheckpointObject -> Text
object :: Text
} deriving stock ((forall x. CheckpointObject -> Rep CheckpointObject x)
-> (forall x. Rep CheckpointObject x -> CheckpointObject)
-> Generic CheckpointObject
forall x. Rep CheckpointObject x -> CheckpointObject
forall x. CheckpointObject -> Rep CheckpointObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CheckpointObject -> Rep CheckpointObject x
from :: forall x. CheckpointObject -> Rep CheckpointObject x
$cto :: forall x. Rep CheckpointObject x -> CheckpointObject
to :: forall x. Rep CheckpointObject x -> CheckpointObject
Generic, Int -> CheckpointObject -> ShowS
[CheckpointObject] -> ShowS
CheckpointObject -> String
(Int -> CheckpointObject -> ShowS)
-> (CheckpointObject -> String)
-> ([CheckpointObject] -> ShowS)
-> Show CheckpointObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CheckpointObject -> ShowS
showsPrec :: Int -> CheckpointObject -> ShowS
$cshow :: CheckpointObject -> String
show :: CheckpointObject -> String
$cshowList :: [CheckpointObject] -> ShowS
showList :: [CheckpointObject] -> ShowS
Show)
deriving anyclass (Maybe CheckpointObject
Value -> Parser [CheckpointObject]
Value -> Parser CheckpointObject
(Value -> Parser CheckpointObject)
-> (Value -> Parser [CheckpointObject])
-> Maybe CheckpointObject
-> FromJSON CheckpointObject
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser CheckpointObject
parseJSON :: Value -> Parser CheckpointObject
$cparseJSONList :: Value -> Parser [CheckpointObject]
parseJSONList :: Value -> Parser [CheckpointObject]
$comittedField :: Maybe CheckpointObject
omittedField :: Maybe CheckpointObject
FromJSON)
type API =
"fine_tuning"
:> "jobs"
:> ( ReqBody '[JSON] CreateFineTuningJob
:> Post '[JSON] JobObject
:<|> QueryParam "after" Text
:> QueryParam "limit" Natural
:> Get '[JSON] (ListOf JobObject)
:<|> Capture "fine_tuning_job_id" FineTuningJobID
:> "events"
:> QueryParam "after" Text
:> QueryParam "limit" Natural
:> Get '[JSON] (ListOf EventObject)
:<|> Capture "fine_tuning_job_id" FineTuningJobID
:> "checkpoints"
:> QueryParam "after" Text
:> QueryParam "limit" Natural
:> Get '[JSON] (ListOf CheckpointObject)
:<|> Capture "fine_tuning_job_id" FineTuningJobID
:> Get '[JSON] JobObject
:<|> Capture "fine_tuning_job_id" FineTuningJobID
:> "cancel"
:> Post '[JSON] JobObject
)