1
Fork 0

don't include unfinished tests in the test suite

fix number literals to accept upper case E
implement multi part string literals
fix tests for string literals, typed literals, boolean literals and
  number literals in the sql 2003 tests
This commit is contained in:
Jake Wheat 2014-04-17 19:19:41 +03:00
parent 488310ff6a
commit 19df6f18aa
2 changed files with 79 additions and 58 deletions

View file

@ -869,7 +869,7 @@ make this choice.
> fracts p = (p++) <$> int > fracts p = (p++) <$> int
> expon p = concat <$> sequence > expon p = concat <$> sequence
> [return p > [return p
> ,string "e" > ,(:[]) <$> oneOf "eE"
> ,option "" (string "+" <|> string "-") > ,option "" (string "+" <|> string "-")
> ,int] > ,int]
@ -926,10 +926,20 @@ todo: work out the symbol parsing better
> >>= optionSuffix moreString) > >>= optionSuffix moreString)
> <?> "string" > <?> "string"
> where > where
> moreString s0 = try $ do > moreString s0 = try $ choice
> [-- handle two adjacent quotes
> do
> void $ char '\'' > void $ char '\''
> s <- manyTill anyChar (char '\'') > s <- manyTill anyChar (char '\'')
> optionSuffix moreString (s0 ++ "'" ++ s) > optionSuffix moreString (s0 ++ "'" ++ s)
> ,-- handle string in separate parts
> -- e.g. 'part 1' 'part 2'
> do
> whitespace
> void $ char '\''
> s <- manyTill anyChar (char '\'')
> optionSuffix moreString (s0 ++ s)
> ]
= helper functions = helper functions

View file

