[Haskell-cafe] Adding support for user defined data types to cassandra-cql

Cody Goodman codygman.consulting at gmail.com
Fri May 26 06:24:45 UTC 2017


Hello all,

I wrote some template Haskell code that looks up data in a cassandra
database in the system.schema_columns table using this library:
https://github.com/the-real-blackh/cassandra-cql/blob/master/Database/Cassandra/CQL.hs

Currently cassandra-cql lets you make queries like this:

getColFamInfo :: Query Rows () (Text, Text, Text, Text, Text)
getColFamInfo = "select keyspace_name, columnfamily_name, column_name,
type, validator from system.schema_columns"

And then it returns type (Text,Text,Text,Text,Text).

I'd prefer to be able to write a query like:

data MyRecord = MyRecord { a :: Text, b :: Text, c :: Text, d :: Text }

getColFamInfo :: Query Rows () (Maybe MyRecord)
getColFamInfo = "select keyspace_name, columnfamily_name, column_name,
type, validator from system.schema_columns"


Point being: I have types being generated from cassandra, but I have no
idea where I'd start modifying the cassandra-cql library to use those types.

Could anyone offer any direction? Also...

Below is a snippet of how Query is implemented, but you can find the full
code here:
https://github.com/the-real-blackh/cassandra-cql/blob/master/Database/Cassandra/CQL.hs

Query Looks like:

{ - START CODE -}

-- | The first type argument for Query. Tells us what kind of query it is.
data Style = Schema   -- ^ A query that modifies the schema, such as DROP
TABLE or CREATE TABLE
           | Write    -- ^ A query that writes data, such as an INSERT or
UPDATE
           | Rows     -- ^ A query that returns a list of rows, such as
SELECT

-- | The text of a CQL query, along with type parameters to make the query
type safe.
-- The type arguments are 'Style', followed by input and output column
types for the
-- query each represented as a tuple.
--
-- The /DataKinds/ language extension is required for 'Style'.
data Query :: Style -> * -> * -> * where
    Query :: QueryID -> Text -> Query style i o
    deriving Show

queryText :: Query s i o -> Text
queryText (Query _ txt) = txt

instance IsString (Query style i o) where
    fromString = query . T.pack

-- | Construct a query. Another way to construct one is as an overloaded
string through
-- the 'IsString' instance if you turn on the /OverloadedStrings/ language
extension, e.g.
--
-- > {-# LANGUAGE OverloadedStrings #-}
-- > ...
-- >
-- > getOneSong :: Query Rows UUID (Text, Text, Maybe Text)
-- > getOneSong = "select title, artist, comment from songs where id=?"
query :: Text -> Query style i o
query cql = Query (QueryID . hash . T.encodeUtf8 $ cql) cql
{ - END CODE -}


Thanks,

Cody Goodman
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170526/ac9eef99/attachment.html>


More information about the Haskell-Cafe mailing list