1
Fork 0

refactor dialect into a non enum and separate to own file

This commit is contained in:
Jake Wheat 2016-02-12 12:51:06 +02:00
parent 2b73907119
commit 1b4eefc431
22 changed files with 304 additions and 252 deletions

View file

@ -0,0 +1,51 @@
Data types to represent different dialect options
> {-# LANGUAGE DeriveDataTypeable #-}
> module Language.SQL.SimpleSQL.Dialect
> (SyntaxFlavour(..)
> ,Dialect(..)
> ,ansi2011
> ,mysql
> ,postgres
> ,oracle
> ,sqlserver
> ) where
> import Data.Data
hack for now, later will expand to flags on a feature by feature basis
> data SyntaxFlavour = ANSI2011
> | MySQL
> | Postgres
> | Oracle
> | SQLServer
> deriving (Eq,Show,Read,Data,Typeable)
> -- | Used to set the dialect used for parsing and pretty printing,
> -- very unfinished at the moment.
> data Dialect = Dialect {diSyntaxFlavour :: SyntaxFlavour}
> deriving (Eq,Show,Read,Data,Typeable)
> -- | ansi sql 2011 dialect
> ansi2011 :: Dialect
> ansi2011 = Dialect ANSI2011
> -- | mysql dialect
> mysql :: Dialect
> mysql = Dialect MySQL
> -- | postgresql dialect
> postgres :: Dialect
> postgres = Dialect Postgres
> -- | oracle dialect
> oracle :: Dialect
> oracle = Dialect Postgres
> -- | microsoft sql server dialect
> sqlserver :: Dialect
> sqlserver = Dialect Postgres

View file

@ -18,7 +18,7 @@ parsec
> ,ParseError(..)
> ,Dialect(..)) where
> import Language.SQL.SimpleSQL.Syntax (Dialect(..))
> import Language.SQL.SimpleSQL.Dialect
> import Text.Parsec (option,string,manyTill,anyChar
> ,try,string,many1,oneOf,digit,(<|>),choice,char,eof
@ -200,7 +200,7 @@ u&"unicode quoted identifier"
> ,return $ concat [t,s]]
> -- mysql can quote identifiers with `
> mySqlQIden = do
> guard (d == MySQL)
> guard (diSyntaxFlavour d == MySQL)
> char '`' *> takeWhile1 (/='`') <* char '`'
This parses a valid identifier without quotes.

View file

@ -202,6 +202,7 @@ fixing them in the syntax but leaving them till the semantic checking
> import Language.SQL.SimpleSQL.Syntax
> import Language.SQL.SimpleSQL.Combinators
> import Language.SQL.SimpleSQL.Errors
> import Language.SQL.SimpleSQL.Dialect
> import qualified Language.SQL.SimpleSQL.Lex as L
> import Data.Maybe
> import Text.Parsec.String (GenParser)
@ -1359,7 +1360,7 @@ allows offset and fetch in either order
> fetch :: Parser ValueExpr
> fetch = fetchFirst <|> limit
> where
> fetchFirst = guardDialect [SQL2011]
> fetchFirst = guardDialect [ANSI2011]
> *> fs *> valueExpr <* ro
> fs = makeKeywordTree ["fetch first", "fetch next"]
> ro = makeKeywordTree ["rows only", "row only"]
@ -2107,7 +2108,7 @@ keywords (I'm not sure what exactly being an unreserved keyword
means).
> reservedWord :: Dialect -> [String]
> reservedWord SQL2011 =
> reservedWord d | diSyntaxFlavour d == ANSI2011 =
> ["abs"
> --,"all"
> ,"allocate"
@ -2435,9 +2436,9 @@ means).
> ]
TODO: create this list properly
move this list into the dialect data type
> reservedWord MySQL = reservedWord SQL2011 ++ ["limit"]
> reservedWord _ = reservedWord ansi2011 ++ ["limit"]
-----------
@ -2450,10 +2451,10 @@ different parsers can be used for different dialects
> type Parser = GenParser Token ParseState
> guardDialect :: [Dialect] -> Parser ()
> guardDialect :: [SyntaxFlavour] -> Parser ()
> guardDialect ds = do
> d <- getState
> guard (d `elem` ds)
> guard (diSyntaxFlavour d `elem` ds)
TODO: the ParseState and the Dialect argument should be turned into a
flags struct. Part (or all?) of this struct is the dialect

View file

@ -13,6 +13,7 @@ TODO: there should be more comments in this file, especially the bits
which have been changed to try to improve the layout of the output.
> import Language.SQL.SimpleSQL.Syntax
> import Language.SQL.SimpleSQL.Dialect
> import Text.PrettyPrint (render, vcat, text, (<>), (<+>), empty, parens,
> nest, Doc, punctuate, comma, sep, quotes,
> doubleQuotes, brackets,hcat)
@ -336,7 +337,7 @@ which have been changed to try to improve the layout of the output.
> ]
> where
> fetchFirst =
> me (\e -> if dia == MySQL
> me (\e -> if diSyntaxFlavour dia == MySQL
> then text "limit" <+> valueExpr dia e
> else text "fetch first" <+> valueExpr dia e
> <+> text "rows only") fe

View file

@ -55,13 +55,19 @@
> ,PrivilegeAction(..)
> ,AdminOptionFor(..)
> ,GrantOptionFor(..)
> -- * Dialect
> ,Dialect(..)
> -- * Dialects
> ,Dialect
> ,ansi2011
> ,mysql
> ,postgres
> ,oracle
> ,sqlserver
> -- * Comment
> ,Comment(..)
> ) where
> import Data.Data
> import Language.SQL.SimpleSQL.Dialect
> -- | Represents a value expression. This is used for the expressions
> -- in select lists. It is also used for expressions in where, group
@ -702,15 +708,6 @@ I'm not sure if this is valid syntax or not.
> | PrivExecute
> deriving (Eq,Show,Read,Data,Typeable)
--------------------------
> -- | Used to set the dialect used for parsing and pretty printing,
> -- very unfinished at the moment.
> data Dialect = SQL2011
> | MySQL
> deriving (Eq,Show,Read,Data,Typeable)
> -- | Comment. Useful when generating SQL code programmatically. The
> -- parser doesn't produce these.
> data Comment = BlockComment String