{ -- | -- Module: Language.Go.Parser.Lexer module Language.Go.Parser.Lexer where import Language.Go.Parser.Tokens import Codec.Binary.UTF8.String import Text.Parsec.Pos } %wrapper "posn" @unicode_char = [\x00-\x7F]|[\x80-\xFF]+ @unicode_nobr = [\x00-\x5C\x5E-\x7F]|[\x80-\xFF]+ @unicode_nobq = [\x00-\x5F\x61-\x7F]|[\x80-\xFF]+ @unicode_nodq = [\x00-\x21\x23-\x7F]|[\x80-\xFF]+ @unicode_letter = [A-Za-z] -- should be [\p{L}] @unicode_digit = [0-9] -- should be [\p{N}] $decimal_digit = [0-9] $octal_digit = [0-7] $hex_digit = [0-9A-Fa-f] $sign = [\+\-] $punctuation = [\!\@\#\$\%\^\&\*\-_\+=\<\>\,\.\:\;\|\\\/\?\~] @letter = _|@unicode_letter @identifier7bit = @letter(@letter|@unicode_digit)* @identifier = (@identifier7bit)|\#\[(@unicode_nobr)+\] @decimal_lit = [1-9]($decimal_digit)* @octal_lit = 0($octal_digit)* @hex_lit = 0[xX]($hex_digit)+ @int_lit = (@decimal_lit|@octal_lit|@hex_lit) @decimals = ($decimal_digit)+ @exponent = [eE]($sign)?(@decimals) @float1lit = (@decimals)\.(@decimals)?(@exponent)? @float2lit = (@decimals)(@exponent) @float3lit = \.(@decimals)(@exponent)? @float_lit = (@float1lit|@float2lit|@float3lit) @imaginary_lit = (@decimals|@float_lit)i @hex_byte_value = \\x($hex_digit){2} @oct_byte_value = \\($octal_digit){3} @little_u_value = \\u($hex_digit){4} @big_u_value = \\U($hex_digit){8} @escaped_char = \\\\\\ -- \\[abfnrtv\`\'\"] @unicode_value = (@unicode_nodq|@little_u_value|@big_u_value|@escaped_char) @byte_value = (@oct_byte_value|@hex_byte_value) @raw_string_lit = \`(@unicode_nobq)*\` @int_string_lit = \"(@unicode_value|@byte_value)*\" @char_lit = \'(@unicode_value|@byte_value)\' @string_lit = (@raw_string_lit|@int_string_lit) @operator = ($punctuation)+|\#\{(@unicode_nobr)+\} -- @comment_char = [\ A-Za-z\-\r\n] -- @ml_char = [\x00-\x29\x2B-\xFF] @ol_char = [^\n] @ml_char = [\x00-\x29\x2B-\xFF]|\*[\x00-\x2E\x30-\xFF] @ol_comment = "//"(@ol_char)*\n @ml_comment = "/*"(@ml_char)*"*/" $whitespace = [\ \t\f\v\r] $whiteline = [\n] tokens :- $whitespace+ { \p s -> posify p $ GoTokNone } $whiteline { \p s -> posify p $ GoTokSemicolonAuto } ";" { \p s -> posify p $ GoTokSemicolon } @ol_comment { \p s -> posify p $ tokenFromComment False s } @ml_comment { \p s -> posify p $ tokenFromComment True s } @int_lit { \p s -> posify p $ tokenFromInt s } @float_lit { \p s -> posify p $ tokenFromReal s } @imaginary_lit { \p s -> posify p $ tokenFromImag s } @char_lit { \p s -> posify p $ tokenFromChar s } @raw_string_lit { \p s -> posify p $ tokenFromRawStr s } @int_string_lit { \p s -> posify p $ tokenFromString s } "(" { \p s -> posify p $ GoTokLParen } ")" { \p s -> posify p $ GoTokRParen } "{" { \p s -> posify p $ GoTokLBrace } "}" { \p s -> posify p $ GoTokRBrace } "[" { \p s -> posify p $ GoTokLBracket } "]" { \p s -> posify p $ GoTokRBracket } "--" { \p s -> posify p $ GoTokDec } "++" { \p s -> posify p $ GoTokInc } "," { \p s -> posify p $ GoTokComma } "." { \p s -> posify p $ GoTokFullStop } @operator { \p s -> posify p $ tokenFromOp s } break { \p s -> posify p $ GoTokBreak } case { \p s -> posify p $ GoTokCase } chan { \p s -> posify p $ GoTokChan } const { \p s -> posify p $ GoTokConst } continue { \p s -> posify p $ GoTokContinue } default { \p s -> posify p $ GoTokDefault } defer { \p s -> posify p $ GoTokDefer } else { \p s -> posify p $ GoTokElse } fallthrough { \p s -> posify p $ GoTokFallthrough } for { \p s -> posify p $ GoTokFor } func { \p s -> posify p $ GoTokFunc } go { \p s -> posify p $ GoTokGo } goto { \p s -> posify p $ GoTokGoto } if { \p s -> posify p $ GoTokIf } import { \p s -> posify p $ GoTokImport } interface { \p s -> posify p $ GoTokInterface } map { \p s -> posify p $ GoTokMap } package { \p s -> posify p $ GoTokPackage } range { \p s -> posify p $ GoTokRange } return { \p s -> posify p $ GoTokReturn } select { \p s -> posify p $ GoTokSelect } struct { \p s -> posify p $ GoTokStruct } switch { \p s -> posify p $ GoTokSwitch } type { \p s -> posify p $ GoTokType } var { \p s -> posify p $ GoTokVar } @identifier { \p s -> posify p $ tokenFromId s } { posAlex2Parsec :: String -> AlexPosn -> SourcePos posAlex2Parsec filename (AlexPn o l c) = newPos filename l c posify :: AlexPosn -> GoToken -> GoTokenPos posify pos tok = GoTokenPos (posAlex2Parsec "" pos) tok }