I am implementing a DSL that is based on using standard haskell functions/combinators to build database queries. From an implementation POV I decided to represent variables in the query like this:
newtype Variable = Var { fromVar :: Text }
this however forces the user to write Var "something"
quite often, so I decided to
write a quasiquoter that does this automatically.
here is an example for the DSL:
{-# LANGUAGE OverloadedStrings #-}
maxQuery :: Query MAX
maxQuery = match
( sch `isa` "school"
$ forWhich "ranking" `labelMatches` ran $ε)
`get` [ran]
`max` [ran]
where
[sch,ran] = map Var ["sch","ran"]
what I would like it to be:
maxQuery :: Query MAX
maxQuery = match
( sch `isa` "school"
$ forWhich "ranking" `labelMatches` ran $ε)
`get` [ran]
`max` [ran]
where [defVars| sch ran |]
or something similar to this.
the quasiquoter i wrote is here:
{-# LANGUAGE TemplateHaskell #-}
module TypeDBTH where
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Quote
import Data.List.Split
import Data.Text (pack)
mkVars :: [String] -> Dec
mkVars vars = ValD
(ListP (map (VarP . mkName) vars))
(NormalB (ListE (map (\v -> AppE (ConE $ mkName "Var")
$ AppE (VarE $ mkName "pack")
(LitE $ StringL v))
vars)))
[]
defVars :: QuasiQuoter
defVars = QuasiQuoter { quoteDec = quoteVars }
--, quoteExp = expQuoteVars }
quoteVars :: String -> Q [Dec]
quoteVars = return . return . mkVars . filter (/= "") . splitOn " "
expQuoteVars :: String -> Q Exp
expQuoteVars s = return $ LetE [(mkVars . filter (/= "") . splitOn " " $ s)] (LitE $ StringL "x")
originally I only wrote quoteVars
. for testing in ghci I added expQuoteVars
.
However, removing the latter one now and trying to write
...
where [defVars| sch ran |]
leaves me with two errors:
lib/TypeDBQuery.hs:806:1: error:
parse error (possibly incorrect indentation or mismatched brackets)
because of the where [quasiquoter]
with nothing after it
and
lib/TypeDBQuery.hs:807:5: error:
• Exception when trying to run compile-time code:
lib/TypeDBTH.hs:18:11-46: Missing field in record construction quoteExp
Code: Language.Haskell.TH.Quote.quoteExp defVars " sch ran "
• In the quasi-quotation: [defVars| sch ran |]
|
807 | x = [defVars| sch ran |]
| ^^^^^^^^^^^^^^^^^^^^
how can i use the quasiquoter for a quoteDec
instead of quoteExp
?
is this possible at all?
I would also be open to use it like this if this is easier then:
maxQuery :: Query MAX
maxQuery = let [defVars | sch ran |] in
$ match
( sch `isa` "school"
$ forWhich "ranking" `labelMatches` ran $ε)
`get` [ran]
`max` [ran]
i took a look at the "tutorials" and info sites of wiki.haskell.org and the TH modules but could not figure out how to do this... https://wiki.haskell.org/Template_Haskell#What_to_do_when_you_can.27t_splice_that_there https://wiki.haskell.org/Quasiquotation https://wiki.haskell.org/A_practical_Template_Haskell_Tutorial
You can only use declaration quasi quotes in top-level declarations unfortunately. From the documentation:
A quasiquote may appear in place of
- An expression
- A pattern
- A type
- A top-level declaration
Instead of using TH, you could consider using OverloadedStrings
:
instance IsString Variable where
fromString str = Var (pack str)
maxQuery :: Query MAX
maxQuery = match
( "sch" `isa` "school"
$ forWhich "ranking" `labelMatches` "ran" $ε)
`get` ["ran"]
`max` ["ran"]