2015-07-31 23:04:18 +02:00
|
|
|
|
|
|
|
|
|
|
|
Test for the lexer
|
|
|
|
|
|
|
|
> module Language.SQL.SimpleSQL.LexerTests (lexerTests) where
|
|
|
|
|
|
|
|
> import Language.SQL.SimpleSQL.TestTypes
|
2016-02-15 19:20:24 +01:00
|
|
|
> import Language.SQL.SimpleSQL.Lex (Token(..),tokenListWillPrintAndLex)
|
2015-07-31 23:04:18 +02:00
|
|
|
> --import Debug.Trace
|
2016-02-15 19:20:24 +01:00
|
|
|
> --import Data.Char (isAlpha)
|
2016-02-13 19:28:12 +01:00
|
|
|
> import Data.List
|
2015-07-31 23:04:18 +02:00
|
|
|
|
2016-02-13 14:54:40 +01:00
|
|
|
> lexerTests :: TestItem
|
|
|
|
> lexerTests = Group "lexerTests" $
|
2016-02-13 15:31:20 +01:00
|
|
|
> [Group "lexer token tests" [ansiLexerTests
|
2016-02-15 19:20:24 +01:00
|
|
|
> ,postgresLexerTests
|
|
|
|
> ,sqlServerLexerTests
|
|
|
|
> ,oracleLexerTests
|
|
|
|
> ,odbcLexerTests]]
|
2016-02-13 14:54:40 +01:00
|
|
|
|
2016-02-12 12:09:58 +01:00
|
|
|
> ansiLexerTable :: [(String,[Token])]
|
|
|
|
> ansiLexerTable =
|
2015-07-31 23:04:18 +02:00
|
|
|
> -- single char symbols
|
|
|
|
> map (\s -> ([s],[Symbol [s]])) "+-^*/%~&|?<>[]=,;()"
|
|
|
|
> -- multi char symbols
|
|
|
|
> ++ map (\s -> (s,[Symbol s])) [">=","<=","!=","<>","||"]
|
|
|
|
> ++ (let idens = ["a", "_a", "test", "table", "Stuff", "STUFF"]
|
|
|
|
> -- simple identifiers
|
2016-02-12 13:13:47 +01:00
|
|
|
> in map (\i -> (i, [Identifier Nothing i])) idens
|
|
|
|
> ++ map (\i -> ("\"" ++ i ++ "\"", [Identifier (Just ("\"","\"")) i])) idens
|
2015-07-31 23:04:18 +02:00
|
|
|
> -- todo: in order to make lex . pretty id, need to
|
|
|
|
> -- preserve the case of the u
|
2016-02-12 13:13:47 +01:00
|
|
|
> ++ map (\i -> ("u&\"" ++ i ++ "\"", [Identifier (Just ("u&\"","\"")) i])) idens
|
2015-07-31 23:04:18 +02:00
|
|
|
> -- host param
|
|
|
|
> ++ map (\i -> (':':i, [HostParam i])) idens
|
|
|
|
> )
|
|
|
|
> -- quoted identifiers with embedded double quotes
|
2016-02-13 14:54:40 +01:00
|
|
|
> -- the lexer doesn't unescape the quotes
|
|
|
|
> ++ [("\"normal \"\" iden\"", [Identifier (Just ("\"","\"")) "normal \"\" iden"])]
|
2015-07-31 23:04:18 +02:00
|
|
|
> -- strings
|
2016-02-13 14:54:40 +01:00
|
|
|
> -- the lexer doesn't apply escapes at all
|
2016-02-12 12:09:58 +01:00
|
|
|
> ++ [("'string'", [SqlString "'" "'" "string"])
|
2016-02-13 14:54:40 +01:00
|
|
|
> ,("'normal '' quote'", [SqlString "'" "'" "normal '' quote"])
|
|
|
|
> ,("'normalendquote '''", [SqlString "'" "'" "normalendquote ''"])]
|
2015-07-31 23:04:18 +02:00
|
|
|
> -- csstrings
|
2016-02-12 12:09:58 +01:00
|
|
|
> ++ map (\c -> (c ++ "'test'", [SqlString (c ++ "'") "'" "test"]))
|
2015-07-31 23:04:18 +02:00
|
|
|
> ["n", "N","b", "B","x", "X", "u&"]
|
|
|
|
> -- numbers
|
|
|
|
> ++ [("10", [SqlNumber "10"])
|
|
|
|
> ,(".1", [SqlNumber ".1"])
|
|
|
|
> ,("5e3", [SqlNumber "5e3"])
|
|
|
|
> ,("5e+3", [SqlNumber "5e+3"])
|
|
|
|
> ,("5e-3", [SqlNumber "5e-3"])
|
|
|
|
> ,("10.2", [SqlNumber "10.2"])
|
|
|
|
> ,("10.2e7", [SqlNumber "10.2e7"])]
|
|
|
|
> -- whitespace
|
|
|
|
> ++ concat [[([a],[Whitespace [a]])
|
|
|
|
> ,([a,b], [Whitespace [a,b]])]
|
|
|
|
> | a <- " \n\t", b <- " \n\t"]
|
|
|
|
> -- line comment
|
|
|
|
> ++ map (\c -> (c, [LineComment c]))
|
2015-08-02 14:58:09 +02:00
|
|
|
> ["--", "-- ", "-- this is a comment", "-- line com\n"]
|
2015-07-31 23:04:18 +02:00
|
|
|
> -- block comment
|
|
|
|
> ++ map (\c -> (c, [BlockComment c]))
|
|
|
|
> ["/**/", "/* */","/* this is a comment */"
|
2015-08-01 12:22:07 +02:00
|
|
|
> ,"/* this *is/ a comment */"
|
2015-07-31 23:04:18 +02:00
|
|
|
> ]
|
|
|
|
|
2016-02-12 12:09:58 +01:00
|
|
|
> ansiLexerTests :: TestItem
|
|
|
|
> ansiLexerTests = Group "ansiLexerTests" $
|
2016-02-15 19:31:06 +01:00
|
|
|
> [Group "ansi lexer token tests" $ [LexTest ansi2011 s t | (s,t) <- ansiLexerTable]
|
2016-02-12 12:09:58 +01:00
|
|
|
> ,Group "ansi generated combination lexer tests" $
|
2016-02-15 19:31:06 +01:00
|
|
|
> [ LexTest ansi2011 (s ++ s1) (t ++ t1)
|
2016-02-12 12:09:58 +01:00
|
|
|
> | (s,t) <- ansiLexerTable
|
|
|
|
> , (s1,t1) <- ansiLexerTable
|
2016-02-15 19:20:24 +01:00
|
|
|
> , tokenListWillPrintAndLex ansi2011 $ t ++ t1
|
2015-07-31 23:04:18 +02:00
|
|
|
|
|
|
|
> ]
|
2016-02-15 19:31:06 +01:00
|
|
|
> ,Group "ansiadhoclexertests" $
|
|
|
|
> map (uncurry $ LexTest ansi2011)
|
2015-07-31 23:04:18 +02:00
|
|
|
> [("", [])
|
2016-02-12 13:13:47 +01:00
|
|
|
> ,("-- line com\nstuff", [LineComment "-- line com\n",Identifier Nothing "stuff"])
|
2016-02-15 19:31:06 +01:00
|
|
|
> ] ++
|
|
|
|
> [-- want to make sure this gives a parse error
|
|
|
|
> LexFails ansi2011 "*/"
|
|
|
|
> -- combinations of pipes: make sure they fail because they could be
|
|
|
|
> -- ambiguous and it is really unclear when they are or not, and
|
|
|
|
> -- what the result is even when they are not ambiguous
|
|
|
|
> ,LexFails ansi2011 "|||"
|
|
|
|
> ,LexFails ansi2011 "||||"
|
|
|
|
> ,LexFails ansi2011 "|||||"
|
|
|
|
> -- another user experience thing: make sure extra trailing
|
|
|
|
> -- number chars are rejected rather than attempting to parse
|
|
|
|
> -- if the user means to write something that is rejected by this code,
|
|
|
|
> -- then they can use whitespace to make it clear and then it will parse
|
|
|
|
> ,LexFails ansi2011 "12e3e4"
|
|
|
|
> ,LexFails ansi2011 "12e3e4"
|
|
|
|
> ,LexFails ansi2011 "12e3e4"
|
|
|
|
> ,LexFails ansi2011 "12e3.4"
|
|
|
|
> ,LexFails ansi2011 "12.4.5"
|
|
|
|
> ,LexFails ansi2011 "12.4e5.6"
|
|
|
|
> ,LexFails ansi2011 "12.4e5e7"]
|
2015-08-15 18:04:29 +02:00
|
|
|
> ]
|
2015-07-31 23:04:18 +02:00
|
|
|
|
2016-02-13 14:54:40 +01:00
|
|
|
todo: lexing tests
|
|
|
|
do quickcheck testing:
|
|
|
|
can try to generate valid tokens then check they parse
|
|
|
|
|
|
|
|
same as above: can also try to pair tokens, create an accurate
|
|
|
|
function to say which ones can appear adjacent, and test
|
|
|
|
|
|
|
|
I think this plus the explicit lists of tokens like above which do
|
|
|
|
basic sanity + explicit edge casts will provide a high level of
|
|
|
|
assurance.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
> postgresLexerTable :: [(String,[Token])]
|
|
|
|
> postgresLexerTable =
|
|
|
|
> -- single char symbols
|
2016-02-13 15:31:20 +01:00
|
|
|
> map (\s -> ([s],[Symbol [s]])) "+-^*/%~&|?<>[]=,;():"
|
2016-02-13 14:54:40 +01:00
|
|
|
> -- multi char symbols
|
2016-02-13 15:31:20 +01:00
|
|
|
> ++ map (\s -> (s,[Symbol s])) [">=","<=","!=","<>","||", "::","..",":="]
|
2016-02-13 19:28:12 +01:00
|
|
|
> -- generic symbols
|
|
|
|
|
|
|
|
An operator name is a sequence of up to NAMEDATALEN-1 (63 by default) characters from the following list:
|
|
|
|
|
|
|
|
+ - * / < > = ~ ! @ # % ^ & | ` ?
|
|
|
|
|
|
|
|
There are a few restrictions on operator names, however:
|
|
|
|
-- and /* cannot appear anywhere in an operator name, since they will be taken as the start of a comment.
|
|
|
|
|
|
|
|
A multiple-character operator name cannot end in + or -, unless the name also contains at least one of these characters:
|
|
|
|
|
|
|
|
~ ! @ # % ^ & | ` ?
|
|
|
|
|
|
|
|
todo: 'negative' tests
|
|
|
|
symbol then --
|
|
|
|
symbol then /*
|
|
|
|
operators without one of the exception chars
|
|
|
|
followed by + or - without whitespace
|
|
|
|
|
|
|
|
also: do the testing for the ansi compatibility special cases
|
|
|
|
|
2016-02-15 19:20:24 +01:00
|
|
|
> ++ [ (x, [Symbol x]) | x <- someValidPostgresOperators 2]
|
|
|
|
|
|
|
|
|
2016-02-13 14:54:40 +01:00
|
|
|
> ++ (let idens = ["a", "_a", "test", "table", "Stuff", "STUFF"]
|
|
|
|
> -- simple identifiers
|
|
|
|
> in map (\i -> (i, [Identifier Nothing i])) idens
|
|
|
|
> ++ map (\i -> ("\"" ++ i ++ "\"", [Identifier (Just ("\"","\"")) i])) idens
|
|
|
|
> -- todo: in order to make lex . pretty id, need to
|
|
|
|
> -- preserve the case of the u
|
|
|
|
> ++ map (\i -> ("u&\"" ++ i ++ "\"", [Identifier (Just ("u&\"","\"")) i])) idens
|
|
|
|
> -- host param
|
|
|
|
> ++ map (\i -> (':':i, [HostParam i])) idens
|
|
|
|
> )
|
|
|
|
> -- positional var
|
2016-02-13 15:31:20 +01:00
|
|
|
> ++ [("$1", [PositionalArg 1])]
|
2016-02-13 14:54:40 +01:00
|
|
|
> -- quoted identifiers with embedded double quotes
|
2016-02-13 15:31:20 +01:00
|
|
|
> ++ [("\"normal \"\" iden\"", [Identifier (Just ("\"","\"")) "normal \"\" iden"])]
|
2016-02-13 14:54:40 +01:00
|
|
|
> -- strings
|
|
|
|
> ++ [("'string'", [SqlString "'" "'" "string"])
|
|
|
|
> ,("'normal '' quote'", [SqlString "'" "'" "normal '' quote"])
|
2016-02-13 15:31:20 +01:00
|
|
|
> ,("'normalendquote '''", [SqlString "'" "'" "normalendquote ''"])
|
|
|
|
> ,("e'this '' quote'", [SqlString "e'" "'" "this '' quote"])
|
|
|
|
> ,("e'this \\' quote'", [SqlString "e'" "'" "this \\' quote"])
|
2016-02-13 16:07:27 +01:00
|
|
|
> ,("'not this \\' quote", [SqlString "'" "'" "not this \\"
|
|
|
|
> ,Whitespace " "
|
|
|
|
> ,Identifier Nothing "quote"])
|
|
|
|
> ,("$$ string 1 $$", [SqlString "$$" "$$" " string 1 "])
|
|
|
|
> ,("$$ string $ 2 $$", [SqlString "$$" "$$" " string $ 2 "])
|
|
|
|
> ,("$a$ $$string 3$$ $a$", [SqlString "$a$" "$a$" " $$string 3$$ "])
|
2016-02-13 14:54:40 +01:00
|
|
|
> ]
|
|
|
|
> -- csstrings
|
|
|
|
> ++ map (\c -> (c ++ "'test'", [SqlString (c ++ "'") "'" "test"]))
|
|
|
|
> ["n", "N","b", "B","x", "X", "u&", "e", "E"]
|
|
|
|
> -- numbers
|
|
|
|
> ++ [("10", [SqlNumber "10"])
|
|
|
|
> ,(".1", [SqlNumber ".1"])
|
|
|
|
> ,("5e3", [SqlNumber "5e3"])
|
|
|
|
> ,("5e+3", [SqlNumber "5e+3"])
|
|
|
|
> ,("5e-3", [SqlNumber "5e-3"])
|
|
|
|
> ,("10.2", [SqlNumber "10.2"])
|
|
|
|
> ,("10.2e7", [SqlNumber "10.2e7"])]
|
|
|
|
> -- whitespace
|
|
|
|
> ++ concat [[([a],[Whitespace [a]])
|
|
|
|
> ,([a,b], [Whitespace [a,b]])]
|
|
|
|
> | a <- " \n\t", b <- " \n\t"]
|
|
|
|
> -- line comment
|
|
|
|
> ++ map (\c -> (c, [LineComment c]))
|
|
|
|
> ["--", "-- ", "-- this is a comment", "-- line com\n"]
|
|
|
|
> -- block comment
|
|
|
|
> ++ map (\c -> (c, [BlockComment c]))
|
|
|
|
> ["/**/", "/* */","/* this is a comment */"
|
|
|
|
> ,"/* this *is/ a comment */"
|
|
|
|
> ]
|
2016-02-13 15:31:20 +01:00
|
|
|
|
2016-02-15 19:20:24 +01:00
|
|
|
> postgresExtraOperatorTable :: [(String,[Token])]
|
|
|
|
> postgresExtraOperatorTable =
|
|
|
|
> [ (x, [Symbol x]) | x <- someValidPostgresOperators 4]
|
|
|
|
|
|
|
|
|
2016-02-13 19:28:12 +01:00
|
|
|
> someValidPostgresOperators :: Int -> [String]
|
|
|
|
> someValidPostgresOperators l =
|
|
|
|
> [ x
|
|
|
|
> | n <- [1..l]
|
|
|
|
> , x <- combos "+-*/<>=~!@#%^&|`?" n
|
2016-02-15 19:31:06 +01:00
|
|
|
> , not ("--" `isInfixOf` x || "/*" `isInfixOf` x || "*/" `isInfixOf` x)
|
2016-02-13 19:28:12 +01:00
|
|
|
> , not (last x `elem` "+-")
|
|
|
|
> || or (map (`elem` x) "~!@#%^&|`?")
|
|
|
|
> ]
|
|
|
|
|
|
|
|
These are postgres operators, which if followed immediately by a + or
|
|
|
|
-, will lex as separate operators rather than one operator including
|
|
|
|
the + or -.
|
|
|
|
|
|
|
|
> somePostgresOpsWhichWontAddTrailingPlusMinus :: Int -> [String]
|
|
|
|
> somePostgresOpsWhichWontAddTrailingPlusMinus l =
|
|
|
|
> [ x
|
|
|
|
> | n <- [1..l]
|
|
|
|
> , x <- combos "+-*/<>=" n
|
2016-02-15 19:31:06 +01:00
|
|
|
> , not ("--" `isInfixOf` x || "/*" `isInfixOf` x || "*/" `isInfixOf` x)
|
2016-02-13 19:28:12 +01:00
|
|
|
> , not (last x `elem` "+-")
|
|
|
|
> ]
|
|
|
|
|
|
|
|
|
2016-02-13 15:31:20 +01:00
|
|
|
> postgresLexerTests :: TestItem
|
|
|
|
> postgresLexerTests = Group "postgresLexerTests" $
|
2016-02-13 19:28:12 +01:00
|
|
|
> [Group "postgres lexer token tests" $
|
2016-02-15 19:31:06 +01:00
|
|
|
> [LexTest postgres s t | (s,t) <- postgresLexerTable ++ postgresExtraOperatorTable]
|
2016-02-15 19:20:24 +01:00
|
|
|
> ,Group "postgres generated combination lexer tests" $
|
2016-02-15 19:31:06 +01:00
|
|
|
> [ LexTest postgres (s ++ s1) (t ++ t1)
|
2016-02-15 19:20:24 +01:00
|
|
|
> | (s,t) <- postgresLexerTable
|
|
|
|
> , (s1,t1) <- postgresLexerTable
|
|
|
|
> , tokenListWillPrintAndLex postgres $ t ++ t1
|
|
|
|
|
|
|
|
> ]
|
2016-02-15 19:31:06 +01:00
|
|
|
> ,Group "adhoc postgres lexertests" $
|
|
|
|
> [LexTest postgres s t
|
2016-02-13 19:38:49 +01:00
|
|
|
> | (s,t) <- edgeCaseCommentOps
|
|
|
|
> ++ edgeCasePlusMinusOps
|
|
|
|
> ++ edgeCasePlusMinusComments]
|
2016-02-15 19:31:06 +01:00
|
|
|
> ++
|
|
|
|
> -- need more tests for */ to make sure it is caught if it is in the middle of a
|
|
|
|
> -- sequence of symbol letters
|
|
|
|
> [LexFails postgres "*/"
|
|
|
|
> ,LexFails postgres "@*/"
|
|
|
|
> ,LexFails postgres "-*/"
|
|
|
|
> ,LexFails postgres "12e3e4"
|
|
|
|
> ,LexFails postgres "12e3e4"
|
|
|
|
> ,LexFails postgres "12e3e4"
|
|
|
|
> ,LexFails postgres "12e3.4"
|
|
|
|
> ,LexFails postgres "12.4.5"
|
|
|
|
> ,LexFails postgres "12.4e5.6"
|
|
|
|
> ,LexFails postgres "12.4e5e7"]
|
2016-02-13 15:31:20 +01:00
|
|
|
> ]
|
2016-02-13 19:28:12 +01:00
|
|
|
> where
|
2016-02-15 19:31:06 +01:00
|
|
|
> edgeCaseCommentOps =
|
|
|
|
> [ (x ++ "/*<test*/", [Symbol x, BlockComment "/*<test*/"])
|
|
|
|
> | x <- eccops
|
|
|
|
> , not (last x == '*')
|
|
|
|
> ] ++
|
|
|
|
> [ (x ++ "--<test", [Symbol x, LineComment "--<test"])
|
|
|
|
> | x <- eccops
|
2016-02-13 19:28:12 +01:00
|
|
|
> , not (last x == '-')
|
|
|
|
> ]
|
2016-02-15 19:31:06 +01:00
|
|
|
> eccops = someValidPostgresOperators 2
|
2016-02-13 19:28:12 +01:00
|
|
|
> edgeCasePlusMinusOps = concat
|
|
|
|
> [ [ (x ++ "+", [Symbol x, Symbol "+"])
|
|
|
|
> , (x ++ "-", [Symbol x, Symbol "-"]) ]
|
|
|
|
> | x <- somePostgresOpsWhichWontAddTrailingPlusMinus 2
|
|
|
|
> ]
|
2016-02-13 19:38:49 +01:00
|
|
|
> edgeCasePlusMinusComments =
|
|
|
|
> [("---", [LineComment "---"])
|
|
|
|
> ,("+--", [Symbol "+", LineComment "--"])
|
|
|
|
> ,("-/**/", [Symbol "-", BlockComment "/**/"])
|
|
|
|
> ,("+/**/", [Symbol "+", BlockComment "/**/"])
|
|
|
|
> ]
|
2016-02-13 19:28:12 +01:00
|
|
|
|
|
|
|
|
2016-02-15 19:20:24 +01:00
|
|
|
> sqlServerLexerTests :: TestItem
|
2016-02-15 19:31:06 +01:00
|
|
|
> sqlServerLexerTests = Group "sqlServerLexTests" $
|
|
|
|
> [ LexTest sqlserver s t | (s,t) <-
|
2016-02-15 19:32:26 +01:00
|
|
|
> [("@variable", [(PrefixedVariable '@' "variable")])
|
2016-02-15 19:20:24 +01:00
|
|
|
> --,("[quoted identifier]", [(Identifier (Just ("[", "]")) "variable")])
|
|
|
|
> ]]
|
|
|
|
|
|
|
|
> oracleLexerTests :: TestItem
|
2016-02-15 19:31:06 +01:00
|
|
|
> oracleLexerTests = Group "oracleLexTests" $
|
|
|
|
> [ LexTest oracle s t | (s,t) <-
|
2016-02-15 19:32:26 +01:00
|
|
|
> [("#variable", [(PrefixedVariable '#' "variable")])
|
2016-02-15 19:20:24 +01:00
|
|
|
> ]
|
|
|
|
> ]
|
|
|
|
|
|
|
|
> odbcLexerTests :: TestItem
|
2016-02-15 19:31:06 +01:00
|
|
|
> odbcLexerTests = Group "odbcLexTests" $
|
|
|
|
> [ LexTest sqlserver {- {odbc = True} -} s t | (s,t) <-
|
2016-02-15 19:20:24 +01:00
|
|
|
> [--("{}", [Symbol "{", Symbol "}"])
|
|
|
|
> ]
|
|
|
|
> ]
|
|
|
|
|
2016-02-13 19:28:12 +01:00
|
|
|
> combos :: [a] -> Int -> [[a]]
|
|
|
|
> combos _ 0 = [[]]
|
|
|
|
> combos l n = [ x:tl | x <- l, tl <- combos l (n - 1) ]
|
2016-02-15 19:20:24 +01:00
|
|
|
|
|
|
|
figure out a way to do quickcheck testing:
|
|
|
|
1. generate valid tokens and check they parse
|
|
|
|
|
|
|
|
2. combine two generated tokens together for the combo testing
|
|
|
|
|
|
|
|
this especially will work much better for the postgresql extensible
|
|
|
|
operator tests which doing exhaustively takes ages and doesn't bring
|
|
|
|
much benefit over testing a few using quickcheck.
|