Data types to represent different dialect options
> {-# LANGUAGE DeriveDataTypeable #-}
> module Language.SQL.SimpleSQL.Dialect
> (Dialect(..)
> ,ansi2011
> ,mysql
> ,postgres
> ,oracle
> ,sqlserver
> ) where
> import Data.Data
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
>
> data Dialect = Dialect
> {
> diKeywords :: [String]
>
> ,diIdentifierKeywords :: [String]
>
> ,diAppKeywords :: [String]
>
>
> ,diSpecialTypeNames :: [String]
>
> ,diFetchFirst :: Bool
>
>
> ,diLimit :: Bool
>
> ,diOdbc :: Bool
>
> ,diBackquotedIden :: Bool
>
> ,diSquareBracketQuotedIden :: Bool
>
> ,diAtIdentifier :: Bool
>
> ,diHashIdentifier :: Bool
>
> ,diPositionalArg :: Bool
>
> ,diDollarString :: Bool
>
> ,diEString :: Bool
>
> ,diPostgresSymbols :: Bool
>
> ,diSqlServerSymbols :: Bool
> }
> deriving (Eq,Show,Read,Data,Typeable)
>
> ansi2011 :: Dialect
> ansi2011 = Dialect {diKeywords = ansi2011ReservedKeywords
> ,diIdentifierKeywords = []
> ,diAppKeywords = ["set"]
> ,diSpecialTypeNames = ansi2011TypeNames
> ,diFetchFirst = True
> ,diLimit = False
> ,diOdbc = False
> ,diBackquotedIden = False
> ,diSquareBracketQuotedIden = False
> ,diAtIdentifier = False
> ,diHashIdentifier = False
> ,diPositionalArg = False
> ,diDollarString = False
> ,diEString = False
> ,diPostgresSymbols = False
> ,diSqlServerSymbols = False
> }
>
> mysql :: Dialect
> mysql = addLimit ansi2011 {diFetchFirst = False
> ,diBackquotedIden = True
> }
>
> postgres :: Dialect
> postgres = addLimit ansi2011 {diPositionalArg = True
> ,diDollarString = True
> ,diEString = True
> ,diPostgresSymbols = True}
>
> oracle :: Dialect
> oracle = ansi2011
>
> sqlserver :: Dialect
> sqlserver = ansi2011 {diSquareBracketQuotedIden = True
> ,diAtIdentifier = True
> ,diHashIdentifier = True
> ,diSqlServerSymbols = True }
> addLimit :: Dialect -> Dialect
> addLimit d = d {diKeywords = "limit": diKeywords d
> ,diLimit = True}
The keyword handling is quite strong - an alternative way to do it
would be to have as few keywords as possible, and only require them
to be quoted when this is needed to resolve a parsing ambiguity.
I don't think this is a good idea for genuine keywords (it probably is
for all the 'fake' keywords in the standard - things which are
essentially function names, or predefined variable names, or type
names, eetc.).
1. working out exactly when each keyword would need to be quoted is
quite error prone, and might change as the parser implementation is
maintained - which would be terrible for users
2. it's not user friendly for the user to deal with a whole load of
special cases - either something is a keyword, then you know you must
always quote it, or it isn't, then you know you never need to quote
it
3. I think not having exceptions makes for better error messages for
the user, and a better sql code maintenance experience.
This might not match actual existing SQL products that well, some of
which I think have idiosyncratic rules about when a keyword must be
quoted. If you want to match one of these dialects exactly with this
parser, I think it will be a lot of work.
> ansi2011ReservedKeywords :: [String]
> ansi2011ReservedKeywords =
> [
> "all"
> ,"allocate"
> ,"alter"
> ,"and"
>
> ,"are"
> ,"array"
>
>
> ,"as"
> ,"asensitive"
> ,"asymmetric"
> ,"at"
> ,"atomic"
> ,"authorization"
>
> ,"begin"
>
>
> ,"between"
> ,"bigint"
> ,"binary"
> ,"blob"
> ,"boolean"
> ,"both"
> ,"by"
> ,"call"
> ,"called"
>
> ,"cascaded"
> ,"case"
> ,"cast"
>
>
> ,"char"
>
> ,"character"
>
> ,"check"
> ,"clob"
> ,"close"
>
> ,"collate"
>
> ,"column"
> ,"commit"
> ,"condition"
> ,"connect"
> ,"constraint"
>
>
>
> ,"corresponding"
>
>
>
> ,"create"
> ,"cross"
> ,"cube"
>
> ,"current"
>
>
>
>
>
>
>
>
>
>
>
> ,"cursor"
> ,"cycle"
> ,"date"
>
> ,"deallocate"
> ,"dec"
> ,"decimal"
> ,"declare"
>
> ,"delete"
>
> ,"deref"
> ,"describe"
> ,"deterministic"
> ,"disconnect"
> ,"distinct"
> ,"double"
> ,"drop"
> ,"dynamic"
> ,"each"
>
> ,"else"
> ,"end"
>
>
> ,"end-exec"
> ,"equals"
> ,"escape"
>
> ,"except"
> ,"exec"
> ,"execute"
> ,"exists"
> ,"exp"
> ,"external"
> ,"extract"
>
> ,"fetch"
> ,"filter"
>
> ,"float"
>
> ,"for"
> ,"foreign"
>
> ,"free"
> ,"from"
> ,"full"
> ,"function"
>
> ,"get"
> ,"global"
> ,"grant"
> ,"group"
>
> ,"groups"
> ,"having"
> ,"hold"
>
> ,"identity"
> ,"in"
> ,"indicator"
> ,"inner"
> ,"inout"
> ,"insensitive"
> ,"insert"
> ,"int"
> ,"integer"
> ,"intersect"
>
> ,"interval"
> ,"into"
> ,"is"
> ,"join"
>
> ,"language"
> ,"large"
>
> ,"lateral"
>
> ,"leading"
> ,"left"
> ,"like"
> ,"like_regex"
>
> ,"local"
> ,"localtime"
> ,"localtimestamp"
>
> ,"match"
>
> ,"member"
> ,"merge"
> ,"method"
>
>
>
> ,"modifies"
>
>
> ,"multiset"
> ,"national"
> ,"natural"
> ,"nchar"
> ,"nclob"
> ,"new"
> ,"no"
> ,"none"
> ,"normalize"
> ,"not"
>
> ,"ntile"
>
>
> ,"numeric"
> ,"octet_length"
> ,"occurrences_regex"
> ,"of"
> ,"offset"
> ,"old"
> ,"on"
> ,"only"
> ,"open"
> ,"or"
> ,"order"
> ,"out"
> ,"outer"
> ,"over"
> ,"overlaps"
> ,"overlay"
> ,"parameter"
> ,"partition"
> ,"percent"
>
>
>
> ,"period"
> ,"portion"
> ,"position"
> ,"position_regex"
>
> ,"precedes"
> ,"precision"
> ,"prepare"
> ,"primary"
> ,"procedure"
> ,"range"
>
> ,"reads"
> ,"real"
> ,"recursive"
> ,"ref"
> ,"references"
> ,"referencing"
>
>
>
>
>
>
>
>
>
> ,"release"
> ,"result"
> ,"return"
> ,"returns"
> ,"revoke"
> ,"right"
> ,"rollback"
> ,"rollup"
>
>
> ,"rows"
> ,"savepoint"
> ,"scope"
> ,"scroll"
> ,"search"
>
> ,"select"
> ,"sensitive"
>
> ,"set"
> ,"similar"
> ,"smallint"
>
> ,"specific"
> ,"specifictype"
> ,"sql"
> ,"sqlexception"
> ,"sqlstate"
> ,"sqlwarning"
>
>
> ,"static"
>
>
> ,"submultiset"
>
> ,"substring_regex"
> ,"succeeds"
>
> ,"symmetric"
> ,"system"
>
>
> ,"table"
> ,"tablesample"
> ,"then"
> ,"time"
> ,"timestamp"
> ,"timezone_hour"
> ,"timezone_minute"
> ,"to"
> ,"trailing"
> ,"translate"
> ,"translate_regex"
> ,"translation"
> ,"treat"
> ,"trigger"
> ,"truncate"
>
>
>
> ,"uescape"
> ,"union"
> ,"unique"
>
> ,"unnest"
> ,"update"
> ,"upper"
>
> ,"using"
>
> ,"values"
> ,"value_of"
>
>
> ,"varbinary"
> ,"varchar"
> ,"varying"
> ,"versioning"
> ,"when"
> ,"whenever"
> ,"where"
>
> ,"window"
> ,"with"
> ,"within"
> ,"without"
>
> ]
> ansi2011TypeNames :: [String]
> ansi2011TypeNames =
> ["double precision"
> ,"character varying"
> ,"char varying"
> ,"character large object"
> ,"char large object"
> ,"national character"
> ,"national char"
> ,"national character varying"
> ,"national char varying"
> ,"national character large object"
> ,"nchar large object"
> ,"nchar varying"
> ,"bit varying"
> ,"binary large object"
> ,"binary varying"
>
> ,"array"
> ,"bigint"
> ,"binary"
> ,"blob"
> ,"boolean"
> ,"char"
> ,"character"
> ,"clob"
> ,"date"
> ,"dec"
> ,"decimal"
> ,"double"
> ,"float"
> ,"int"
> ,"integer"
> ,"nchar"
> ,"nclob"
> ,"numeric"
> ,"real"
> ,"smallint"
> ,"time"
> ,"timestamp"
> ,"varchar"
> ,"varbinary"
> ]