{- This module was generated from data in the Kate syntax highlighting file sql-postgresql.xml, version 1.10, by Shane Wright (me@shanewright.co.uk) -} module Text.Highlighting.Kate.Syntax.SqlPostgresql ( highlight, parseExpression, syntaxName, syntaxExtensions ) where import Text.Highlighting.Kate.Definitions import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec import Control.Monad (when) import Data.Map (fromList) import Data.Maybe (fromMaybe, maybeToList) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "SQL (PostgreSQL)" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.sql;*.SQL" -- | Highlight source code using this syntax definition. highlight :: String -> Either String [SourceLine] highlight input = case runParser parseSource startingState "source" input of Left err -> Left $ show err Right result -> Right result -- | Parse an expression using appropriate local context. parseExpression :: GenParser Char SyntaxState LabeledSource parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "SQL (PostgreSQL)" } context <- currentContext <|> (pushContext "Normal" >> currentContext) result <- parseRules context updateState $ \st -> st { synStLanguage = oldLang } return result parseSource = do lineContents <- lookAhead wholeLine updateState $ \st -> st { synStCurrentLine = lineContents } result <- manyTill parseSourceLine eof return $ map normalizeHighlighting result startingState = SyntaxState {synStContexts = fromList [("SQL (PostgreSQL)",["Normal"])], synStLanguage = "SQL (PostgreSQL)", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = False, synStKeywordCaseSensitive = False, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do lookAhead $ newline <|> (eof >> return '\n') context <- currentContext case context of "Normal" -> return () >> pHandleEndLine "CreateFunction" -> return () >> pHandleEndLine "FunctionBody" -> return () >> pHandleEndLine "MultiLineString" -> return () >> pHandleEndLine "String" -> return () >> pHandleEndLine "SingleLineComment" -> (popContext) >> pEndLine "MultiLineComment" -> return () >> pHandleEndLine "Identifier" -> (popContext) >> pEndLine "Preprocessor" -> (popContext) >> pEndLine _ -> pHandleEndLine withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" let labs = attr : maybeToList (lookup attr styles) st <- getState let oldCharsParsed = synStCharsParsedInLine st let prevchar = if null txt then '\n' else last txt updateState $ \st -> st { synStCharsParsedInLine = oldCharsParsed + length txt, synStPrevChar = prevchar } return (labs, txt) styles = [("Keyword","kw"),("Function","fu"),("Data Type","dt"),("Decimal","dv"),("Float","fl"),("String","st"),("String Char","ch"),("Comment","co"),("Identifier","ot"),("Symbol","ch"),("Preprocessor","ot")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) list_keywords = Set.fromList $ words $ "abort access action add admin after aggregate alias all allocate alter analyse analyze any are as asc asensitive assertion assignment asymmetric at atomic authorization backward before begin between binary both breadth by c cache call called cardinality cascade cascaded case cast catalog catalog_name chain char_length character_length character_set_catalog character_set_name character_set_schema characteristics check checked checkpoint class class_origin clob close cluster coalesce cobol collate collation collation_catalog collation_name collation_schema column column_name command_function command_function_code comment commit committed completion condition_number connect connection connection_name constraint constraint_catalog constraint_name constraint_schema constraints constructor contains continue convert copy corresponding count create createdb createuser cross cube current current_date current_path current_role current_time current_timestamp current_user cursor cursor_name cycle data database date datetime_interval_code datetime_interval_precision day deallocate dec decimal declare default deferrable deferred defined definer delete delimiters depth deref desc describe descriptor destroy destructor deterministic diagnostics dictionary disconnect dispatch distinct do domain double drop dynamic dynamic_function dynamic_function_code each else encoding encrypted end end-exec equals escape every except exception exclusive exec execute existing exists explain external fetch final first for force foreign fortran forward found free freeze from full function g general generated get global go goto grant granted group grouping handler having hierarchy hold host hour identity ignore ilike immediate immutable implementation in increment index indicator infix inherits initialize initially inner inout input insensitive insert instance instantiable instead intersect interval into invoker is isnull isolation iterate join k key key_member key_type lancompiler language large last lateral leading left length less level like limit listen load local localtime localtimestamp location locator lock lower m map match max maxvalue message_length message_octet_length message_text method min minute minvalue mod mode modifies modify module month more move mumps name names national natural new next no nocreatedb nocreateuser none not nothing notify notnull null nullable nullif number numeric object octet_length of off offset oids old on only open operation operator option options order ordinality out outer output overlaps overlay overriding owner pad parameter parameter_mode parameter_name parameter_ordinal_position parameter_specific_catalog parameter_specific_name parameter_specific_schema parameters partial pascal password path pendant pli position postfix precision prefix preorder prepare preserve primary prior privileges procedural procedure public read reads real recursive ref references referencing reindex relative rename repeatable replace reset restrict result return returned_length returned_octet_length returned_sqlstate returns revoke right role rollback rollup routine routine_catalog routine_name routine_schema row row_count rows rule savepoint scale schema schema_name scope scroll search second section security select self sensitive sequence serializable server_name session session_user set setof sets share show similar simple size some source space specific specific_name specifictype sql sqlcode sqlerror sqlexception sqlstate sqlwarning stable start state statement static statistics stdin stdout structure style subclass_origin sublist substring sum symmetric sysid system system_user table table_name temp template temporary terminate than then timezone_hour timezone_minute to toast trailing transaction transaction_active transactions_committed transactions_rolled_back transform transforms translate translation treat trigger trigger_catalog trigger_name trigger_schema trim truncate trusted type uncommitted under unencrypted union unique unknown unlisten unnamed unnest until update upper usage user user_defined_type_catalog user_defined_type_name user_defined_type_schema using vacuum valid value values variable varying verbose version view volatile when whenever where with without work write year zone false true" list_operators = Set.fromList $ words $ "+ - * / || |/ ||/ ! !! @ & | # << >> % ^ = != <> < <= > >= ~ ~* !~ !~* ^= := => ** .. and or not ## && &< &> <-> <^ >^ ?# ?- ?-| @-@ ?| ?|| @@ ~= <<= >>=" list_functions = Set.fromList $ words $ "abs cbrt ceil degrees exp floor ln log mod pi pow radians random round sign sqrt trunc acos asin atan atan2 cos cot sin tan bit_length char_length character_length lower octet_length position substring trim upper ascii btrim chr convert initcap length lpad ltrim pg_client_encoding repeat rpad rtrim strpos substr to_ascii translate encode decode to_char to_date to_timestamp to_number age date_part date_trunc extract isfinite now timeofday timestamp extract area box center diameter height isclosed isopen pclose npoint popen radius width box circle lseg path point polygon broadcast host masklen set_masklen netmask network abbrev nextval currval setval coalesce nullif has_table_privilege pg_get_viewdef pg_get_ruledef pg_get_indexdef pg_get_userbyid obj_description col_description avg count max min stddev sum variance" list_types = Set.fromList $ words $ "lztext bigint int2 int8 bigserial serial8 bit bit varying varbit boolean bool box bytea character char character varying varchar cidr circle date double precision float8 inet integer int int4 interval line lseg macaddr money numeric decimal oid path point polygon real smallint serial text time timetz timestamp timestamptz timestamp with timezone" regex_'25bulk'5fexceptions'5cb = compileRegex "%bulk_exceptions\\b" regex_'25bulk'5frowcount'5cb = compileRegex "%bulk_rowcount\\b" regex_'25found'5cb = compileRegex "%found\\b" regex_'25isopen'5cb = compileRegex "%isopen\\b" regex_'25notfound'5cb = compileRegex "%notfound\\b" regex_'25rowcount'5cb = compileRegex "%rowcount\\b" regex_'25rowtype'5cb = compileRegex "%rowtype\\b" regex_'25type'5cb = compileRegex "%type\\b" regex_rem'5cb = compileRegex "rem\\b" regex_'2f'24 = compileRegex "/$" regex_'40'40'3f'5b'5e'40_'5ct'5cr'5cn'5d = compileRegex "@@?[^@ \\t\\r\\n]" defaultAttributes = [("Normal","Normal Text"),("CreateFunction","Normal Text"),("FunctionBody","Normal Text"),("MultiLineString","String"),("String","String"),("SingleLineComment","Comment"),("MultiLineComment","Comment"),("Identifier","Identifier"),("Preprocessor","Preprocessor")] parseRules "Normal" = do (attr, result) <- (((pString False "CREATE FUNCTION" >>= withAttribute "Keyword") >>~ pushContext "CreateFunction") <|> ((pKeyword " \n\t(),;[]{}\\" list_keywords >>= withAttribute "Keyword")) <|> ((pKeyword " \n\t(),;[]{}\\" list_operators >>= withAttribute "Operator")) <|> ((pKeyword " \n\t(),;[]{}\\" list_functions >>= withAttribute "Function")) <|> ((pKeyword " \n\t(),;[]{}\\" list_types >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'25bulk'5fexceptions'5cb >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'25bulk'5frowcount'5cb >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'25found'5cb >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'25isopen'5cb >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'25notfound'5cb >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'25rowcount'5cb >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'25rowtype'5cb >>= withAttribute "Data Type")) <|> ((pRegExpr regex_'25type'5cb >>= withAttribute "Data Type")) <|> ((pFloat >>= withAttribute "Float")) <|> ((pInt >>= withAttribute "Decimal")) <|> ((pDetectChar False '\'' >>= withAttribute "String") >>~ pushContext "String") <|> ((pDetectChar False '#' >>= withAttribute "Comment") >>~ pushContext "SingleLineComment") <|> ((pDetect2Chars False '-' '-' >>= withAttribute "Comment") >>~ pushContext "SingleLineComment") <|> ((pDetect2Chars False '/' '*' >>= withAttribute "Comment") >>~ pushContext "MultiLineComment") <|> ((pColumn 0 >> pRegExpr regex_rem'5cb >>= withAttribute "Comment") >>~ pushContext "SingleLineComment") <|> ((pDetectChar False '"' >>= withAttribute "Comment") >>~ pushContext "Identifier") <|> ((pAnyChar ":&" >>= withAttribute "Symbol")) <|> ((pColumn 0 >> pRegExpr regex_'2f'24 >>= withAttribute "Symbol")) <|> ((pColumn 0 >> pRegExpr regex_'40'40'3f'5b'5e'40_'5ct'5cr'5cn'5d >>= withAttribute "Preprocessor") >>~ pushContext "Preprocessor") <|> ((pRegExprDynamic "\\$([^\\$\\n\\r]*)\\$" >>= withAttribute "Operator") >>~ pushContext "MultiLineString")) return (attr, result) parseRules "CreateFunction" = do (attr, result) <- (((pRegExprDynamic "\\$([^\\$\\n\\r]*)\\$" >>= withAttribute "Function") >>~ pushContext "FunctionBody") <|> ((parseRules "Normal"))) return (attr, result) parseRules "FunctionBody" = do (attr, result) <- (((pRegExprDynamic "\\$%1\\$" >>= withAttribute "Function") >>~ (popContext >> popContext)) <|> ((parseRules "Normal"))) return (attr, result) parseRules "MultiLineString" = do (attr, result) <- ((pRegExprDynamic "\\$%1\\$" >>= withAttribute "Operator") >>~ (popContext)) return (attr, result) parseRules "String" = do (attr, result) <- (((pLineContinue >>= withAttribute "String") >>~ (popContext)) <|> ((pHlCStringChar >>= withAttribute "String Char")) <|> ((pDetectChar False '&' >>= withAttribute "Symbol")) <|> ((pDetectChar False '\'' >>= withAttribute "String") >>~ (popContext))) return (attr, result) parseRules "SingleLineComment" = pzero parseRules "MultiLineComment" = do (attr, result) <- (((pLineContinue >>= withAttribute "Comment") >>~ (popContext)) <|> ((pDetect2Chars False '*' '/' >>= withAttribute "Comment") >>~ (popContext))) return (attr, result) parseRules "Identifier" = do (attr, result) <- ((pDetectChar False '"' >>= withAttribute "Identifier") >>~ (popContext)) return (attr, result) parseRules "Preprocessor" = pzero parseRules "" = parseRules "Normal" parseRules x = fail $ "Unknown context" ++ x