-- | -- Module : Language.Go.Parser.Tokens -- Copyright : (c) 2011 Andrew Robbins -- License : GPLv3 (see COPYING) -- -- x module Language.Go.Parser.Tokens where import Language.Go.Syntax.AST (GoSource) import Text.Parsec.String import Text.Parsec.Prim import Text.Parsec.Pos (SourcePos(..)) -- | GoTokener is the type used for all tokenizers -- type GoTokener = GenParser Char () [GoToken] -- | GoParser is the type used for all parsers type GoParser a = GenParser GoTokenPos () a -- | GoTokenPos encodes tokens and source positions data GoTokenPos = GoTokenPos !SourcePos !GoToken deriving (Eq, Show) -- | GoToken encodes tokens data GoToken = GoTokNone | GoTokComment Bool String -- BEGIN literals | GoTokInteger (Maybe String) Integer | GoTokFloat (Maybe String) Float | GoTokFloatI (Maybe String) Float | GoTokChar (Maybe String) Char | GoTokString (Maybe String) String -- END literals -- BEGIN wraps | GoTokLParen -- '(' | GoTokRParen -- ')' | GoTokLBrace -- '{' | GoTokRBrace -- '}' | GoTokLBracket -- '[' | GoTokRBracket -- ']' -- END wraps -- BEGIN keywords | GoTokBreak | GoTokCase | GoTokChan | GoTokConst | GoTokContinue | GoTokDefault | GoTokDefer | GoTokElse | GoTokFallthrough | GoTokFor | GoTokFunc | GoTokGo | GoTokGoto | GoTokIf | GoTokImport | GoTokInterface | GoTokMap | GoTokPackage | GoTokRange | GoTokReturn | GoTokSelect | GoTokStruct | GoTokSwitch | GoTokType | GoTokVar -- END keywords | GoTokSemicolonAuto | GoTokSemicolon -- ';' | GoTokColon -- ':' | GoTokComma -- ',' | GoTokFullStop -- '.' | GoTokAsterisk -- '*' | GoTokElipsis -- '...' | GoTokDec -- '--' | GoTokInc -- '++' -- BEGIN names | GoTokId String | GoTokOp String -- END names deriving (Eq, Read, Show) -- Data, Typeable tokenSimplify :: (Int, Int) -> String -> String tokenSimplify (n, m) s = map (s!!) [n..(length s)-m-1] tokenFromId :: String -> GoToken tokenFromId s = GoTokId $ if s!!0 == '#' && s!!1 == '[' then tokenSimplify (2, 1) s else s tokenFromOp :: String -> GoToken tokenFromOp s = GoTokOp $ if s!!0 == '#' && s!!1 == '{' then tokenSimplify (2, 1) s else s -- False=singleline True=multiline tokenFromComment :: Bool -> String -> GoToken tokenFromComment False s = GoTokComment False $ tokenSimplify (2, 1) s tokenFromComment True s = GoTokComment True $ tokenSimplify (2, 2) s tokenFromInt :: String -> GoToken tokenFromInt s = GoTokInteger (Just s) $ ((read s) :: Integer) tokenFromReal :: String -> GoToken tokenFromReal s = GoTokFloat (Just s) $ (read s) tokenFromImag :: String -> GoToken tokenFromImag s = GoTokFloatI (Just s) $ (read $ init s) tokenFromRawStr :: String -> GoToken tokenFromRawStr s = GoTokString (Just s) $ tokenSimplify (1, 1) s -- TODO: process \u#### and stuff tokenFromString :: String -> GoToken tokenFromString s = GoTokString (Just s) $ tokenSimplify (1, 1) s tokenFromChar :: String -> GoToken tokenFromChar s = GoTokChar (Just s) (s!!1)