module MSAzureAPI.MachineLearning.Jobs (
  createJob
  , listJobs
  , JobBaseResource(..)
  , JobBase(..)
  , Status(..)
  , SystemData(..)
                                       ) where

import Control.Applicative (Alternative(..))
import Control.Monad.IO.Class (MonadIO(..))
import Data.Foldable (asum)
import Data.Functor (void)
-- import Data.Maybe (listToMaybe)
import GHC.Generics (Generic(..))

-- aeson
import qualified Data.Aeson as A (ToJSON(..), genericToEncoding, FromJSON(..), genericParseJSON, defaultOptions, Options(..), withObject, withText, (.:), (.:?), object, (.=), Key, Value, camelTo2)
-- bytestring
import qualified Data.ByteString as BS (ByteString)
import qualified Data.ByteString.Char8 as BS8 (pack, unpack)
import qualified Data.ByteString.Lazy as LBS (ByteString)
-- hoauth2
-- import Network.OAuth.OAuth2 (OAuth2Token(..))
import Network.OAuth.OAuth2.Internal (AccessToken(..))
-- req
import Network.HTTP.Req (Req, Url, Option, Scheme(..), header, (=:))
-- text
import Data.Text (Text, pack, unpack)
import qualified Data.Text.Lazy as TL (Text, pack, unpack, toStrict)
-- time
import Data.Time (UTCTime, getCurrentTime)
-- import Data.Time.Format (FormatTime, formatTime, defaultTimeLocale)
-- import Data.Time.LocalTime (getZonedTime)
-- -- xeno
-- import qualified Xeno.DOM.Robust as X (Node, Content(..), name, contents, children)
-- -- xmlbf-xeno
-- import qualified Xmlbf.Xeno as XB (fromRawXml)
-- xmlbf
-- import qualified Xmlbf as XB (Parser, runParser, pElement, pText)

import qualified MSAzureAPI.Internal.Common as MSA (APIPlane(..), Collection, (==:), put, get, getBs, post, getLbs, aesonOptions)

-- | List jobs
--
-- @ GET https:\/\/management.azure.com\/subscriptions\/{subscriptionId}\/resourceGroups\/{resourceGroupName}\/providers\/Microsoft.MachineLearningServices\/workspaces\/{workspaceName}\/jobs?api-version=2023-04-01&$skip={$skip}&jobType={jobType}&tag={tag}&listViewType={listViewType}@
listJobs ::
  Text -- ^ subscription id
  -> Text -- ^ res group id
  -> Text -- ^ ML workspace id
  -> AccessToken -> Req (MSA.Collection JobBaseResource)
listJobs :: Text
-> Text -> Text -> AccessToken -> Req (Collection JobBaseResource)
listJobs Text
sid Text
rgid Text
wsid = forall b.
FromJSON b =>
APIPlane -> [Text] -> Option 'Https -> AccessToken -> Req b
MSA.get APIPlane
MSA.APManagement [
    Text
"subscriptions", Text
sid,
    Text
"resourceGroups", Text
rgid,
    Text
"providers", Text
"Microsoft.MachineLearningServices",
    Text
"workspaces", Text
wsid,
    Text
"jobs"
    ] (Text
"api-version" Text -> Text -> Option 'Https
MSA.==: Text
"2023-04-01")


-- | Create a job
--
-- docs: <https://learn.microsoft.com/en-us/rest/api/azureml/2023-04-01/jobs/create-or-update?tabs=HTTP>
--
-- @PUT https:\/\/management.azure.com\/subscriptions\/{subscriptionId}\/resourceGroups\/{resourceGroupName}\/providers\/Microsoft.MachineLearningServices\/workspaces\/{workspaceName}\/jobs\/{id}?api-version=2023-04-01@
createJob ::
  Text -- ^ subscription id
  -> Text -- ^ res group id
  -> Text -- ^ ML workspace id
  -> Text -- ^ job id
  -> JobBase
  -> AccessToken -> Req JobBaseResource
createJob :: Text
-> Text
-> Text
-> Text
-> JobBase
-> AccessToken
-> Req JobBaseResource
createJob Text
sid Text
rgid Text
wsid Text
jid =
  forall b a.
(FromJSON b, ToJSON a) =>
APIPlane -> [Text] -> Option 'Https -> a -> AccessToken -> Req b
MSA.put APIPlane
MSA.APManagement [
  Text
"subscriptions", Text
sid,
    Text
"resourceGroups", Text
rgid,
    Text
"providers", Text
"Microsoft.MachineLearningServices",
    Text
"workspaces", Text
wsid,
    Text
"jobs", Text
jid] (Text
"api-version" Text -> Text -> Option 'Https
MSA.==: Text
"2023-04-01")

