orchestrate-0.2.0.3: An API client for http://orchestrate.io/.

Safe HaskellNone
LanguageHaskell2010

Database.Orchestrate.Types

Contents

Synopsis

General Types

Aliases

type Key = Text Source

type Ref = Text Source

type RestCall a = Options -> String -> IO (Response a) Source

This represents a function that makes a call to the Orchestrate API server. It takes Options, a URL String, and returns a Response.

Result Limits

Conditional API Calls

data IfMatch Source

A richer type than IfMatch for specifying conditional calls.

Constructors

IfMatch Ref

Only perform the action if the ref does exist.

IfNoneMatch Ref

Only perform the action if the ref does not exist.

NoMatch

Always perform the action.

Instances

Ranges

type Range a = (RangeEnd a, RangeEnd a) Source

This is a range tuple. Each end can be specified separately.

data RangeEnd a Source

This represents the end of a range.

Constructors

Inclusive a

The end should be inclusive. I.e., it should include a.

Exclusive a

The end should be exclusive. I.e., it should not include a.

Open

There is no bound on this end.

Key/Value Types

type KVList v = ResultList (ResultItem Path v) Source

A list of data returned by listV.

v
The type of the data contained in the list.

Ref Types

data TombstoneItem v Source

TombstoneItem data represents the data values in the database.

Constructors

TombstoneItem

TombstoneItem data are no longer alive. They are simply markers for deleted data.

Fields

_tombstonePath :: !Path

The path to the deleted data.

_tombstoneTime :: !Timestamp

The timestamp of this data.

LiveItem

LiveItem data are still in the database.

Fields

_livePath :: !Path

The path to the data.

_liveValue :: !(Maybe v)

If values are requested, this will contain the data.

_liveTime :: !Timestamp

The timestamp for the data.

Type Lenses and Prisms

_TombstoneItem :: Prism' (TombstoneItem v) (TombstoneItem v) Source

A Prism' into data created with the TombstoneItem constructor.

_LiveItem :: Prism' (TombstoneItem v) (TombstoneItem v) Source

A Prism' into data created with the LiveItem constructor.

Event Types

Type Aliases

type EventList a b = ResultList (EventItem a b) Source

A list of events returned by listEvents.

This data type uses two parameters:

a
The type of data being stored for the event.
b
A phantom type for the type of data associated with the event. This data must also be stored in Orchestrate using the Database.Orchestrate.KeyValue API.

Event Location

data EventPath Source

The data necessary to access an event.

Constructors

EventPath 

Fields

_eventPath :: !Path

The base Path to this data.

_eventPathType :: !EventType

The kind of event.

_eventPathTime :: !Timestamp

The event's timestamp.

_eventPathOrd :: !Int

The event's ordinal number.

Event Data

data EventItem a b Source

One item in an EventList.

This data type uses two parameters:

a
The type of data being stored for the event.
b
A phantom type for the type of data associated with the event. This data must also be stored in Orchestrate using the Database.Orchestrate.KeyValue API.

Constructors

EventItem 

Fields

_eventItem :: !(ResultItem EventPath a)

The data itself and the path to it.

_eventTime :: !Timestamp

The event's timestamp.

_eventOrd :: !Int

The event's ordinal number.

Instances

eventOrd :: forall a b b. Lens (EventItem a b) (EventItem a b) Int Int Source

Graph Types

type RelList a b = ResultList (ResultItem Path b) Source

A list of edges returned by getRel.

This datatype uses two parameters:

a
The data type for the edge's origin node.
b
The data type for the edge's target node.

Search Types

List of Search Results

data SearchList v Source

The collection of search results.

Constructors

SearchList 

Fields

_searchResults :: !(ResultList (SearchItem v))

The list of search results.

_searchTotal :: !Int

The total number of hits for the search. This may be more than the number of results returned.

Single Search Result

data SearchItem v Source

A single search item.

Constructors

SearchItem 

Fields

_searchItem :: !(ResultItem Path v)

The path to the item and the item itself.

_searchScore :: !Double

The item's relevancy to the query.

Session

data Session Source

The data for a session with the Orchestrate database.

Constructors

Session 

Fields

_sessionURL :: !Text

The base URL for the Orchestrate API.

_sessionKey :: !APIKey

The API key for accessing the API.

_sessionVersion :: !Int

The version of the API.

_sessionOptions :: !Options

The baseline set of Options for making wreq calls. This includes the API key.

Orchestrate Types

Data

class (ToJSON a, FromJSON a) => OrchestrateData a where Source

This is a class for data that can be stored in an Orchestrate Key/Value store. See Database.Orchestrate.KeyValue for where this is used.

Methods

tableName :: a -> Collection Source

This is the name of the collection to store this data type in.

dataKey :: a -> Key Source

This is the key to store the value in.

Monad Types

newtype OrchestrateT m a Source

The type for the Orchestrate monad. All interactions with the Orchestrate API are run in this monad. It combines a reader over Session data with error handling using EitherT SomeException.

type OrchestrateIO = OrchestrateT IO Source

OrchestrateT over IO, the way God intended.

type Orchestrate = OrchestrateT Identity Source

OrchestrateT over Identity. Only the most useless monad ever.

Result Types

Lists of Results

data ResultList i Source

A parameterized list of results returned by an API call.

i
the type of the data contained.

Constructors

ResultList 

resultList :: forall i i. Lens (ResultList i) (ResultList i) [i] [i] Source

Individual Results

data ResultItem p v Source

A parameterized single item returned in a collection by an API call.

p
the type of the path data to this data.
v
the type of the value for this data.

Constructors

ResultItem 

Fields

_itemPath :: !p
 
_itemValue :: !v
 

Instances

itemPath :: forall p v p. Lens (ResultItem p v) (ResultItem p v) p p Source

itemValue :: forall p v v. Lens (ResultItem p v) (ResultItem p v) v v Source

Rich Item Locations (Paths)

data Path Source

This represents the unique access information for a value in the store.

Constructors

Path 

Fields

_itemCollection :: !Collection

The collection containing the data.

_itemKey :: !Key

The data's key in the collection.

_itemRef :: !Ref

The reference to the current version of the value.

Re-exports

Accessing Data

ask :: MonadReader r m => m r

Retrieves the monad environment.

asks

Arguments

:: forall (m :: * -> *). MonadReader r m 
=> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

Throwing and Handling Errors

throwError :: MonadError e m => forall a. e -> m a

Is used within a monadic computation to begin exception processing.

catchError :: MonadError e m => forall a. m a -> (e -> m a) -> m a

A handler function to handle previous errors and return to normal execution. A common idiom is:

do { action1; action2; action3 } `catchError` handler

where the action functions can call throwError. Note that handler and the do-block must have the same return type.