| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Orchestrate.Utils
Contents
- runO :: Monad m => OrchestrateT m a -> Session -> m (Either SomeException a)
- runO' :: Monad m => OrchestrateT m a -> Session -> m (Either SomeException a)
- orchestrateEither :: Monad m => Either SomeException a -> OrchestrateT m a
- io :: MonadIO m => IO a -> OrchestrateT m a
- api :: RequestHeaders -> [Text] -> [FormParam] -> RestCall a -> OrchestrateIO (Response a)
- api' :: RequestHeaders -> [Text] -> [FormParam] -> RestCall a -> OrchestrateIO (Either Status (Response a))
- api404 :: Show a => RequestHeaders -> [Text] -> [FormParam] -> RestCall a -> OrchestrateIO (Maybe (Response a))
- apiCheck :: RequestHeaders -> [Text] -> [FormParam] -> RestCall a -> OrchestrateIO (Response a)
- apiCheckDecode :: FromJSON a => RequestHeaders -> [Text] -> [FormParam] -> RestCall ByteString -> OrchestrateIO a
- ping :: OrchestrateIO ()
- baseUrl :: Monad m => OrchestrateT m Text
- buildUrl :: Monad m => [Text] -> OrchestrateT m String
- withAuth' :: APIKey -> Options
- withAuth :: APIKey -> Options -> Options
- envSession :: IO Session
- ifMatch :: IfMatch -> [Header]
- ifMatch' :: IfMatch' -> [Header]
- locationCollection :: Prism' Text Text
- locationKey :: Prism' Text Text
- locationRef :: Prism' Text Text
- locationType :: Prism' Text Text
- locationTimestamp :: Prism' Text Integer
- locationOrdinal :: Prism' Text Int
- getLocation :: Response a -> Text
- rangeStart :: FormValue a => ByteString -> RangeEnd a -> Maybe FormParam
- rangeEnd :: FormValue a => ByteString -> RangeEnd a -> Maybe FormParam
- rot :: (a -> b -> c -> d) -> c -> a -> b -> d
- tshow :: Show a => a -> Text
- initTail :: [a] -> (Maybe a, [a])
Type Utilities
Executing OrchestrateIO Actions
runO :: Monad m => OrchestrateT m a -> Session -> m (Either SomeException a) Source
Run an OrchestrateT action with a Session that does not include
authentication. This function will add proper authentication before
running the action.
runO' :: Monad m => OrchestrateT m a -> Session -> m (Either SomeException a) Source
Run an OrchestrateT action with a Session that already includes
authentication.
This is the most minimal handler.
Lifting
orchestrateEither :: Monad m => Either SomeException a -> OrchestrateT m a Source
Lifts an Either value into the OrchestrateT monad.
io :: MonadIO m => IO a -> OrchestrateT m a Source
Lifts an IO action into the OrchestrateT monad.
API Infrastructure
Arguments
| :: RequestHeaders | Additional HTTP headers. |
| -> [Text] | The parts of the URL path. |
| -> [FormParam] | The form parameters. |
| -> RestCall a | The wreq function to make the call. |
| -> OrchestrateIO (Response a) | Returns the call's response. |
This assembles and performs an API call.
Arguments
| :: RequestHeaders | Additional HTTP headers. |
| -> [Text] | The parts of the URL path. |
| -> [FormParam] | The form parameters. |
| -> RestCall a | The wreq function to make the call. |
| -> OrchestrateIO (Either Status (Response a)) | Returns either the error status or the response. |
This assembles and peforms an API call, lifting any status code errors
out of the monad and returning them in an explicit Either.
Arguments
| :: Show a | |
| => RequestHeaders | Additional HTTP headers. |
| -> [Text] | The parts of the URL path. |
| -> [FormParam] | The form parameters. |
| -> RestCall a | The wreq function to make the call. |
| -> OrchestrateIO (Maybe (Response a)) | Returns maybe the response. |
This assembles and performs an API call. It returns Nothing if the
call returns a 404 status code.
Arguments
| :: RequestHeaders | Additional HTTP headers. |
| -> [Text] | The parts of the URL path. |
| -> [FormParam] | The form parameters. |
| -> RestCall a | The wreq function to make the call. |
| -> OrchestrateIO (Response a) | Returns the verified response. |
This assembles and performs an API call and checks that the status
passes checkResponse.
Arguments
| :: FromJSON a | |
| => RequestHeaders | Additional HTTP headers. |
| -> [Text] | The parts of the URL path. |
| -> [FormParam] | The form parameters. |
| -> RestCall ByteString | The wreq function to make the call. |
| -> OrchestrateIO a | Returns the verified, decoded response. |
This assembles and performs an API call. Afterward it checks the status code and decodes the JSON response.
API Functions
ping :: OrchestrateIO () Source
Pings the Orchestrate API.
Data Type Helpers
Session Utilities
baseUrl :: Monad m => OrchestrateT m Text Source
Create the base Orchestrate API URL given the current Session.
Arguments
| :: Monad m | |
| => [Text] | The parts of the URL path. These are joined by |
| -> OrchestrateT m String | Returns the URL as a |
Builds a URL from its assembled parts.
envSession :: IO Session Source
This returns the Session with the API key taken from the
ORCHESTRATE_API environment variable.
The value of sessionOptions will include authentication.
Match Utilities
Location Prisms and Functions
locationType :: Prism' Text Text Source
A prism over the type part of a Location URL from an event
operation.
locationTimestamp :: Prism' Text Integer Source
A prism over the timestamp part of a Location URL from an event
operation.
locationOrdinal :: Prism' Text Int Source
A prism over the ordinal part of a Location URL from an event
operation.
getLocation :: Response a -> Text Source
Retrieves the Location from a response's headers.
Range Utilities
Arguments
| :: FormValue a | |
| => ByteString | The suffix for the form parameter. |
| -> RangeEnd a | The |
| -> Maybe FormParam | Returns the form parameter. |
Given a starting RangeEnd, return the form parameter.
Arguments
| :: FormValue a | |
| => ByteString | The suffix for the form parameter. |
| -> RangeEnd a | The |
| -> Maybe FormParam | Returns the form parameter. |
Given an ending RangeEnd, return the form parameter.