-- | https://learn.microsoft.com/en-us/rest/api/azureml/2023-04-01/jobs/create-or-update?tabs=HTTP#jobbaseresource
data JobBaseResource = JobBaseResource {
  JobBaseResource -> Text
jbrId :: Text
  , JobBaseResource -> Text
jbrName :: Text
  , JobBaseResource -> SystemData
jbrSystemData :: SystemData
  , JobBaseResource -> JobBase
jbrProperties :: JobBase
                                       } deriving (JobBaseResource -> JobBaseResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobBaseResource -> JobBaseResource -> Bool
$c/= :: JobBaseResource -> JobBaseResource -> Bool
== :: JobBaseResource -> JobBaseResource -> Bool
$c== :: JobBaseResource -> JobBaseResource -> Bool
Eq, Int -> JobBaseResource -> ShowS
[JobBaseResource] -> ShowS
JobBaseResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobBaseResource] -> ShowS
$cshowList :: [JobBaseResource] -> ShowS
show :: JobBaseResource -> String
$cshow :: JobBaseResource -> String
showsPrec :: Int -> JobBaseResource -> ShowS
$cshowsPrec :: Int -> JobBaseResource -> ShowS
Show, forall x. Rep JobBaseResource x -> JobBaseResource
forall x. JobBaseResource -> Rep JobBaseResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobBaseResource x -> JobBaseResource
$cfrom :: forall x. JobBaseResource -> Rep JobBaseResource x
Generic)
instance A.FromJSON JobBaseResource where
  parseJSON :: Value -> Parser JobBaseResource
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (String -> Options
MSA.aesonOptions String
"jbr")

data SystemData = SystemData {
  SystemData -> UTCTime
sdCreatedAt :: UTCTime
  , SystemData -> Text
sdCreatedBy :: Text
  , SystemData -> UTCTime
srLastModifiedAt :: UTCTime
  , SystemData -> Text
srLastModifiedBy :: Text
                             } deriving (SystemData -> SystemData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SystemData -> SystemData -> Bool
$c/= :: SystemData -> SystemData -> Bool
== :: SystemData -> SystemData -> Bool
$c== :: SystemData -> SystemData -> Bool
Eq, Int -> SystemData -> ShowS
[SystemData] -> ShowS
SystemData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SystemData] -> ShowS
$cshowList :: [SystemData] -> ShowS
show :: SystemData -> String
$cshow :: SystemData -> String
showsPrec :: Int -> SystemData -> ShowS
$cshowsPrec :: Int -> SystemData -> ShowS
Show, forall x. Rep SystemData x -> SystemData
forall x. SystemData -> Rep SystemData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SystemData x -> SystemData
$cfrom :: forall x. SystemData -> Rep SystemData x
Generic)
instance A.FromJSON SystemData where
  parseJSON :: Value -> Parser SystemData
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (String -> Options
MSA.aesonOptions String
"sd")

-- | JobBase
--
-- https://learn.microsoft.com/en-us/rest/api/azureml/2023-04-01/jobs/create-or-update?tabs=HTTP
-- data JobBase = JBAutoMLJob {
--   jbStatus :: Status
--   , jbComponentId :: Text
--   , jb
--                            } -- ^ https://learn.microsoft.com/en-us/rest/api/azureml/2023-04-01/jobs/list?tabs=HTTP#automljob
--              | JBCommandJob {
--   jbStatus :: Status
--                            }
--              | JBPipelineJob {
--   jbStatus :: Status
--                            }
--              | JBSweepJob {
--   jbStatus :: Status
--                            }
data JobBase = JobBase {
    JobBase -> Status
jbStatus :: Status
  , JobBase -> Text
jbComponentId :: Text
  , JobBase -> Text
jbComputeId :: Text
  , JobBase -> Text
jbDescription :: Text
  , JobBase -> Text
jbDisplayName :: Text
  -- , jbInputs :: A.Value -- AutoMLJob doesn't have inputs
  , JobBase -> Value
jbOutputs :: A.Value
  , JobBase -> Value
jbProperties :: A.Value
                       }
             deriving (JobBase -> JobBase -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobBase -> JobBase -> Bool
$c/= :: JobBase -> JobBase -> Bool
== :: JobBase -> JobBase -> Bool
$c== :: JobBase -> JobBase -> Bool
Eq, Int -> JobBase -> ShowS
[JobBase] -> ShowS
JobBase -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobBase] -> ShowS
$cshowList :: [JobBase] -> ShowS
show :: JobBase -> String
$cshow :: JobBase -> String
showsPrec :: Int -> JobBase -> ShowS
$cshowsPrec :: Int -> JobBase -> ShowS
Show, forall x. Rep JobBase x -> JobBase
forall x. JobBase -> Rep JobBase x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobBase x -> JobBase
$cfrom :: forall x. JobBase -> Rep JobBase x
Generic)
instance A.FromJSON JobBase where
  parseJSON :: Value -> Parser JobBase
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (String -> Options
MSA.aesonOptions String
"jb")
instance A.ToJSON JobBase where
  toEncoding :: JobBase -> Encoding
toEncoding = forall a.
(Generic a, GToJSON' Encoding Zero (Rep a)) =>
Options -> a -> Encoding
A.genericToEncoding (String -> Options
MSA.aesonOptions String
"jb")

data Status = CancelRequested
            | Canceled
            | Completed
            | Failed
            | Finalizing
            | NotResponding
            | NotStarted
            | Paused
            | Preparing
            | Provisioning
            | Queued
            | Running
            | Starting
            | Unknown
            deriving (Status -> Status -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: Status -> Status -> Bool
Eq, Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status] -> ShowS
$cshowList :: [Status] -> ShowS
show :: Status -> String
$cshow :: Status -> String
showsPrec :: Int -> Status -> ShowS
$cshowsPrec :: Int -> Status -> ShowS
Show, 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
$cto :: forall x. Rep Status x -> Status
$cfrom :: forall x. Status -> Rep Status x
Generic)
instance A.FromJSON Status
instance A.ToJSON Status