hascas-1.1.0: Cassandra driver for haskell

Copyright(c) Saurabh Rawat 2016
LicenseApache
Maintainersaurabh.rawat90@gmail.com
Safe HaskellNone
LanguageHaskell2010

CQL

Contents

Description

This is a cassandra driver. It currently has:

  • Select
  • Insert
  • Update
  • Delete
  • Prepared Queries
  • Batch Queries
  • Automatic Records Conversion
  • Collections

The driver gets the list of all nodes in the cluster and load balances amongst them. So you can connect to any one node in the cluster and it will take care of the rest.

Initialize the driver by calling

  CQL.init host port retryInterval

for example

  CQL.init "127.0.0.1" (PortNumber 9042) (RetryInterval 1000000)

Example:

data Emp = Emp {
  empID    :: Int64,
  deptID   :: Int32,
  alive    :: Bool ,
  id       :: UUID,
  name     :: CQLString,
  salary   :: CQLDouble,
  someList :: CQLList Int32,
  someSet  :: CQLSet CQLDouble,
  someMap  :: CQLMap CQLString CQLString
}
  deriving(Show, Eq)

deriveBuildRec ''Emp

main :: IO ()
main = do
    candle <- CQL.init "127.0.0.1" (PortNumber 9042) (RetryInterval 1000000)

    res <- flip runReaderT candle $ runExceptT $ do
      let q = create "keyspace demodb WITH REPLICATION = {'class' : SimpleStrategy,replication_factor: 1}"
      runCQL LOCAL_ONE q

      --create a table
      let tableQuery = "TABLE demodb.emp (empID bigint,deptID int,alive boolean,id uuid,name varchar,salary double,"
                       ++ "someset setdouble,somelist listint,somemap maptext,PRIMARY KEY (empID, deptID))"

      let q = create tableQuery
      runCQL LOCAL_ONE q

      --execute prepared queries
      p <- prepare "INSERT INTO demodb.emp (empID,deptID,alive,id,name,salary,somelist,someset,somemap) VALUES (?,?,?,?,?,?,?,?,?)"
      execCQL LOCAL_ONE p [
            put (104::Int64),
            put (15::Int32),
            put True,
            put $ fromJust $ fromString "38d0ceb1-9e3e-427c-bc36-0106398f672b",
            put $ CQLString "Hot Shot",
            put $ CQLDouble 100000.0,
            put ((CQLList [1,2,3,4,5,6]) :: CQLList Int32),
            put ((CQLSet $ fromList [CQLDouble 0.001, CQLDouble 1000.0]) :: CQLSet CQLDouble),
            put $ CQLMap $ DMS.fromList [(CQLString "some", CQLString Things)]]

      -- execute prepared queries and get results
      p <- prepare "select empID, deptID, alive, id, name, salary, someset, somemap, somelist from demodb.emp where empid = ? and deptid = ?"
      res <- execCQL LOCAL_ONE p [
            put (104::Int64),
            put (15::Int32)]
      liftIO $ print $ catMaybes ((fmap fromRow res)::[Maybe Emp])
      liftIO $ print (fromCQL (Prelude.head res) (CQLString "salary")::Maybe Double)
      liftIO $ print (fromCQL (Prelude.head res) (CQLString "name")::Maybe CQLString)

      --select rows from table
      let q = select "demodb.emp"  and' "deptID" (15::Int32)
      rows <- runCQL LOCAL_ONE q
      liftIO $ print $ catMaybes ((fmap fromRow res)::[Maybe Emp])

      --batch queries
      p <- prepare "INSERT INTO demodb.emp (empID, deptID, alive, id, name, salary) VALUES (?, ?, ?, ?, ?, ?)"
      let q = batch (update "demodb.emp"  where' "empID" (104::Int64) # and' "deptID" (15::Int32)) <>
            batch (update "demodb.emp"  where' "empID" (104::Int64) # and' "deptID" (15::Int32)) <>
            prepBatch p [
                        put (101::Int64),
                        put (13::Int32),
                        put True,
                        put $ fromJust $ fromString "48d0ceb1-9e3e-427c-bc36-0106398f672b",
                        put $ CQLString "Hot1 Shot1",
                        put $ CQLDouble 10000.0]
      runBatch q

      --drop a table
      let q = drop' "table demodb.emp"
      runCQL LOCAL_ONE q

      --drop a keyspace
      let q = drop' "keyspace demodb"
      runCQL LOCAL_ONE q

    print res