@ -8,6 +8,7 @@ We are only interested in the query syntax, goes through sections 5-10
The goal is to create some coverage tests to get close to supporting a The goal is to create some coverage tests to get close to supporting a
large amount of the SQL. large amount of the SQL.
> {-# LANGUAGE OverloadedStrings #-}
> module Language.SQL.SimpleSQL.SQL2003 (sql2003Tests) where > module Language.SQL.SimpleSQL.SQL2003 (sql2003Tests) where
> import Language.SQL.SimpleSQL.TestTypes > import Language.SQL.SimpleSQL.TestTypes
@ -16,30 +17,30 @@ large amount of the SQL.
> sql2003Tests :: TestItem > sql2003Tests :: TestItem
> sql2003Tests = Group "sql2003Tests" > sql2003Tests = Group "sql2003Tests"
> [stringLiterals > [stringLiterals
> ,nationalCharacterStringLiterals > --,nationalCharacterStringLiterals
> ,unicodeStringLiterals > --,unicodeStringLiterals
> ,binaryStringLiterals > --,binaryStringLiterals
> ,numericLiterals > ,numericLiterals
> ,dateAndTimeLiterals > ,dateAndTimeLiterals
> ,booleanLiterals > ,booleanLiterals
> ,identifiers > --,identifiers
> ,typeNames > --,typeNames
> ,parenthesizedValueExpression > --,parenthesizedValueExpression
> ,targetSpecification > --,targetSpecification
> ,contextuallyTypeValueSpec > --,contextuallyTypeValueSpec
> ,nextValueExpression > --,nextValueExpression
> ,arrayElementReference > --,arrayElementReference
> ,multisetElementReference > --,multisetElementReference
> ,numericValueExpression > --,numericValueExpression
> ,booleanValueExpression > --,booleanValueExpression
> ,arrayValueConstructor > --,arrayValueConstructor
> ,tableValueConstructor > --,tableValueConstructor
> ,fromClause > --,fromClause
> ,whereClause > --,whereClause
> ,groupbyClause > --,groupbyClause
> ,querySpecification > --,querySpecification
> ,queryExpressions > --,queryExpressions
> ,sortSpecificationList > --,sortSpecificationList
> ] > ]
= 5 Lexical Elements = 5 Lexical Elements
@ -245,6 +246,8 @@ Syntax rule 6: A <nondoublequote character> is any character of the source langu
The rule for <doublequote symbol> in the standard uses two adjacent literal double quotes rather than referencing <double quote>; the reasons are not clear. It is annotated '!! two consecutive double quote characters'. The rule for <doublequote symbol> in the standard uses two adjacent literal double quotes rather than referencing <double quote>; the reasons are not clear. It is annotated '!! two consecutive double quote characters'.
TODO: unicode delimited identifier
<doublequote symbol> ::= <double quote> <double quote> <doublequote symbol> ::= <double quote> <double quote>
<delimiter token> ::= <delimiter token> ::=
@ -463,11 +466,16 @@ The <quote symbol> rule consists of two immediately adjacent <quote> marks with
> stringLiterals :: TestItem > stringLiterals :: TestItem
> stringLiterals = Group "string literals" $ map (uncurry TestValueExpr) > stringLiterals = Group "string literals" $ map (uncurry TestValueExpr)
> [("'a regular string literal'", undefined) > [("'a regular string literal'"
> ,("'something' ' some more' 'and more'", undefined) > ,StringLit "a regular string literal")
> ,("'something' \n ' some more' \t 'and more'", undefined) > ,("'something' ' some more' 'and more'"
> ,("'something' -- a comment\n ' some more' /*another comment*/ 'and more'", undefined) > ,StringLit "something some moreand more")
> ,("'a quote: '', stuff'", undefined) > ,("'something' \n ' some more' \t 'and more'"
> ,StringLit "something some moreand more")
> ,("'something' -- a comment\n ' some more' /*another comment*/ 'and more'"
> ,StringLit "something some moreand more")
> ,("'a quote: '', stuff'"
> ,StringLit "a quote: ', stuff")
> ] > ]
TODO: all the stuff with character set representations. TODO: all the stuff with character set representations.
@ -546,32 +554,32 @@ TODO: separator stuff for all the string literals?
> numericLiterals :: TestItem > numericLiterals :: TestItem
> numericLiterals = Group "numeric literals" $ map (uncurry TestValueExpr) > numericLiterals = Group "numeric literals" $ map (uncurry TestValueExpr)
> [("11", undefined) > [("11", NumLit "11")
> ,("11.11", undefined) > ,("11.11", NumLit "11.11")
> ,("11E23", undefined) > ,("11E23", NumLit "11E23")
> ,("11E+23", undefined) > ,("11E+23", NumLit "11E+23")
> ,("11E-23", undefined) > ,("11E-23", NumLit "11E-23")
> ,("11.11E23", undefined) > ,("11.11E23", NumLit "11.11E23")
> ,("11.11E+23", undefined) > ,("11.11E+23", NumLit "11.11E+23")
> ,("11.11E-23", undefined) > ,("11.11E-23", NumLit "11.11E-23")
> ,("+11E23", undefined) > ,("+11E23", PrefixOp "+" $ NumLit "11E23")
> ,("+11E+23", undefined) > ,("+11E+23", PrefixOp "+" $ NumLit "11E+23")
> ,("+11E-23", undefined) > ,("+11E-23", PrefixOp "+" $ NumLit "11E-23")
> ,("+11.11E23", undefined) > ,("+11.11E23", PrefixOp "+" $ NumLit "11.11E23")
> ,("+11.11E+23", undefined) > ,("+11.11E+23", PrefixOp "+" $ NumLit "11.11E+23")
> ,("+11.11E-23", undefined) > ,("+11.11E-23", PrefixOp "+" $ NumLit "11.11E-23")
> ,("-11E23", undefined) > ,("-11E23", PrefixOp "-" $ NumLit "11E23")
> ,("-11E+23", undefined) > ,("-11E+23", PrefixOp "-" $ NumLit "11E+23")
> ,("-11E-23", undefined) > ,("-11E-23", PrefixOp "-" $ NumLit "11E-23")
> ,("-11.11E23", undefined) > ,("-11.11E23", PrefixOp "-" $ NumLit "11.11E23")
> ,("-11.11E+23", undefined) > ,("-11.11E+23", PrefixOp "-" $ NumLit "11.11E+23")
> ,("-11.11E-23", undefined) > ,("-11.11E-23", PrefixOp "-" $ NumLit "11.11E-23")
> ,("11.11e23", undefined) > ,("11.11e23", NumLit "11.11e23")
> ] > ]
@ -645,9 +653,12 @@ at this time.
> dateAndTimeLiterals :: TestItem > dateAndTimeLiterals :: TestItem
> dateAndTimeLiterals = Group "date and time literals" $ map (uncurry TestValueExpr) > dateAndTimeLiterals = Group "date and time literals" $ map (uncurry TestValueExpr)
> [("date 'date literal", undefined) > [("date 'date literal'"
> ,("time 'time literal", undefined) > ,TypedLit (TypeName "date") "date literal")
> ,("timestamp 'timestamp literal'", undefined) > ,("time 'time literal'"
> ,TypedLit (TypeName "time") "time literal")
> ,("timestamp 'timestamp literal'"
> ,TypedLit (TypeName "timestamp") "timestamp literal")
> ] > ]
TODO: intervals + more date and time literals TODO: intervals + more date and time literals
@ -658,9 +669,9 @@ TODO: intervals + more date and time literals
> booleanLiterals :: TestItem > booleanLiterals :: TestItem
> booleanLiterals = Group "boolean literals" $ map (uncurry TestValueExpr) > booleanLiterals = Group "boolean literals" $ map (uncurry TestValueExpr)
> [("true", undefined) > [("true", Iden "true")
> ,("false", undefined) > ,("false", Iden "false")
> ,("unknown", undefined) > ,("unknown", Iden "unknown")
> ] > ]
so is unknown effectively an alias for null with a cast or is it so is unknown effectively an alias for null with a cast or is it