Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
To implement an ASAP:O producer, you should only need this interface. It exposes no memory-management functions (like free) or pointers, and is thus safe to use.
Synopsis
- newtype Endpoint = Endpoint Text
- newtype ProcessingThreads = ProcessingThreads Int
- data RequestHandlerType
- newtype Error = Error Text
- newtype Metadata = Metadata Text
- data SourceCredentials
- data DeletionFlags
- data Producer
- data LogLevel
- = LogNone
- | LogError
- | LogInfo
- | LogDebug
- | LogWarning
- newtype FileName = FileName Text
- newtype DatasetSubstream = DatasetSubstream Int
- newtype DatasetSize = DatasetSize Int
- data VersionInfo = VersionInfo {}
- data UpsertMode
- data MetadataIngestMode
- data AutoIdFlag
- data TransferFlag
- data StorageFlag
- data RequestResponse = RequestResponse {}
- data Opcode
- data GenericRequestHeader = GenericRequestHeader {}
- getRequestsQueueSize :: Producer -> IO Int
- getRequestsQueueVolumeMb :: Producer -> IO Int
- setRequestsQueueLimits :: Producer -> Int -> Int -> IO ()
- checkError :: (Ptr AsapoErrorHandle -> IO b) -> IO (Either Error b)
- checkErrorWithGivenHandle :: AsapoErrorHandle -> b -> IO (Either Error b)
- withProducer :: forall a. Endpoint -> ProcessingThreads -> RequestHandlerType -> SourceCredentials -> NominalDiffTime -> (Error -> IO a) -> (Producer -> IO a) -> IO a
- enableLocalLog :: Producer -> Bool -> IO ()
- waitRequestsFinished :: Producer -> NominalDiffTime -> IO (Either Error Int)
- getVersionInfo :: Producer -> IO (Either Error VersionInfo)
- getStreamInfo :: Producer -> StreamName -> NominalDiffTime -> IO (Either Error StreamInfo)
- getStreamMeta :: Producer -> StreamName -> NominalDiffTime -> IO (Either Error (Maybe Text))
- getBeamtimeMeta :: Producer -> NominalDiffTime -> IO (Either Error (Maybe Text))
- deleteStream :: Producer -> StreamName -> NominalDiffTime -> [DeletionFlags] -> IO (Either Error Int)
- getLastStream :: Producer -> NominalDiffTime -> IO (Either Error StreamInfo)
- send :: Producer -> MessageId -> FileName -> Metadata -> DatasetSubstream -> DatasetSize -> AutoIdFlag -> ByteString -> TransferFlag -> StorageFlag -> StreamName -> (RequestResponse -> IO ()) -> IO (Either Error Int)
- sendFile :: Producer -> MessageId -> FileName -> Metadata -> DatasetSubstream -> DatasetSize -> AutoIdFlag -> Int -> FileName -> TransferFlag -> StorageFlag -> StreamName -> (RequestResponse -> IO ()) -> IO (Either Error Int)
- sendStreamFinishedFlag :: Producer -> StreamName -> MessageId -> StreamName -> (RequestResponse -> IO ()) -> IO (Either Error Int)
- sendBeamtimeMetadata :: Producer -> Metadata -> MetadataIngestMode -> UpsertMode -> (RequestResponse -> IO ()) -> IO (Either Error Int)
- sendStreamMetadata :: Producer -> Metadata -> MetadataIngestMode -> UpsertMode -> StreamName -> (RequestResponse -> IO ()) -> IO (Either Error Int)
- setLogLevel :: Producer -> LogLevel -> IO ()
- enableRemoteLog :: Producer -> Bool -> IO ()
- setCredentials :: Producer -> SourceCredentials -> IO (Either Error Int)
Documentation
Wrapper around an ASAP:O producer endpoint (usually something like "host:port")
newtype ProcessingThreads Source #
Wrapper around the number of ASAP:O processing threads (simply to make call signatures mor readable)
Wrapper around an ASAP:O producer error. Note that there is only an error "explanation" here, no error code, since the C interface does not expose this.
data SourceCredentials Source #
data DeletionFlags Source #
DeleteMeta | Delete metadata also |
DeleteErrorOnNotExist | Don't throw an error if the data doesn't exist anyways |
Instances
Eq DeletionFlags Source # | |
Defined in Asapo.Either.Producer (==) :: DeletionFlags -> DeletionFlags -> Bool # (/=) :: DeletionFlags -> DeletionFlags -> Bool # |
Wrapper around file name (dubious to use Text
here, but fine for now)
data VersionInfo Source #
Instances
Show VersionInfo Source # | |
Defined in Asapo.Either.Producer showsPrec :: Int -> VersionInfo -> ShowS # show :: VersionInfo -> String # showList :: [VersionInfo] -> ShowS # |
data AutoIdFlag Source #
Anti-boolean-blindness for the "auto id" flag in the message header
Instances
Eq AutoIdFlag Source # | |
Defined in Asapo.Either.Producer (==) :: AutoIdFlag -> AutoIdFlag -> Bool # (/=) :: AutoIdFlag -> AutoIdFlag -> Bool # |
data RequestResponse Source #
Information about the request and its response, to be used in the ASAP:O send callback
data GenericRequestHeader Source #
Information about the send request, to be used in the ASAP:O send callback
getRequestsQueueSize :: Producer -> IO Int Source #
Get current size of the requests queue (number of requests pending/being processed)
getRequestsQueueVolumeMb :: Producer -> IO Int Source #
Get current volume of the requests queue (total memory of occupied by pending/being processed requests)
setRequestsQueueLimits Source #
Set maximum size of the requests queue
checkError :: (Ptr AsapoErrorHandle -> IO b) -> IO (Either Error b) Source #
Helper function since most ASAP:O functions receive a pointer to an error handle as the last argument, so error checking becomes "abstractable"
checkErrorWithGivenHandle :: AsapoErrorHandle -> b -> IO (Either Error b) Source #
Internal function to check and return either an error (if it's present behind the given handle) or a "result" of some function that produced the error handle
:: forall a. Endpoint | |
-> ProcessingThreads | |
-> RequestHandlerType | |
-> SourceCredentials | |
-> NominalDiffTime | timeout |
-> (Error -> IO a) | |
-> (Producer -> IO a) | |
-> IO a |
Create a producer and do something with it. This is the main entrypoint into the producer
waitRequestsFinished :: Producer -> NominalDiffTime -> IO (Either Error Int) Source #
Wait for all outstanding requests to finish
getVersionInfo :: Producer -> IO (Either Error VersionInfo) Source #
Retrieve producer version info
:: Producer | |
-> StreamName | |
-> NominalDiffTime | Timeout |
-> IO (Either Error StreamInfo) |
Retrieve info for a single stream
:: Producer | |
-> StreamName | |
-> NominalDiffTime | timeout |
-> IO (Either Error (Maybe Text)) |
Retrieve metadata for the given stream (which might be missing, in which case Nothing
is returned)
Retrieve metadata for the given stream (which might be missing, in which case Nothing
is returned)
:: Producer | |
-> StreamName | |
-> NominalDiffTime | timeout |
-> [DeletionFlags] | |
-> IO (Either Error Int) |
Delete the given stream
:: Producer | |
-> NominalDiffTime | Timeout |
-> IO (Either Error StreamInfo) |
Retrieve info for the latest stream
send :: Producer -> MessageId -> FileName -> Metadata -> DatasetSubstream -> DatasetSize -> AutoIdFlag -> ByteString -> TransferFlag -> StorageFlag -> StreamName -> (RequestResponse -> IO ()) -> IO (Either Error Int) Source #
Send a message containing raw data. Due to newtype and enum usage, all parameter should be self-explanatory
:: Producer | |
-> MessageId | |
-> FileName | File name to put into the message header |
-> Metadata | |
-> DatasetSubstream | |
-> DatasetSize | |
-> AutoIdFlag | |
-> Int | Size |
-> FileName | File to actually send |
-> TransferFlag | |
-> StorageFlag | |
-> StreamName | |
-> (RequestResponse -> IO ()) | |
-> IO (Either Error Int) |
Send a message containing a file. Due to newtype and enum usage, all parameter should be self-explanatory
sendStreamFinishedFlag :: Producer -> StreamName -> MessageId -> StreamName -> (RequestResponse -> IO ()) -> IO (Either Error Int) Source #
As the title says, send the "stream finished" flag
sendBeamtimeMetadata :: Producer -> Metadata -> MetadataIngestMode -> UpsertMode -> (RequestResponse -> IO ()) -> IO (Either Error Int) Source #
Send or extend beamtime metadata
sendStreamMetadata :: Producer -> Metadata -> MetadataIngestMode -> UpsertMode -> StreamName -> (RequestResponse -> IO ()) -> IO (Either Error Int) Source #
Send or extend stream metadata
setCredentials :: Producer -> SourceCredentials -> IO (Either Error Int) Source #
Set a different set of credentials