hlivy-1.0.1: Client library for the Apache Livy REST API

Copyright(C) 2019 Earnest Research
LicenseMIT
MaintainerDaniel Donohue <ddonohue@earnestresearch.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Network.Livy

Contents

Description

hlivy is a Haskell library that provides bindings to the Apache Livy REST API, which enables one to easily launch Spark applications -- either in an interactive or batch fashion -- via HTTP requests to the Livy server running on the master node of a Spark cluster.

Usage:

In general, to use this library, one creates a request by using a default constructor and modifying it, as needed, with the provided request lenses. Wrapping this request with send creates a Livy action that can be ran with runLivy.

For example, to run a Spark application whose main class is com.company.my_app and to request 4 cores per executor from the cluster:

import Network.Livy
import Control.Lens ((?~), (&))

main :: IO (Either LivyError CreateBatchResponse)
main = do
  env <- newEnv "localhost" 8998
  let req = createBatch "/user/hadoop/my-app.jar"
          & cbClassName ?~ "com.company.my_app"
          & cbExecutorCores ?~ 4
  runLivy env $ send req

For more example usage, see the examples.

Synopsis

Running Livy actions

type Livy = LivyT Env (ResourceT IO) Source #

A specialization of LivyT.

newtype LivyT r m a Source #

LivyT transformer.

Constructors

LivyT 

Fields

Instances
Monad m => MonadReader r (LivyT r m) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

ask :: LivyT r m r #

local :: (r -> r) -> LivyT r m a -> LivyT r m a #

reader :: (r -> a) -> LivyT r m a #

MonadTrans (LivyT r) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

lift :: Monad m => m a -> LivyT r m a #

Monad m => Monad (LivyT r m) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

(>>=) :: LivyT r m a -> (a -> LivyT r m b) -> LivyT r m b #

(>>) :: LivyT r m a -> LivyT r m b -> LivyT r m b #

return :: a -> LivyT r m a #

fail :: String -> LivyT r m a #

Functor m => Functor (LivyT r m) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

fmap :: (a -> b) -> LivyT r m a -> LivyT r m b #

(<$) :: a -> LivyT r m b -> LivyT r m a #

Applicative m => Applicative (LivyT r m) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

pure :: a -> LivyT r m a #

(<*>) :: LivyT r m (a -> b) -> LivyT r m a -> LivyT r m b #

liftA2 :: (a -> b -> c) -> LivyT r m a -> LivyT r m b -> LivyT r m c #

(*>) :: LivyT r m a -> LivyT r m b -> LivyT r m b #

(<*) :: LivyT r m a -> LivyT r m b -> LivyT r m a #

MonadIO m => MonadIO (LivyT r m) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

liftIO :: IO a -> LivyT r m a #

MonadThrow m => MonadThrow (LivyT r m) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

throwM :: Exception e => e -> LivyT r m a #

MonadCatch m => MonadCatch (LivyT r m) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

catch :: Exception e => LivyT r m a -> (e -> LivyT r m a) -> LivyT r m a #

MonadResource m => MonadResource (LivyT r m) Source # 
Instance details

Defined in Network.Livy.Monad

Methods

liftResourceT :: ResourceT IO a -> LivyT r m a #

runLivy :: HasEnv r => r -> Livy a -> IO a Source #

Run the Livy monad.

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

data Env Source #

Environment required to make requests to Livy.

Constructors

Env 

Fields

class HasEnv a where Source #

Minimal complete definition

environment

Methods

environment :: Lens' a Env Source #

envManager :: Lens' a Manager Source #

Manager used to create and manage HTTP connections.

envHost :: Lens' a ByteString Source #

The host name.

envPort :: Lens' a Int Source #

The port number.

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.

Methods

request :: a -> Request Source #

Instances
LivyRequest RunStatementCompletion Source # 
Instance details

Defined in Network.Livy.Client.Interactive.RunStatementCompletion

LivyRequest RunStatement Source # 
Instance details

Defined in Network.Livy.Client.Interactive.RunStatement

LivyRequest KillSession Source # 
Instance details

Defined in Network.Livy.Client.Interactive.KillSession

LivyRequest GetSessions Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessions

LivyRequest GetSessionStatements Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessionStatements

LivyRequest GetSessionStatement Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessionStatement

LivyRequest GetSessionState Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessionState

LivyRequest GetSessionLogs Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessionLogs

LivyRequest GetSession Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSession

LivyRequest CreateSession Source # 
Instance details

Defined in Network.Livy.Client.Interactive.CreateSession

LivyRequest CancelStatement Source # 
Instance details

Defined in Network.Livy.Client.Interactive.CancelStatement

LivyRequest KillBatch Source # 
Instance details

Defined in Network.Livy.Client.Batch.KillBatch

LivyRequest GetBatches Source # 
Instance details

Defined in Network.Livy.Client.Batch.GetBatches

LivyRequest GetBatchState Source # 
Instance details

Defined in Network.Livy.Client.Batch.GetBatchState

