Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Connection
- data ConnId
- ident :: Lens' Connection ConnId
- host :: Lens' Connection Host
- connect :: MonadIO m => ConnectionSettings -> TimeoutManager -> Version -> Logger -> Host -> m Connection
- canConnect :: MonadIO m => Host -> m Bool
- close :: Connection -> IO ()
- request :: (Tuple a, Tuple b) => Connection -> Request k a b -> IO (Response k a b)
- type Raw a = a () () ()
- requestRaw :: Connection -> Raw Request -> IO (Raw Response)
- query :: (Tuple a, Tuple b, MonadIO m) => Connection -> Consistency -> QueryString k a b -> a -> m [b]
- defQueryParams :: Consistency -> a -> QueryParams a
- type EventHandler = Event -> IO ()
- allEventTypes :: [EventType]
- register :: MonadIO m => Connection -> [EventType] -> EventHandler -> m ()
- resolve :: HostName -> PortNumber -> IO [InetAddr]
Documentation
data Connection Source #
A connection to a Host
in a Cassandra cluster.
Instances
Eq Connection Source # | |
Defined in Database.CQL.IO.Connection (==) :: Connection -> Connection -> Bool # (/=) :: Connection -> Connection -> Bool # | |
Show Connection Source # | |
Defined in Database.CQL.IO.Connection showsPrec :: Int -> Connection -> ShowS # show :: Connection -> String # showList :: [Connection] -> ShowS # |
Lifecycle
connect :: MonadIO m => ConnectionSettings -> TimeoutManager -> Version -> Logger -> Host -> m Connection Source #
Establish and initialise a new connection to a Cassandra host.
canConnect :: MonadIO m => Host -> m Bool Source #
Check the connectivity of a Cassandra host on a new connection.
close :: Connection -> IO () Source #
Requests
requestRaw :: Connection -> Raw Request -> IO (Raw Response) Source #
Queries
query :: (Tuple a, Tuple b, MonadIO m) => Connection -> Consistency -> QueryString k a b -> a -> m [b] Source #
defQueryParams :: Consistency -> a -> QueryParams a Source #
Construct default QueryParams
for the given consistency
and bound values. In particular, no page size, paging state
or serial consistency will be set.
Events
type EventHandler = Event -> IO () Source #
allEventTypes :: [EventType] Source #
register :: MonadIO m => Connection -> [EventType] -> EventHandler -> m () Source #