Generate QuasiQuoter with TemplateHaskell

Hello!

I have a feeling this is probably some silly mistake, but I can’t figure it out.

Given this QuasiQuoter

[database|
database testDb

table data_types
    type_text text
    type_integer integer
    type_bigint bigint
    type_boolean boolean
|]

I get an error.

test/Test/Db.hs:8:11: error:
    • Type constructor ‘QuasiQuoter’ used as a constructor-like thing
    • In the expression:
        QuasiQuoter
          {quotePat = error "quasiquoter used in pattern context",
           quoteType = error "quasiquoter used in type context",
           quoteDec = error "quasiquoter used in declaration context",
           quoteExp = dbSql}
      In an equation for ‘sql’:
          sql
            = QuasiQuoter
                {quotePat = error "quasiquoter used in pattern context",
                 quoteType = error "quasiquoter used in type context",
                 quoteDec = error "quasiquoter used in declaration context",
                 quoteExp = dbSql}

When I expand the database QuasiQuoter (expand TemplateHaskell Splice from HLS) I get this.

dbSql :: String -> Q Exp
dbSql
  = unsafeSql
      (((Database ((unpackCStringLen# "testDb"#) 6))
          ...

sql :: QuasiQuoter
sql
  = QuasiQuoter
      {quotePat = error "quasiquoter used in pattern context",
       quoteType = error "quasiquoter used in type context",
       quoteDec = error "quasiquoter used in declaration context",
       quoteExp = dbSql}

The sql QuasiQuoter looks legit to me, in fact if I don’t generate it with TH and just write it by hand like this

[database|
database testDb

table data_types
    type_text text
    type_integer integer
    type_bigint bigint
    type_boolean boolean
|]

sql :: QuasiQuoter
sql =
  QuasiQuoter
    { quotePat = error "quasiquoter used in pattern context"
    , quoteType = error "quasiquoter used in type context"
    , quoteDec = error "quasiquoter used in declaration context"
    , quoteExp = dbSql
    }

it works just fine.

Relevant code is here and here.

You need to use a single prime on this line:

With double primes it will look for the type constructor name, but you want the term constructor.

2 Likes

Thank you very much! That was indeed it, and yep, “some silly mistake”.

I can even confidently say that, after understanding the problem, I now also understand the error message :sweat_smile:

I must agree that the error message is not that helpful:

Type constructor ‘QuasiQuoter’ used as a constructor-like thing

It is a type constructor so why is it a problem that it is used as a constructor-like thing?

In my comment I distinguished type constructors from term constructors, but that’s also not very easy to understand for everyone I’d imagine. I wonder what a better message would be.

By the way, you can and probably should define your functions like genQuasiQuote like this:

genQuasiQuote :: Quote m => Name -> Name -> m [Dec]
genQuasiQuote sql dbSql =
  [d| $(varP sql)
        = QuasiQuoter
            {quotePat = error "quasiquoter used in pattern context",
             quoteType = error "quasiquoter used in type context",
             quoteDec = error "quasiquoter used in declaration context",
             quoteExp = $(varE dbSql)} |]

That avoids depending too much on the internal template haskell types.

Edit: You can’t easily splice in a given name into the type signature. You could also consider to let the templates define the names for you automatically, e.g.:

gen :: Quote m => m Exp -> m [Dec]
gen dbExp =
  [d| dbSql :: String -> Q Exp
      dbSql = unsafeSql $dbExp
 
      sql :: QuasiQuoter
      sql
        = QuasiQuoter
            {quotePat = error "quasiquoter used in pattern context",
             quoteType = error "quasiquoter used in type context",
             quoteDec = error "quasiquoter used in declaration context",
             quoteExp = dbSql} |]
2 Likes

Well, this is what GHC normally does.

data X = MkX String

f = X "abc"

test/Test/Db.hs:28:5: error:
    • Illegal term-level use of the type constructor or class ‘X’
    • defined at test/Test/Db.hs:26:1
    • In the expression: X "abc"
      In an equation for ‘f’: f = X "abc"
   |
28 | f = X "abc"
   |     ^

I think this is the problem.

data X = MkX { abc :: String }

f = X { abc = "abc" }

test/Test/Db.hs:28:5: error: Not in scope: data constructor ‘X’
   |
28 | f = X { abc = "abc" }
   |     ^

So in normal circumstances, GHC doesn’t assume it is a type constructor that we are trying to use, but it simply fails to find a relevant data constructor. Thanks to the TH magic, we can actually place a type constructor there.

Oh, that looks way more readable than bare AST. Names will be unfortunately very important in the future, as I plan to TH a lot of things for the user (persistent-like generation of types for columns holding primary keys etc).

While we are at it (or maybe it should be another post?) I’m curious what do you think of this monster:

It is silly, but it allows for this library to even be a thing, so it’s kinda important.

I think there’s a bug in it, because you are coercing the label := ty to ty. Edit: or I guess you could just store the ty directly in the any when constructing these?

But my immediate thought was that you can do this safely with a GADT:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedRecordDot #-}

import GHC.Records
import GHC.TypeLits
import Data.Proxy
import Data.Kind

type (:=) :: Symbol -> Type -> Type
data label := ty = (KnownSymbol label) => Proxy label := ty

type Row :: [Type] -> Type
data Row xs where
  RNil :: Row '[]
  RCons :: x -> Row xs -> Row ((l := x) : xs)

instance HasField l (Row ((l := t) : e)) t where
  getField (RCons x _) = x
  {-# INLINE getField #-}

instance HasField l (Row (_0 : (l := t) : e)) t where
  getField (RCons _ (RCons x _)) = x
  {-# INLINE getField #-}

foo :: Row ["x" := Int, "y" := Int]
foo = RCons 1 (RCons 2 RNil)

bar :: Int
bar = foo.y

foo2 :: Row ["x" := Int, "x" := Int]
foo2 = RCons 1 (RCons 2 RNil)

bar2 :: Int
bar2 = foo2.x

I’m honestly surprised GHC does not complain about overlapping even if I use the same label name multiple times. Nevermind, it does:

Row.hs:36:8: error:
    • Overlapping instances for HasField
                                  "x" (Row '["x" := Int, "x" := Int]) Int
        arising from selecting the field ‘x’
      Matching instances:
        instance HasField l (Row (_0 : (l := t) : e)) t
          -- Defined at Row.hs:22:10
        instance HasField l (Row ((l := t) : e)) t
          -- Defined at Row.hs:18:10
    • In the expression: foo2.x
      In an equation for ‘bar2’: bar2 = foo2.x
   |
36 | bar2 = foo2.x
   |        ^^^^^^

You could also consider using the row-types package.

Or HList:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE UndecidableInstances #-}

import Data.HList as HL
import GHC.Records as GR

instance HL.HasField l (Record r) v => GR.HasField l (Record r) v where
  getField = hLookupByLabel (Label @l)
  {-# INLINE getField #-}

foo :: Record [Tagged "x" Int, Tagged "y" Int]
foo = Tagged 1 .*. Tagged 2 .*. emptyRecord

bar :: Int
bar = foo.y

Or vinyl. Or plenty of others. This wheel has been invented many times over.

1 Like

I suggested row-types because it seems like the best offering according to this sheet:

1 Like

Hm I’m not sure what this means. I’m unable to misuse it (misconstruction is a different thing, but hopefully library will handle it).

Those GADT/HList variants don’t look too performant for the task. This thing will hold potentially many rows from the database and because it it statically known what the database will return I can generate serialization code for each query.

row-types looks interesting, but this might be problematic “Lists of (label,type) pairs are kept sorted thereby ensuring that { x = 0, y = 0 } and { y = 0, x = 0 } have the same type.” in the context of query results.

I guess I’ll have to study this comparison document, it is really well made!

I mean that constructing rows like this won’t work:

myRow :: Row ["x" := Int, "y" := Int]
myRow = Row [unsafeCoerce (Proxy @"x" := (1 :: Int)), unsafeCoerce (Proxy @"y" := (1 :: Int))]

But I realised you are probably constructing them like this:

myRow :: Row ["x" := Int, "y" := Int]
myRow = Row [unsafeCoerce (1 :: Int), unsafeCoerce (1 :: Int)]

Ah, but you’re using slow lists too. If all your types are serializable then you should probably be using a type like ByteArray or perhaps a manually managed Ptr together with Storable instances for the contents.

1 Like

Could you articulate in words what you aim to achieve with the “monster”?

Yes, the list is temporary, just a convenient thing for a proof of concept. I was thinking about SmallArray from primitive. I’ll add ByteArray to the pile, when I can get to some benchmarks. Thanks.

The Row type or the library? I’ll answer both, as they are connected.

The Vector of Rows is supposed to hold an arbitrary relation - result of an arbitrary database query. As such, I think, it is fine for it to be read only and focused on fast construction/access, rather than users manipulating it, which is the main concern of other record libraries (and, well, a far harder task).

The Library? I think there is a gap in the database libraries landscape. We have “database”-simple libs, that allow you to write SQL, but are unsafe and bother you with serialization. And we have EDSL libs, that are safer, offer some automatic serialization, but limit what queries you can express and require buy-in; you have to learn them and their way of doing things.

The closest thing to what I want is, AFAIK, hasql-th, but it can only check the syntax, and you still have to serialize the results and define some record to easily work with the result.

So to close the gap, I want a library that will allow writing arbitrary SQL and automatically serializing the results to an easy-to-use (read, really) data structure. No custom records for each query, as query itself already defines the data structure!

1 Like