Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
/v1/fine_tuning/jobs
Synopsis
- newtype FineTuningJobID = FineTuningJobID {}
- data CreateFineTuningJob = CreateFineTuningJob {
- model :: Model
- training_file :: FileID
- hyperparameters :: Maybe Hyperparameters
- suffix :: Maybe Text
- validation_file :: Maybe FileID
- integrations :: Maybe (Vector Integration)
- seed :: Maybe Integer
- _CreateFineTuningJob :: CreateFineTuningJob
- data JobObject = JobObject {
- id :: FineTuningJobID
- created_at :: POSIXTime
- error :: Maybe Error
- fine_tuned_model :: Maybe Model
- finished_at :: Maybe POSIXTime
- hyperparameters :: Hyperparameters
- model :: Model
- object :: Text
- organization_id :: Text
- result_files :: Vector FileID
- status :: Status
- trained_tokens :: Maybe Natural
- training_file :: FileID
- validation_file :: Maybe FileID
- integrations :: Maybe (Vector Integration)
- seed :: Integer
- estimated_finish :: Maybe POSIXTime
- data EventObject = EventObject {}
- data CheckpointObject = CheckpointObject {}
- data AutoOr a
- data Hyperparameters = Hyperparameters {}
- data WAndB = WAndB {}
- data Integration = Integration_WAndB {}
- data Status
- data Level
- data Metrics = Metrics {}
- 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))))))))
Main types
newtype FineTuningJobID Source #
Fine tuning job ID
Instances
FromJSON FineTuningJobID Source # | |
Defined in OpenAI.V1.FineTuning.Jobs parseJSON :: Value -> Parser FineTuningJobID # parseJSONList :: Value -> Parser [FineTuningJobID] # | |
ToJSON FineTuningJobID Source # | |
Defined in OpenAI.V1.FineTuning.Jobs toJSON :: FineTuningJobID -> Value # toEncoding :: FineTuningJobID -> Encoding # toJSONList :: [FineTuningJobID] -> Value # toEncodingList :: [FineTuningJobID] -> Encoding # omitField :: FineTuningJobID -> Bool # | |
IsString FineTuningJobID Source # | |
Defined in OpenAI.V1.FineTuning.Jobs fromString :: String -> FineTuningJobID # | |
Show FineTuningJobID Source # | |
Defined in OpenAI.V1.FineTuning.Jobs showsPrec :: Int -> FineTuningJobID -> ShowS # show :: FineTuningJobID -> String # showList :: [FineTuningJobID] -> ShowS # | |
ToHttpApiData FineTuningJobID Source # | |
Defined in OpenAI.V1.FineTuning.Jobs toUrlPiece :: FineTuningJobID -> Text # toEncodedUrlPiece :: FineTuningJobID -> Builder # toHeader :: FineTuningJobID -> ByteString # toQueryParam :: FineTuningJobID -> Text # |
data CreateFineTuningJob Source #
Request body for /v1/fine_tuning/jobs
CreateFineTuningJob | |
|
Instances
The fine_tuning.job object represents a fine-tuning job that has been created through the API.
JobObject | |
|
Instances
data EventObject Source #
Fine-tuning job event object
Instances
data CheckpointObject Source #
The fine_tuning.job.checkpoint
object represents a model checkpoint for
a fine-tuning job that is ready to use
CheckpointObject | |
|
Instances
Other types
A type that can also be the string "auto"
Instances
FromJSON a => FromJSON (AutoOr a) Source # | |
Defined in OpenAI.V1.AutoOr | |
ToJSON a => ToJSON (AutoOr a) Source # | |
IsString a => IsString (AutoOr a) Source # | |
Defined in OpenAI.V1.AutoOr fromString :: String -> AutoOr a # | |
Generic (AutoOr a) Source # | |
Show a => Show (AutoOr a) Source # | |
type Rep (AutoOr a) Source # | |
Defined in OpenAI.V1.AutoOr type Rep (AutoOr a) = D1 ('MetaData "AutoOr" "OpenAI.V1.AutoOr" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Auto" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Specific" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
data Hyperparameters Source #
The hyperparameters used for the fine-tuning job
Instances
The settings for your integration with Weights and
Instances
FromJSON WAndB Source # | |
Defined in OpenAI.V1.FineTuning.Jobs | |
ToJSON WAndB Source # | |
Generic WAndB Source # | |
Show WAndB Source # | |
type Rep WAndB Source # | |
Defined in OpenAI.V1.FineTuning.Jobs type Rep WAndB = D1 ('MetaData "WAndB" "OpenAI.V1.FineTuning.Jobs" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "WAndB" 'PrefixI 'True) ((S1 ('MetaSel ('Just "project") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "entity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "tags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Vector Text)))))) |
data Integration Source #
An integration to enable for your fine-tuning job
Instances
The current status of the fine-tuning job
Instances
FromJSON Status Source # | |
Defined in OpenAI.V1.FineTuning.Jobs | |
Generic Status Source # | |
Show Status Source # | |
type Rep Status Source # | |
Defined in OpenAI.V1.FineTuning.Jobs type Rep Status = D1 ('MetaData "Status" "OpenAI.V1.FineTuning.Jobs" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) ((C1 ('MetaCons "Validating_Files" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Queued" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Running" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Succeeded" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Failed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cancelled" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Log level
Instances
FromJSON Level Source # | |
Defined in OpenAI.V1.FineTuning.Jobs | |
Generic Level Source # | |
Show Level Source # | |
type Rep Level Source # | |
Defined in OpenAI.V1.FineTuning.Jobs type Rep Level = D1 ('MetaData "Level" "OpenAI.V1.FineTuning.Jobs" "openai-1.0.0-DWUl3td9tpcnv1wfBaSVp" 'False) (C1 ('MetaCons "Info" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Warn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type))) |
Metrics at the step number during the fine-tuning job.
Instances
Servant
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)))))))) Source #
Servant API