Synopsis

Documentation

init :: HostName -> PortID -> RetryInterval -> ExceptT ShortStr IO Candle Source #

The first function you need to call. It initializes the driver and connects to the cluster. You only need to specify one node from your cluster here. Retryinterval is the interval with which connection to a node will be retried in case of disconnection.

data Consistency Source #

Consistency levels.

Instances

Eq Consistency Source # 
Generic Consistency Source # 

Associated Types

type Rep Consistency :: * -> * #

Binary Consistency Source # 
type Rep Consistency Source # 
type Rep Consistency = D1 (MetaData "Consistency" "Common" "hascas-1.1.0-2J3p39r14RvLXXEsGkmsnj" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ANY" PrefixI False) U1) (C1 (MetaCons "ONE" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TWO" PrefixI False) U1) ((:+:) (C1 (MetaCons "THREE" PrefixI False) U1) (C1 (MetaCons "QUORUM" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "ALL" PrefixI False) U1) ((:+:) (C1 (MetaCons "LOCAL_QUORUM" PrefixI False) U1) (C1 (MetaCons "EACH_QUORUM" PrefixI False) U1))) ((:+:) (C1 (MetaCons "SERIAL" PrefixI False) U1) ((:+:) (C1 (MetaCons "LOCAL_SERIAL" PrefixI False) U1) (C1 (MetaCons "LOCAL_ONE" PrefixI False) U1)))))

newtype RetryInterval Source #

Constructors

RetryInterval Int 

Data Types

data Rows Source #

Instances

type Row = Map CQLString (Word16, Maybe Word16, Maybe Word16, Bytes) Source #

Row result type.

newtype Bytes Source #

Constructors

Bytes ByteString 

Instances

Eq Bytes Source # 

Methods

(==) :: Bytes -> Bytes -> Bool #

(/=) :: Bytes -> Bytes -> Bool #

Ord Bytes Source # 

Methods

compare :: Bytes -> Bytes -> Ordering #

(<) :: Bytes -> Bytes -> Bool #

(<=) :: Bytes -> Bytes -> Bool #

(>) :: Bytes -> Bytes -> Bool #

(>=) :: Bytes -> Bytes -> Bool #

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

Show Bytes Source # 

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Binary Bytes Source # 

Methods

put :: Bytes -> Put #

get :: Get Bytes #

putList :: [Bytes] -> Put #

newtype CQLMap k v Source #

Constructors

CQLMap (Map k v) 

Instances

(Eq v, Eq k) => Eq (CQLMap k v) Source # 

Methods

(==) :: CQLMap k v -> CQLMap k v -> Bool #

(/=) :: CQLMap k v -> CQLMap k v -> Bool #

(Ord v, Ord k) => Ord (CQLMap k v) Source # 

Methods

compare :: CQLMap k v -> CQLMap k v -> Ordering #

(<) :: CQLMap k v -> CQLMap k v -> Bool #

(<=) :: CQLMap k v -> CQLMap k v -> Bool #

(>) :: CQLMap k v -> CQLMap k v -> Bool #

(>=) :: CQLMap k v -> CQLMap k v -> Bool #

max :: CQLMap k v -> CQLMap k v -> CQLMap k v #

min :: CQLMap k v -> CQLMap k v -> CQLMap k v #

(Show v, Show k) => Show (CQLMap k v) Source # 

Methods

showsPrec :: Int -> CQLMap k v -> ShowS #

show :: CQLMap k v -> String #

showList :: [CQLMap k v] -> ShowS #

Generic (CQLMap k v) Source # 

Associated Types

type Rep (CQLMap k v) :: * -> * #

Methods

from :: CQLMap k v -> Rep (CQLMap k v) x #

to :: Rep (CQLMap k v) x -> CQLMap k v #

type Rep (CQLMap k v) Source # 
type Rep (CQLMap k v) = D1 (MetaData "CQLMap" "Common" "hascas-1.1.0-2J3p39r14RvLXXEsGkmsnj" True) (C1 (MetaCons "CQLMap" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map k v))))

newtype CQLSet el Source #

Constructors

CQLSet (Set el) 

Instances

