Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Livy = LivyT Env (ResourceT IO)
- newtype LivyT r m a = LivyT {}
- runLivy :: HasEnv r => r -> Livy a -> IO a
- runLivyT :: HasEnv r => r -> LivyT r m a -> m a
- send :: LivyConstraint r m a => a -> m (Either LivyError (LivyResponse a))
- data Env = Env {
- _envManager :: !Manager
- _envHost :: !ByteString
- _envPort :: !Int
- class HasEnv a where
- environment :: Lens' a Env
- envManager :: Lens' a Manager
- envHost :: Lens' a ByteString
- envPort :: Lens' a Int
- newEnv :: MonadIO m => ByteString -> Int -> m Env
- class LivyRequest a where
- type family LivyResponse a :: *
- module Network.Livy.Client.Batch
- module Network.Livy.Client.Interactive
- data Batch = Batch {}
- newtype BatchId = BatchId Int
- data BatchState
- type BatchAppInfo = HashMap Text (Maybe Text)
- bId :: Lens' Batch BatchId
- bAppId :: Lens' Batch (Maybe Text)
- bAppInfo :: Lens' Batch BatchAppInfo
- bLog :: Lens' Batch [Text]
- bState :: Lens' Batch BatchState
- data Session = Session {
- _sId :: !SessionId
- _sAppId :: !(Maybe Text)
- _sOwner :: !(Maybe Text)
- _sProxyUser :: !(Maybe Text)
- _sKind :: !SessionKind
- _sLog :: ![Text]
- _sState :: !SessionState
- _sAppInfo :: !SessionAppInfo
- newtype SessionId = SessionId Int
- data SessionKind
- data SessionState
- type SessionAppInfo = HashMap Text (Maybe Text)
- sId :: Lens' Session SessionId
- sAppId :: Lens' Session (Maybe Text)
- sOwner :: Lens' Session (Maybe Text)
- sProxyUser :: Lens' Session (Maybe Text)
- sKind :: Lens' Session SessionKind
- sLog :: Lens' Session [Text]
- sState :: Lens' Session SessionState
- sAppInfo :: Lens' Session SessionAppInfo
- data Statement = Statement {
- _stId :: !StatementId
- _stCode :: !(Maybe Text)
- _stState :: !(Maybe StatementState)
- _stOutput :: !(Maybe StatementOutput)
- newtype StatementId = StatementId Int
- data StatementState
- data StatementOutput = StatementOutput {
- _stoStatus :: !(Maybe Text)
- _stoExecutionCount :: !(Maybe Integer)
- _stoData :: !(Maybe StatementData)
- type StatementData = HashMap Text (Maybe Text)
- stoStatus :: Lens' StatementOutput (Maybe Text)
- stoExecutionCount :: Lens' StatementOutput (Maybe Integer)
- stoData :: Lens' StatementOutput (Maybe StatementData)
- stId :: Lens' Statement StatementId
- stCode :: Lens' Statement (Maybe Text)
- stState :: Lens' Statement (Maybe StatementState)
- stOutput :: Lens' Statement (Maybe StatementOutput)
- data LivyError = LivyError {
- _leType :: !LivyErrorType
- _leMessage :: !ByteString
- _leResponseBody :: !(Maybe ByteString)
- _leCode :: !(Maybe LivyHTTPErrorCode)
- data LivyErrorType
- data LivyHTTPErrorCode
- data APIVersion = V050Incubating
Running Livy actions
LivyT
transformer.
Instances
Monad m => MonadReader r (LivyT r m) Source # | |
MonadTrans (LivyT r) Source # | |
Defined in Network.Livy.Monad | |
Monad m => Monad (LivyT r m) Source # | |
Functor m => Functor (LivyT r m) Source # | |
Applicative m => Applicative (LivyT r m) Source # | |
MonadIO m => MonadIO (LivyT r m) Source # | |
Defined in Network.Livy.Monad | |
MonadThrow m => MonadThrow (LivyT r m) Source # | |
Defined in Network.Livy.Monad | |
MonadCatch m => MonadCatch (LivyT r m) Source # | |
MonadResource m => MonadResource (LivyT r m) Source # | |
Defined in Network.Livy.Monad liftResourceT :: ResourceT IO a -> LivyT r m a # |
runLivyT :: HasEnv r => r -> LivyT r m a -> m a Source #
Run a LivyT action with the given environment.
send :: LivyConstraint r m a => a -> m (Either LivyError (LivyResponse a)) Source #
Send a request, returning the associated response if successful.
Environment
Environment required to make requests to Livy.
Env | |
|
newEnv :: MonadIO m => ByteString -> Int -> m Env Source #
Creates a new environment with a new Manager
with default settings.
Request/response
class LivyRequest a where Source #
Specify how a request is created.
Instances
type family LivyResponse a :: * Source #
The response type of a Livy request.
Instances
type LivyResponse RunStatementCompletion Source # | |
type LivyResponse RunStatement Source # | |
type LivyResponse KillSession Source # | |
type LivyResponse GetSessions Source # | |
type LivyResponse GetSessionStatements Source # | |
type LivyResponse GetSessionStatement Source # | |
type LivyResponse GetSessionState Source # | |
type LivyResponse GetSessionLogs Source # | |
type LivyResponse GetSession Source # | |
Defined in Network.Livy.Client.Interactive.GetSession | |
type LivyResponse CreateSession Source # | |
type LivyResponse CancelStatement Source # | |
type LivyResponse KillBatch Source # | |
Defined in Network.Livy.Client.Batch.KillBatch | |
type LivyResponse GetBatches Source # | |
Defined in Network.Livy.Client.Batch.GetBatches | |
type LivyResponse GetBatchState Source # | |
type LivyResponse GetBatchLogs Source # | |
Defined in Network.Livy.Client.Batch.GetBatchLogs | |
type LivyResponse GetBatch Source # | |
Defined in Network.Livy.Client.Batch.GetBatch | |
type LivyResponse CreateBatch Source # | |
Defined in Network.Livy.Client.Batch.CreateBatch |
Livy actions
module Network.Livy.Client.Batch
REST objects
Batch session
A batch session with Livy.
The id of this batch session.
data BatchState Source #
The present state of a batch session.
BatchNotStarted | Batch session has not been started. |
BatchStarting | Batch session is starting. |
BatchRecovering | Batch session is recovering. |
BatchIdle | Batch session is waiting for input. |
BatchRunning | Batch session is running. |
BatchBusy | Batch session is executing a statement. |
BatchShuttingDown | Batch session is shutting down. |
BatchError | Batch session errored out. |
BatchDead | Batch session has exited. |
BatchKilled | Batch session is killed. |
BatchSuccess | Batch session is successfully stopped. |
Instances
Lenses
Interactive session
An interactive session with Livy.
Session | |
|
The id of this interactive session.
data SessionKind Source #
The kind of Livy session.
SparkSession | A Scala Spark session. |
PySparkSession | A PySpark session. |
SparkRSession | A SparkR session. |
SQLSession | A Spark SQL session. |
SharedSession | A session that supports all types. |
Instances
data SessionState Source #
The present state of a session.
SessionNotStarted | Session has not been started. |
SessionStarting | Session is starting. |
SessionRecovering | Session is recovering. |
SessionIdle | Session is waiting for input. |
SessionRunning | Session is running. |
SessionBusy | Session is executing a statement. |
SessionShuttingDown | Session is shutting down. |
SessionError | Session errored out. |
SessionDead | Session has exited. |
SessionKilled | Session is killed. |
SessionSuccess | Session is successfully stopped. |
Instances
Lenses
Statements for interactive sessions
A Statement
represents the result of an execution statement.
Statement | |
|
newtype StatementId Source #
The id of this statement.
Instances
Eq StatementId Source # | |
Defined in Network.Livy.Client.Types.Statement (==) :: StatementId -> StatementId -> Bool # (/=) :: StatementId -> StatementId -> Bool # | |
Show StatementId Source # | |
Defined in Network.Livy.Client.Types.Statement showsPrec :: Int -> StatementId -> ShowS # show :: StatementId -> String # showList :: [StatementId] -> ShowS # | |
ToJSON StatementId Source # | |
Defined in Network.Livy.Client.Types.Statement toJSON :: StatementId -> Value # toEncoding :: StatementId -> Encoding # toJSONList :: [StatementId] -> Value # toEncodingList :: [StatementId] -> Encoding # | |
FromJSON StatementId Source # | |
Defined in Network.Livy.Client.Types.Statement parseJSON :: Value -> Parser StatementId # parseJSONList :: Value -> Parser [StatementId] # | |
ToText StatementId Source # | |
Defined in Network.Livy.Client.Types.Statement toText :: StatementId -> Text Source # |
data StatementState Source #
The present state of a submitted Statement
.
StatementWaiting | Statement is enqueued but execution hasn't started. |
StatementRunning | Statement is currently running. |
StatementAvailable | Statement has a response ready. |
StatementError | Statement failed. |
StatementCancelling | Statement is being cancelled. |
StatementCancelled | Statement is cancelled. |
Instances
data StatementOutput Source #
The output of a completed statement.
StatementOutput | |
|
Instances
Eq StatementOutput Source # | |
Defined in Network.Livy.Client.Types.Statement (==) :: StatementOutput -> StatementOutput -> Bool # (/=) :: StatementOutput -> StatementOutput -> Bool # | |
Show StatementOutput Source # | |
Defined in Network.Livy.Client.Types.Statement showsPrec :: Int -> StatementOutput -> ShowS # show :: StatementOutput -> String # showList :: [StatementOutput] -> ShowS # | |
ToJSON StatementOutput Source # | |
Defined in Network.Livy.Client.Types.Statement toJSON :: StatementOutput -> Value # toEncoding :: StatementOutput -> Encoding # toJSONList :: [StatementOutput] -> Value # toEncodingList :: [StatementOutput] -> Encoding # | |
FromJSON StatementOutput Source # | |
Defined in Network.Livy.Client.Types.Statement parseJSON :: Value -> Parser StatementOutput # parseJSONList :: Value -> Parser [StatementOutput] # |
Lenses
Exceptions
An error with Livy.
LivyError | |
|
Instances
Show LivyError Source # | |
Exception LivyError Source # | |
Defined in Network.Livy.Types toException :: LivyError -> SomeException # fromException :: SomeException -> Maybe LivyError # displayException :: LivyError -> String # |
data LivyErrorType Source #
Livy error types.
Instances
Show LivyErrorType Source # | |
Defined in Network.Livy.Types showsPrec :: Int -> LivyErrorType -> ShowS # show :: LivyErrorType -> String # showList :: [LivyErrorType] -> ShowS # |
data LivyHTTPErrorCode Source #
HTTP response error codes.
Instances
Show LivyHTTPErrorCode Source # | |
Defined in Network.Livy.Types showsPrec :: Int -> LivyHTTPErrorCode -> ShowS # show :: LivyHTTPErrorCode -> String # showList :: [LivyHTTPErrorCode] -> ShowS # |
Misc.
data APIVersion Source #
V050Incubating | The version of Livy for this package release. |
Instances
Show APIVersion Source # | |
Defined in Network.Livy showsPrec :: Int -> APIVersion -> ShowS # show :: APIVersion -> String # showList :: [APIVersion] -> ShowS # |