LivyRequest GetBatchLogs Source # 
Instance details

Defined in Network.Livy.Client.Batch.GetBatchLogs

LivyRequest GetBatch Source # 
Instance details

Defined in Network.Livy.Client.Batch.GetBatch

LivyRequest CreateBatch Source # 
Instance details

Defined in Network.Livy.Client.Batch.CreateBatch

type family LivyResponse a :: * Source #

The response type of a Livy request.

Instances
type LivyResponse RunStatementCompletion Source # 
Instance details

Defined in Network.Livy.Client.Interactive.RunStatementCompletion

type LivyResponse RunStatement Source # 
Instance details

Defined in Network.Livy.Client.Interactive.RunStatement

type LivyResponse KillSession Source # 
Instance details

Defined in Network.Livy.Client.Interactive.KillSession

type LivyResponse GetSessions Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessions

type LivyResponse GetSessionStatements Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessionStatements

type LivyResponse GetSessionStatement Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessionStatement

type LivyResponse GetSessionState Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessionState

type LivyResponse GetSessionLogs Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSessionLogs

type LivyResponse GetSession Source # 
Instance details

Defined in Network.Livy.Client.Interactive.GetSession

type LivyResponse CreateSession Source # 
Instance details

Defined in Network.Livy.Client.Interactive.CreateSession

type LivyResponse CancelStatement Source # 
Instance details

Defined in Network.Livy.Client.Interactive.CancelStatement

type LivyResponse KillBatch Source # 
Instance details

Defined in Network.Livy.Client.Batch.KillBatch

type LivyResponse GetBatches Source # 
Instance details

Defined in Network.Livy.Client.Batch.GetBatches

type LivyResponse GetBatchState Source # 
Instance details

Defined in Network.Livy.Client.Batch.GetBatchState

type LivyResponse GetBatchLogs Source # 
Instance details

Defined in Network.Livy.Client.Batch.GetBatchLogs

type LivyResponse GetBatch Source # 
Instance details

Defined in Network.Livy.Client.Batch.GetBatch

type LivyResponse CreateBatch Source # 
Instance details

Defined in Network.Livy.Client.Batch.CreateBatch

Livy actions

REST objects

Batch session

data Batch Source #

A batch session with Livy.

Constructors

Batch 

Fields

Instances
Eq Batch Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

Methods

(==) :: Batch -> Batch -> Bool #

(/=) :: Batch -> Batch -> Bool #

Show Batch Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

Methods

showsPrec :: Int -> Batch -> ShowS #

show :: Batch -> String #

showList :: [Batch] -> ShowS #

ToJSON Batch Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

FromJSON Batch Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

newtype BatchId Source #

The id of this batch session.

Constructors

BatchId Int 

data BatchState Source #

The present state of a batch session.

Constructors

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
Bounded BatchState Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

Enum BatchState Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

Eq BatchState Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

Show BatchState Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

ToJSON BatchState Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

FromJSON BatchState Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

ToText BatchState Source # 
Instance details

Defined in Network.Livy.Client.Types.Batch

type BatchAppInfo = HashMap Text (Maybe Text) Source #

Detailed application information.

Lenses

Interactive session

data Session Source #

An interactive session with Livy.

Constructors

Session 

Fields

data SessionKind Source #

The kind of Livy session.

Constructors

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
Bounded SessionKind Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

Enum SessionKind Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

Eq SessionKind Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

Show SessionKind Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

ToJSON SessionKind Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

FromJSON SessionKind Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

ToText SessionKind Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

data SessionState Source #

The present state of a session.

Constructors

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
Bounded SessionState Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

Enum SessionState Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

Eq SessionState Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

Show SessionState Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

ToJSON SessionState Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

FromJSON SessionState Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

ToText SessionState Source # 
Instance details

Defined in Network.Livy.Client.Types.Session

type SessionAppInfo = HashMap Text (Maybe Text) Source #

Detailed application information.

Lenses

Statements for interactive sessions

data Statement Source #

A Statement represents the result of an execution statement.

Constructors

Statement 

Fields

data StatementState Source #

The present state of a submitted Statement.

Constructors

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
Bounded StatementState Source # 
Instance details

Defined in Network.Livy.Client.Types.Statement

Enum StatementState Source # 
Instance details

Defined in Network.Livy.Client.Types.Statement

Eq StatementState Source # 
Instance details

Defined in Network.Livy.Client.Types.Statement

Show StatementState Source # 
Instance details

Defined in Network.Livy.Client.Types.Statement

ToJSON StatementState Source # 
Instance details

Defined in Network.Livy.Client.Types.Statement

FromJSON StatementState Source # 
Instance details

Defined in Network.Livy.Client.Types.Statement

ToText StatementState Source # 
Instance details

Defined in Network.Livy.Client.Types.Statement

type StatementData = HashMap Text (Maybe Text) Source #

Statement output.

Lenses

Exceptions

Misc.

data APIVersion Source #

Constructors

V050Incubating

The version of Livy for this package release.

Instances
Show APIVersion Source # 
Instance details

Defined in Network.Livy