Eq el => Eq (CQLSet el) Source # 

Methods

(==) :: CQLSet el -> CQLSet el -> Bool #

(/=) :: CQLSet el -> CQLSet el -> Bool #

Ord el => Ord (CQLSet el) Source # 

Methods

compare :: CQLSet el -> CQLSet el -> Ordering #

(<) :: CQLSet el -> CQLSet el -> Bool #

(<=) :: CQLSet el -> CQLSet el -> Bool #

(>) :: CQLSet el -> CQLSet el -> Bool #

(>=) :: CQLSet el -> CQLSet el -> Bool #

max :: CQLSet el -> CQLSet el -> CQLSet el #

min :: CQLSet el -> CQLSet el -> CQLSet el #

Show el => Show (CQLSet el) Source # 

Methods

showsPrec :: Int -> CQLSet el -> ShowS #

show :: CQLSet el -> String #

showList :: [CQLSet el] -> ShowS #

Generic (CQLSet el) Source # 

Associated Types

type Rep (CQLSet el) :: * -> * #

Methods

from :: CQLSet el -> Rep (CQLSet el) x #

to :: Rep (CQLSet el) x -> CQLSet el #

type Rep (CQLSet el) Source # 
type Rep (CQLSet el) = D1 (MetaData "CQLSet" "Common" "hascas-1.1.0-2J3p39r14RvLXXEsGkmsnj" True) (C1 (MetaCons "CQLSet" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set el))))

newtype CQLList el Source #

Constructors

CQLList [el] 

Instances

Eq el => Eq (CQLList el) Source # 

Methods

(==) :: CQLList el -> CQLList el -> Bool #

(/=) :: CQLList el -> CQLList el -> Bool #

Ord el => Ord (CQLList el) Source # 

Methods

compare :: CQLList el -> CQLList el -> Ordering #

(<) :: CQLList el -> CQLList el -> Bool #

(<=) :: CQLList el -> CQLList el -> Bool #

(>) :: CQLList el -> CQLList el -> Bool #

(>=) :: CQLList el -> CQLList el -> Bool #

max :: CQLList el -> CQLList el -> CQLList el #

min :: CQLList el -> CQLList el -> CQLList el #

Show el => Show (CQLList el) Source # 

Methods

showsPrec :: Int -> CQLList el -> ShowS #

show :: CQLList el -> String #

showList :: [CQLList el] -> ShowS #

Generic (CQLList el) Source # 

Associated Types

type Rep (CQLList el) :: * -> * #

Methods

from :: CQLList el -> Rep (CQLList el) x #

to :: Rep (CQLList el) x -> CQLList el #

type Rep (CQLList el) Source # 
type Rep (CQLList el) = D1 (MetaData "CQLList" "Common" "hascas-1.1.0-2J3p39r14RvLXXEsGkmsnj" True) (C1 (MetaCons "CQLList" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [el])))

Auto derive conversion for record types

deriveBuildRec :: Name -> Q [Dec] Source #

Derives BuildRec instances for record types.

fromRow :: BuildRec a => Row -> Maybe a Source #

Get the result from a row.

DSL for creating queries

(#) :: Q -> Q -> Q infixl 7 Source #

Combine DSL actions select "demodb.emp" and' "deptID" (15::Int32)

limit :: Int -> Q Source #

with :: Binary k => String -> k -> Q Source #

where' :: Binary k => String -> k -> Q Source #

and' :: Binary k => String -> k -> Q Source #

Prepare and run queries

runCQL :: Consistency -> Q -> ExceptT ShortStr (ReaderT Candle IO) [Row] Source #

Run a query directly.

prepare :: ByteString -> ExceptT ShortStr (ReaderT Candle IO) Prepared Source #

Prepare a query, returns a prepared query which can be fed to execCQL for execution.

execCQL :: Consistency -> Prepared -> [Put] -> ExceptT ShortStr (ReaderT Candle IO) [Row] Source #

Execute a prepared query.

Batching

batch :: Q -> LoggedBatch Source #

Create a simple batch statement, with query string and parameters.

prepBatch :: Prepared -> [Put] -> LoggedBatch Source #

Create a prepared batch statement with Prepared query and parameters.

runBatch :: Batchable a => a -> ExceptT ShortStr (ReaderT Candle IO) [Row] Source #

Run a batch query.