| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.Flink.Stateful
Description
Primary module containing everything needed to create stateful functions with Flink.
All stateful functions should have a single record type that represents the entire internal state
of the function. Stateful functions API provides many "slots" to store state, but for the purposes of this library
that is hardcoded to the single key flink_state which you can see in the example module.yaml.
The Serde typeclass abstracts serialization away from the library so that users can decide how
state should be serialized. Aeson is very convenient so I use it in the example, but protobuf or any other
binary format is also acceptable. Flink essentially stores function state as an opaque ByteString regardless.
When running your program don't forget to pass +RTS -N to your binary to run on all cores.
Synopsis
- class MonadIO m => StatefulFunc s m | m -> s where
- insideCtx :: (s -> a) -> m a
- getCtx :: m s
- setCtx :: s -> m ()
- modifyCtx :: (s -> s) -> m ()
- sendMsg :: Message a => (Text, Text, Text) -> a -> m ()
- sendMsgDelay :: Message a => (Text, Text, Text) -> Int -> a -> m ()
- sendEgressMsg :: Message a => (Text, Text) -> a -> m ()
- sendByteMsg :: Serde a => (Text, Text, Text) -> a -> m ()
- sendByteMsgDelay :: Serde a => (Text, Text, Text) -> Int -> a -> m ()
- flinkWrapper :: Serde s => (Any -> Function s ()) -> ByteString -> Env -> ToFunction'InvocationBatchRequest -> IO (Either FlinkError (FunctionState ByteString))
- createApp :: FunctionTable -> Application
- flinkServer :: FunctionTable -> Server FlinkApi
- flinkApi :: Proxy FlinkApi
- class Serde a where
- deserializeBytes :: ByteString -> Either String a
- serializeBytes :: a -> ByteString
- type FunctionTable = Map (Text, Text) (ByteString, ByteString -> Env -> ToFunction'InvocationBatchRequest -> IO (Either FlinkError (FunctionState ByteString)))
- newtype JsonSerde a = JsonSerde {
- getJson :: a
- newtype ProtoSerde a = ProtoSerde {
- getMessage :: a
- jsonState :: Json s => (a -> Function s ()) -> a -> Function (JsonSerde s) ()
- protoState :: Message s => (a -> Function s ()) -> a -> Function (ProtoSerde s) ()
- serdeInput :: (Serde s, Serde a, StatefulFunc s m, MonadError FlinkError m, MonadReader Env m) => (a -> m b) -> Any -> m b
- protoInput :: (Serde s, Message a, StatefulFunc s m, MonadError FlinkError m, MonadReader Env m) => (a -> m b) -> Any -> m b
- jsonInput :: (Serde s, Json a, StatefulFunc s m, MonadError FlinkError m, MonadReader Env m) => (a -> m b) -> Any -> m b
Documentation
class MonadIO m => StatefulFunc s m | m -> s where Source #
Used to represent all Flink stateful function capabilities.
Contexts are received from Flink and deserializeBytesd into s
all modifications to state are shipped back to Flink at the end of the
batch to be persisted.
Message passing is also queued up and passed back at the end of the current batch.
Minimal complete definition
setInitialCtx, insideCtx, getCtx, setCtx, modifyCtx, sendMsg, sendMsgDelay, sendEgressMsg, sendByteMsg, sendByteMsgDelay
Methods
insideCtx :: (s -> a) -> m a Source #
modifyCtx :: (s -> s) -> m () Source #
Arguments
| :: Message a | |
| => (Text, Text, Text) | Function address (namespace, type, id) |
| -> a | protobuf message to send |
| -> m () |
Arguments
| :: Message a | |
| => (Text, Text, Text) | Function address (namespace, type, id) |
| -> Int | delay before message send |
| -> a | protobuf message to send |
| -> m () |
Arguments
| :: Message a | |
| => (Text, Text) | egress address (namespace, type) |
| -> a | protobuf message to send (should be a Kafka or Kinesis protobuf record) |
| -> m () |
Instances
| StatefulFunc s (Function s) Source # | |
Defined in Network.Flink.Internal.Stateful Methods setInitialCtx :: s -> Function s () insideCtx :: (s -> a) -> Function s a Source # getCtx :: Function s s Source # setCtx :: s -> Function s () Source # modifyCtx :: (s -> s) -> Function s () Source # sendMsg :: Message a => (Text, Text, Text) -> a -> Function s () Source # sendMsgDelay :: Message a => (Text, Text, Text) -> Int -> a -> Function s () Source # sendEgressMsg :: Message a => (Text, Text) -> a -> Function s () Source # sendByteMsg :: Serde a => (Text, Text, Text) -> a -> Function s () Source # sendByteMsgDelay :: Serde a => (Text, Text, Text) -> Int -> a -> Function s () Source # | |
flinkWrapper :: Serde s => (Any -> Function s ()) -> ByteString -> Env -> ToFunction'InvocationBatchRequest -> IO (Either FlinkError (FunctionState ByteString)) Source #
Takes a function taking an arbitrary state type and converts it to take ByteStrings.
This allows each function in the FunctionTable to take its own individual type of state and just expose
a function accepting ByteString to the library code.
createApp :: FunctionTable -> Application Source #
Takes function table and creates a wai Application to serve flink requests
flinkServer :: FunctionTable -> Server FlinkApi Source #
Takes function table and creates a servant Server to serve flink requests
Methods
deserializeBytes :: ByteString -> Either String a Source #
decodes types from strict ByteStrings
serializeBytes :: a -> ByteString Source #
encodes types to strict ByteStrings
Instances
| Serde () Source # | |
Defined in Network.Flink.Internal.Stateful Methods deserializeBytes :: ByteString -> Either String () Source # serializeBytes :: () -> ByteString Source # | |
| Serde ByteString Source # | |
Defined in Network.Flink.Internal.Stateful Methods deserializeBytes :: ByteString -> Either String ByteString Source # | |
| Serde ByteString Source # | |
Defined in Network.Flink.Internal.Stateful Methods deserializeBytes :: ByteString0 -> Either String ByteString Source # | |
| Json a => Serde (JsonSerde a) Source # | |
Defined in Network.Flink.Internal.Stateful Methods deserializeBytes :: ByteString -> Either String (JsonSerde a) Source # serializeBytes :: JsonSerde a -> ByteString Source # | |
| Message a => Serde (ProtoSerde a) Source # | |
Defined in Network.Flink.Internal.Stateful Methods deserializeBytes :: ByteString -> Either String (ProtoSerde a) Source # serializeBytes :: ProtoSerde a -> ByteString Source # | |
type FunctionTable = Map (Text, Text) (ByteString, ByteString -> Env -> ToFunction'InvocationBatchRequest -> IO (Either FlinkError (FunctionState ByteString))) Source #
Instances
| Functor JsonSerde Source # | |
| Json a => Serde (JsonSerde a) Source # | |
Defined in Network.Flink.Internal.Stateful Methods deserializeBytes :: ByteString -> Either String (JsonSerde a) Source # serializeBytes :: JsonSerde a -> ByteString Source # | |
newtype ProtoSerde a Source #
Constructors
| ProtoSerde | |
Fields
| |
Instances
| Functor ProtoSerde Source # | |
Defined in Network.Flink.Internal.Stateful Methods fmap :: (a -> b) -> ProtoSerde a -> ProtoSerde b # (<$) :: a -> ProtoSerde b -> ProtoSerde a # | |
| Message a => Serde (ProtoSerde a) Source # | |
Defined in Network.Flink.Internal.Stateful Methods deserializeBytes :: ByteString -> Either String (ProtoSerde a) Source # serializeBytes :: ProtoSerde a -> ByteString Source # | |
jsonState :: Json s => (a -> Function s ()) -> a -> Function (JsonSerde s) () Source #
Convenience function for wrapping state in newtype for JSON serialization
protoState :: Message s => (a -> Function s ()) -> a -> Function (ProtoSerde s) () Source #
Convenience function for wrapping state in newtype for Protobuf serialization
serdeInput :: (Serde s, Serde a, StatefulFunc s m, MonadError FlinkError m, MonadReader Env m) => (a -> m b) -> Any -> m b Source #
Deserializes input messages as arbitrary bytes by extracting them out of the protobuf Any and ignoring the type since that's protobuf specific
protoInput :: (Serde s, Message a, StatefulFunc s m, MonadError FlinkError m, MonadReader Env m) => (a -> m b) -> Any -> m b Source #
Deserializes input messages by unpacking the protobuf Any into the expected type.
If you are passing messages via protobuf, this is much more typesafe than serdeInput
jsonInput :: (Serde s, Json a, StatefulFunc s m, MonadError FlinkError m, MonadReader Env m) => (a -> m b) -> Any -> m b Source #
Deserializes input messages as arbitrary bytes by extracting them out of the protobuf Any and ignoring the type since that's protobuf specific