1
Fork 0

change the names in the ast to be lists so can support qualified names

everywhere:
  TRSimple: replaces the TRQualified
  Iden
  App name
  AggregateApp name
  WindowApp name
  operator names (not sure if this is used in ansi sql)
  explicit table
  function in from clause
This commit is contained in:
Jake Wheat 2014-04-18 11:43:37 +03:00
parent 3df87a3cf9
commit 2cad424379
7 changed files with 78 additions and 65 deletions

View file

@ -67,8 +67,8 @@ These are a few misc tests which don't fit anywhere else.
> ,("select a + b * c"
> ,makeSelect {qeSelectList =
> [(BinOp (Iden (Name "a")) (Name "+")
> (BinOp (Iden (Name "b")) (Name "*") (Iden (Name "c")))
> [(BinOp (Iden "a") "+"
> (BinOp (Iden "b") "*" (Iden "c"))
> ,Nothing)]})
> ]

View file

@ -21,7 +21,7 @@ expression
> ,ms [TRSimple "t", TRSimple "u"])
> ,("select a from s.t"
> ,ms [TRQualified "s" "t"])
> ,ms [TRSimple ["s","t"]])
these lateral queries make no sense but the syntax is valid

View file

@ -2,6 +2,7 @@
This is the types used to define the tests as pure data. See the
Tests.lhs module for the 'interpreter'.
> {-# LANGUAGE FlexibleInstances #-}
> module Language.SQL.SimpleSQL.TestTypes where
> import Language.SQL.SimpleSQL.Syntax
@ -24,3 +25,6 @@ hack to make the tests a bit simpler
> instance IsString Name where
> fromString = Name
> instance IsString [Name] where
> fromString = (:[]) . Name

View file

@ -47,7 +47,7 @@ Tests for parsing value expressions
> identifiers = Group "identifiers" $ map (uncurry TestValueExpr)
> [("iden1", Iden "iden1")
> --,("t.a", Iden2 "t" "a")
> ,("\"quoted identifier\"", Iden $ QName "quoted identifier")
> ,("\"quoted identifier\"", Iden [QName "quoted identifier"])
> ]
> star :: TestItem
@ -65,9 +65,9 @@ Tests for parsing value expressions
> dots :: TestItem
> dots = Group "dot" $ map (uncurry TestValueExpr)
> [("t.a", BinOp (Iden "t") "." (Iden "a"))
> [("t.a", Iden ["t","a"])
> ,("t.*", BinOp (Iden "t") "." Star)
> ,("a.b.c", BinOp (BinOp (Iden "a") "." (Iden "b")) "." (Iden "c"))
> ,("a.b.c", Iden ["a","b","c"])
> ,("ROW(t.*,42)", App "ROW" [BinOp (Iden "t") "." Star, NumLit "42"])
> ]