Copyright | (c) Alec Theriault 2017-2018 |
---|---|
License | BSD-style |
Maintainer | alec.theriault@gmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Contains roughly the same stuff as syntax::parse::token
- data definitions for tokens.
Synopsis
- data Token
- = Equal
- | Less
- | Greater
- | Ampersand
- | Pipe
- | Exclamation
- | Tilde
- | Plus
- | Minus
- | Star
- | Slash
- | Percent
- | Caret
- | GreaterEqual
- | GreaterGreaterEqual
- | AmpersandAmpersand
- | PipePipe
- | LessLess
- | GreaterGreater
- | EqualEqual
- | NotEqual
- | LessEqual
- | LessLessEqual
- | MinusEqual
- | AmpersandEqual
- | PipeEqual
- | PlusEqual
- | StarEqual
- | SlashEqual
- | CaretEqual
- | PercentEqual
- | At
- | Dot
- | DotDot
- | DotDotEqual
- | DotDotDot
- | Comma
- | Semicolon
- | Colon
- | ModSep
- | RArrow
- | LArrow
- | FatArrow
- | Pound
- | Dollar
- | Question
- | EmbeddedCode String
- | EmbeddedIdent String
- | OpenDelim !Delim
- | CloseDelim !Delim
- | LiteralTok LitTok (Maybe Name)
- | IdentTok Ident
- | LifetimeTok Ident
- | Space Space Name
- | Doc String !AttrStyle !Bool
- | Shebang
- | Eof
- | Interpolated (Nonterminal Span)
- spaceNeeded :: Token -> Token -> Bool
- data Space
- data Delim
- data LitTok
- data AttrStyle
Documentation
A general token (based on syntax::parse::token::Token
).
Unlike its libsyntax
counterpart, Token
has folded in syntax::parse::token::BinOpToken
and syntax::parse::token::BinOpEqToken
as regular tokens.
Equal |
|
Less |
|
Greater |
|
Ampersand |
|
Pipe |
|
Exclamation |
|
Tilde |
|
Plus |
|
Minus |
|
Star |
|
Slash |
|
Percent |
|
Caret |
|
GreaterEqual |
|
GreaterGreaterEqual |
|
AmpersandAmpersand |
|
PipePipe |
|
LessLess |
|
GreaterGreater |
|
EqualEqual |
|
NotEqual |
|
LessEqual |
|
LessLessEqual |
|
MinusEqual |
|
AmpersandEqual |
|
PipeEqual |
|
PlusEqual |
|
StarEqual |
|
SlashEqual |
|
CaretEqual |
|
PercentEqual |
|
At |
|
Dot |
|
DotDot |
|
DotDotEqual |
|
DotDotDot |
|
Comma |
|
Semicolon |
|
Colon |
|
ModSep |
|
RArrow |
|
LArrow |
|
FatArrow |
|
Pound |
|
Dollar |
|
Question |
|
EmbeddedCode String |
|
EmbeddedIdent String |
|
OpenDelim !Delim | One of |
CloseDelim !Delim | One of |
LiteralTok LitTok (Maybe Name) | a literal token with an optional suffix (something like |
IdentTok Ident | an arbitrary identifier (something like |
LifetimeTok Ident | a lifetime (something like |
Space Space Name | whitespace |
Doc String !AttrStyle !Bool | doc comment with its contents, whether it is outer/inner, and whether it is inline or not |
Shebang |
|
Eof | end of file token |
Interpolated (Nonterminal Span) | can be expanded into several tokens in macro-expansion |
Instances
spaceNeeded :: Token -> Token -> Bool Source #
Check whether a space is needed between two tokens to avoid confusion.
Rust is whitespace independent. Short of providing space between tokens, whitespace is all the same to the parser.
Whitespace | usual white space: |
Comment | comment (either inline or not) |
Instances
Bounded Space Source # | |
Enum Space Source # | |
Defined in Language.Rust.Syntax.Token | |
Eq Space Source # | |
Data Space Source # | |
Defined in Language.Rust.Syntax.Token gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Space -> c Space # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Space # dataTypeOf :: Space -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Space) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Space) # gmapT :: (forall b. Data b => b -> b) -> Space -> Space # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Space -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Space -> r # gmapQ :: (forall d. Data d => d -> u) -> Space -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Space -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Space -> m Space # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Space -> m Space # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Space -> m Space # | |
Ord Space Source # | |
Show Space Source # | |
Generic Space Source # | |
NFData Space Source # | |
Defined in Language.Rust.Syntax.Token | |
type Rep Space Source # | |
A delimiter token (syntax::parse::token::DelimToken
).
Paren | round parenthesis: |
Bracket | square bracket: |
Brace | curly brace: |
NoDelim | empty delimiter |
Instances
Bounded Delim Source # | |
Enum Delim Source # | |
Defined in Language.Rust.Syntax.Token | |
Eq Delim Source # | |
Data Delim Source # | |
Defined in Language.Rust.Syntax.Token gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delim -> c Delim # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delim # dataTypeOf :: Delim -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Delim) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delim) # gmapT :: (forall b. Data b => b -> b) -> Delim -> Delim # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delim -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delim -> r # gmapQ :: (forall d. Data d => d -> u) -> Delim -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Delim -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delim -> m Delim # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delim -> m Delim # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delim -> m Delim # | |
Ord Delim Source # | |
Show Delim Source # | |
Generic Delim Source # | |
NFData Delim Source # | |
Defined in Language.Rust.Syntax.Token | |
type Rep Delim Source # | |
Defined in Language.Rust.Syntax.Token type Rep Delim = D1 (MetaData "Delim" "Language.Rust.Syntax.Token" "flp-0.1.0.0-DeMkA8gwwJbCOh6gqZDp9v" False) ((C1 (MetaCons "Paren" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Bracket" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Brace" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoDelim" PrefixI False) (U1 :: Type -> Type))) |
A literal token (syntax::parse::token::Lit
)
ByteTok Name | byte |
CharTok Name | character |
IntegerTok Name | integral literal (could have type |
FloatTok Name | floating point literal (could have type |
StrTok Name | string literal |
StrRawTok Name !Int | raw string literal and the number of |
ByteStrTok Name | byte string literal |
ByteStrRawTok Name !Int | raw byte string literal and the number of |
Instances
Distinguishes between attributes that are associated with the node that follows them and
attributes that are associated with the node that contains them (syntax::ast::AttrStyle
).
These two cases need to be distinguished only for pretty printing - they are otherwise
fundamentally equivalent.
Example: #[repr(C)]
is an outer attribute while #![feature(slice_patterns)]
is an inner one