{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Network.Livy.Client.Types.Statement
(
Statement (..)
, StatementId (..)
, StatementState (..)
, StatementOutput (..)
, StatementData
, stoStatus
, stoExecutionCount
, stoData
, stId
, stCode
, stState
, stOutput
) where
import Control.Lens hiding ((.=))
import Data.Aeson
import Data.Aeson.TH
import qualified Data.HashMap.Strict as Map
import Data.Text (Text)
import qualified Data.Text as T
import Data.Typeable
import Network.Livy.Client.Internal.JSON
import Network.Livy.Internal.Text
data StatementState
= StatementWaiting
| StatementRunning
| StatementAvailable
| StatementError
| StatementCancelling
| StatementCancelled
deriving (Bounded, Enum, Eq, Show, Typeable)
instance ToText StatementState where
toText = T.toLower . T.drop 9 . T.pack . show
instance ToJSON StatementState where
toJSON = String . toText
instance FromJSON StatementState where
parseJSON = withText "StatementState" $ \t ->
case lookup t toTextLookup of
Just st -> return st
Nothing -> fail . T.unpack $ "Unknown statement state: " <> t
type StatementData = Map.HashMap Text (Maybe Text)
data StatementOutput = StatementOutput
{ _stoStatus :: !(Maybe Text)
, _stoExecutionCount :: !(Maybe Integer)
, _stoData :: !(Maybe StatementData)
} deriving (Eq, Show, Typeable)
makeLenses ''StatementOutput
instance ToJSON StatementOutput where
toJSON (StatementOutput s c d) = object
[ "status" .= s
, "execution_count" .= c
, "data" .= d
]
instance FromJSON StatementOutput where
parseJSON = withObject "StatementOutput" $ \o -> StatementOutput
<$> o .:? "status"
<*> o .:? "execution_count"
<*> o .:? "data"
newtype StatementId = StatementId Int
deriving (Eq, Show, Typeable, ToText, ToJSON, FromJSON)
data Statement = Statement
{ _stId :: !StatementId
, _stCode :: !(Maybe Text)
, _stState :: !(Maybe StatementState)
, _stOutput :: !(Maybe StatementOutput)
} deriving (Eq, Show, Typeable)
makeLenses ''Statement
deriveJSON (recordPrefixOptions 3) ''Statement