2 The C Language
This library provides data types representing C abstract syntax, a C parser, and macros for constructing C abstract syntax with a convenient parenthesized syntax. It can be required via:
2.1 C Language Grammar
typedef int T; |
void proc(char T) { } |
The following is a more detailed (and slightly reorganized) grammar than the one in the C99 standard which explicitly specifies when tokens bound as typedef names can be used as identifiers.
| ‹List›X | ::= | X {"," ‹List›X}* |
| ‹AnyIdentifier› | ::= | ‹Identifier› |
|
| | | ‹TypedefName› |
2.1.1 Expressions
| ‹PrimaryExpression› | ::= | ‹Identifier› |
|
| | | ‹Constant› |
|
| | | ‹StringLiteral› |
|
| | | "(" ‹Expression› ")" |
| ‹PostfixExpression› | ::= | ‹PrimaryExpression› |
|
| | | ‹PostfixExpression› "[" ‹Expression› "]" |
|
| | | ‹PostfixExpression› "(" [‹List›‹AssignmentExpression›] ")" |
|
| | | ‹PostfixExpression› "." ‹AnyIdentifier› |
|
| | | ‹PostfixExpression› "->" ‹AnyIdentifier› |
|
| | | ‹PostfixExpression› "++" |
|
| | | ‹PostfixExpression› "–" |
|
| | | "(" ‹TypeName› ")" "{" ‹List›‹Initializer› [","] "}" |
| ‹UnaryExpression› | ::= | "++" ‹UnaryExpression› |
|
| | | "–" ‹UnaryExpression› |
|
| | | {"&" | "*" | "+" | "-" | "~" | "!"} ‹CastExpression› |
|
| | | "sizeof" ‹UnaryExpression› |
|
| | | "sizeof" "(" ‹TypeName› ")" |
| ‹CastExpression› | ::= | ‹UnaryExpression› |
|
| | | "(" ‹TypeName› ")" ‹CastExpression› |
| ‹BinaryExpression›(E,Op) | ::= | E |
|
| | | ‹BinaryExpression›(E,Op) Op E |
| ‹MultiplicativeExpression› | ::= | ‹BinaryExpression›(‹CastExpression›,{"*" | "/" | "%"}) |
| ‹AdditiveExpression› | ::= | ‹BinaryExpression›(‹MultiplicativeExpression›,{"+" | "-"}) |
| ‹ShiftExpression› | ::= | ‹BinaryExpression›(‹AdditiveExpression›,{"<<" | ">>"}) |
| ‹RelationalExpression› | ::= | ‹BinaryExpression›(‹ShiftExpression›,{"<" | ">" | "<=" | ">="}) |
| ‹EqualityExpression› | ::= | ‹BinaryExpression›(‹RelationalExpression›,{"==" | "!="}) |
| ‹ANDExpression› | ::= | ‹BinaryExpression›(‹EqualityExpression›,"&") |
| ‹ExclusiveORExpression› | ::= | ‹BinaryExpression›(‹ANDExpression›,"^") |
| ‹InclusiveORExpression› | ::= | ‹BinaryExpression›(‹ExclusiveORExpression›,"|") |
| ‹LogicalANDExpression› | ::= | ‹BinaryExpression›(‹LogicalORExpression›,"||") |
| ‹ConditionalExpression› | ::= | ‹LogicalORExpression› |
|
| | | ‹LogicalORExpression› "?" ‹Expression› ":" ‹ConditionalExpression› |
| ‹AssignmentExpression› | ::= | ‹ConditionalExpression› |
|
| | | ‹UnaryExpression› ‹AssignmentOperator› ‹AssignmentExpression› |
| ‹AssignmentOperator› | ::= | "=" | "*=" | "/=" | "%=" | "+=" | "-=" |
|
| | | "<<=" | ">>=" | "&=" | "^=" | "|=" |
| ‹Expression› | ::= | ‹List›‹AssignmentExpression› |
| ‹ConstantExpression› | ::= | ‹ConditionalExpression› |
2.1.2 Declarations
| ‹Declaration› | ::= | ‹DeclarationModifier›+ [‹List›‹InitDeclarator›‹Identifier›] ";" |
|
| | | ‹DeclarationSpecifiers› [‹List›‹InitDeclarator›‹AnyIdentifier›] ";" |
| ‹DeclarationSpecifiers› | ::= | ‹DeclarationModifier›* ‹TaggedTypeSpecifier› ‹DeclarationModifier›* |
|
| | | ‹DeclarationModifier›* ‹TypedefName› ‹DeclarationModifier›* |
|
| | | ‹DeclarationModifier›* {‹PrimTypeSpecifier› ‹DeclarationModifier›*}+ |
| ‹DeclarationModifier› | ::= | ‹StorageClassSpecifier› |
|
| | | ‹TypeQualifier› |
|
| | | ‹FunctionSpecifier› |
| ‹InitDeclarator›X | ::= | ‹Declarator›X ["=" ‹Initializer›] |
| ‹StorageClassSpecifier› | ::= | "typedef" | "extern" | "static" | "auto" | "register" |
| ‹TypeSpecifier› | ::= | ‹PrimTypeSpecifier› |
|
| | | ‹TaggedTypeSpecifier› |
|
| | | ‹TypedefName› |
| ‹PrimTypeSpecifier› | ::= | "void" |
|
| | | "char" | "short" | "int" | "long" |
|
| | | "float" | "double" |
|
| | | "signed" | "unsigned" |
|
| | | "_Bool" | "_Complex" |
| ‹TaggedTypeSpecifier› | ::= | {"struct" | "union"} [‹Tag›] "{" ‹StructDeclaration›+ "}" |
|
| | | {"struct" | "union"} ‹Tag› |
|
| | | ‹EnumSpecifier› |
| ‹Tag› | ::= | ‹Identifier› |
|
| | | ‹TypedefName› |
| ‹StructDeclaration› | ::= | ‹TypeQualifier›+ [‹List›‹StructDeclarator›‹Identifier›] ";" |
|
| | | ‹StructSpecifiers› [‹List›‹StructDeclarator›‹AnyIdentifier›] ";" |
| ‹StructSpecifiers› | ::= | ‹TypeQualifier›* ‹TaggedTypeSpecifier› ‹TypeQualifier›* |
|
| | | ‹TypeQualifier›* ‹TypedefName› ‹TypeQualifier›* |
|
| | | ‹TypeQualifier›* {‹PrimTypeSpecifier› ‹TypeQualifier›*}+ |
| ‹StructDeclarator›X | ::= | ‹Declarator›X |
|
| | | [‹Declarator›X] ":" ‹ConstantExpression› |
| ‹EnumSpecifier› | ::= | "enum" [‹Tag›] "{" ‹List›‹Enumerator› [","] "}" |
|
| | | "enum" ‹Tag› |
| ‹Enumerator› | ::= | ‹AnyIdentifier› ["=" ‹ConstantExpression›] |
| ‹TypeQualifier› | ::= | "const" | "restrict" | "volatile" |
| ‹FunctionSpecifier› | ::= | "inline" |
| ‹Declarator›X | ::= | [‹Pointer›] ‹DirectDeclarator›X |
| ‹DirectDeclarator›X | ::= | X |
|
| | | "(" ‹Declarator›X ")" |
|
| | | ‹DirectDeclarator›X "[" ‹TypeQualifier›* [‹AssignmentExpression›] "]" |
|
| | | ‹DirectDeclarator›X "[" "static" ‹TypeQualifier›* ‹AssignmentExpression› "]" |
|
| | | ‹DirectDeclarator›X "[" TypeQualifier+ "static" ‹AssignmentExpression› "]" |
|
| | | ‹DirectDeclarator›X "[" ‹TypeQualifier›* "*" "]" |
|
| | | ‹DirectDeclarator›X "(" ‹ParameterTypeList› ")" |
|
| | | ‹DirectDeclarator›X "(" [‹List›‹Identifier›] ")" |
| ‹Pointer› | ::= | {"*" ‹TypeQualifier›*}+ |
| ‹ParameterTypeList› | ::= | ‹List›‹ParameterDeclaration› ["," "..."] |
| ‹ParameterDeclaration› | ::= | ‹DeclarationModifier›+ [‹Declarator›‹Identifier›] |
|
| | | ‹DeclarationSpecifiers› [‹Declarator›‹AnyIdentifier›] |
|
| | | ‹DeclarationModifier›+ ‹AbstractDeclarator› |
|
| | | ‹DeclarationSpecifiers› ‹AbstractDeclarator› |
| ‹TypeName› | ::= | {‹TypeSpecifier› | ‹TypeQualifier›}+ [‹AbstractDeclarator›] |
| ‹AbstractDeclarator› | ::= | ‹Pointer› |
|
| | | [‹Pointer›] ‹DirectAbstractDeclarator› |
| ‹DirectAbstractDeclarator› | ::= | "(" ‹AbstractDeclarator› ")" |
|
| | | [‹DirectAbstractDeclarator›] "[" ‹TypeQualifier›* [‹AssignmentExpression›] "]" |
|
| | | [‹DirectAbstractDeclarator›] "[" "static" ‹TypeQualifier›* ‹AssignmentExpression› "]" |
|
| | | [‹DirectAbstractDeclarator›] "[" ‹TypeQualifier›+ "static" ‹AssignmentExpression› "]" |
|
| | | [‹DirectAbstractDeclarator›] "[" "*" "]" |
|
| | | [‹DirectAbstractDeclarator›] "(" [‹ParameterTypeList›] ")" |
| ‹Initializer› | ::= | ‹AssignmentExpression› |
|
| | | "{" ‹List›{[‹List›‹Designator› "="] ‹Initializer›} [","] "}" |
| ‹Designator› | ::= | "[" ‹ConstantExpression› "]" |
|
| | | "." ‹AnyIdentifier› |
2.1.3 Statements
The parameterized statement non-terminals such as ‹Statement›X take a flag indicating whether the productions may be right-terminated by a one-armed if statement (i.e., an if statement with no else clause). This is used to avoid the “dangling else” ambiguity.
| ‹Statement›X | ::= | ‹LabeledStatement›X |
|
| | | ‹CompoundStatement› |
|
| | | ‹ExpressionStatement› |
|
| | | ‹SelectionStatement›X |
|
| | | ‹IterationStatement›X |
|
| | | ‹JumpStatement› |
| ‹LabeledStatement›X | ::= | ‹AnyIdentifier› ":" ‹Statement›X |
|
| | | "case" ‹ConstantExpression› ":" ‹Statement›X |
|
| | | "default" ":" ‹Statement›X |
| ‹CompoundStatement› | ::= | "{" ‹BlockItem›* "}" |
| ‹BlockItem› | ::= | ‹Declaration› |
|
| | | ‹Statement›#t |
| ‹ExpressionStatement› | ::= | [‹Expression›] ";" |
| ‹SelectionStatement›X | ::= | ‹IfStatement›X |
|
| | | "switch" "(" ‹Expression› ")" ‹Statement›X |
| ‹IfStatement›#t | ::= | "if" "(" ‹Expression› ")" ‹Statement›#t ["else" ‹Statement›#t] |
| ‹IfStatement›#f | ::= | "if" "(" ‹Expression› ")" ‹Statement›#t "else" ‹Statement›#f |
| ‹IterationStatement›X | ::= | "while" "(" ‹Expression› ")" ‹Statement›X |
|
| | | "do" ‹Statement›#t "while" "(" ‹Expression› ")" ";" |
|
| | | "for" "(" [‹Expression›] ";" [‹Expression›] ";" [‹Expression›] ")" ‹Statement›X |
|
| | | "for" "(" ‹Declaration› [‹Expression›] ";" [‹Expression›] ")" ‹Statement›X |
| ‹JumpStatement› | ::= | "goto" ‹AnyIdentifier› ";" |
|
| | | "continue" ";" |
|
| | | "break" ";" |
|
| | | "return" [‹Expression›] ";" |
2.1.4 Programs
| ‹TranslationUnit› | ::= | ‹ExternalDefinition›+ |
| ‹ExternalDefinition› | ::= | ‹FunctionDefinition› |
|
| | | ‹Declaration› |
| ‹FunctionDefinition› | ::= | ‹FunctionHead› [‹List›‹Declaration›] ‹FunctionBody› |
| ‹FunctionHead› | ::= | ‹DeclarationModifier›+ ‹Declarator›‹Identifier› |
|
| | | ‹DeclarationSpecifiers› ‹Declarator›‹AnyIdentifier› |
| ‹FunctionBody› | ::= | ‹CompoundStatement› |
2.2 Abstract Syntax
The abstract syntax of C is represented as structs. All of the structure definitions are provided by the package
(require (planet dherman/c:3:3/ast)) |
All of the structs defined in this library are prefab structs, and consist entirely of read-able and write-able data.
2.2.1 Source Locations
Source location information is stored with the following struct type.
| ||||||||||||||||||||||||||||||||||||||||
start-offset : exact-nonnegative-integer? | ||||||||||||||||||||||||||||||||||||||||
start-line : exact-positive-integer? | ||||||||||||||||||||||||||||||||||||||||
start-col : exact-nonnegative-integer? | ||||||||||||||||||||||||||||||||||||||||
end-offset : exact-nonnegative-integer? | ||||||||||||||||||||||||||||||||||||||||
end-line : exact-positive-integer? | ||||||||||||||||||||||||||||||||||||||||
end-col : exact-nonnegative-integer? | ||||||||||||||||||||||||||||||||||||||||
path : any |
(position-min p ...+) → position? |
p : position? |
(position-max p ...+) → position? |
p : position? |
(src->syntax x [datum original?]) → syntax? |
x : src? |
datum : any = '... |
original? : boolean? = #t |
(id->syntax id [original?]) → syntax? |
id : id? |
original? : boolean? = #t |
(primitive-type-specifier? x) → boolean? |
x : symbol? |
(unary-operator? x) → boolean? |
x : symbol? |
(binary-operator? x) → boolean? |
x : symbol? |
(assignment-operator? x) → boolean? |
x : symbol? |
(increment-operator? x) → boolean? |
x : symbol? |
2.2.2 Identifiers
| ||||||
name : symbol? |
| ||||||
name : symbol? |
| ||||||
name : (or/c 'const 'restrict 'volatile) |
| ||||||
name : (or/c unary-operator? binary-operator? assignment-operator? increment-operator?) |
| ||||||
class : (or/c 'typedef 'extern 'static 'auto 'register) |
|
|
|
2.2.3 Expressions
| ||||||
id : id:var? |
| ||||||
value : integer? | ||||||
qualifiers : (listof id:qualifier?) |
| ||||||
value : inexact-real? | ||||||
qualifiers : (listof id:qualifier?) |
| ||||||
source : string? | ||||||
wide? : boolean? |
Example: | ||
|
| ||||||
source : string? | ||||||
wide? : boolean? |
Example: | ||
|
| ||||||
type : type? | ||||||
inits : (listof (or/c init? (cons (listof dtor?) init?))) |
| ||||||
expr : expr? | ||||||
offset : expr? |
| ||||||
function : expr? | ||||||
arguments : (listof expr?) |
| ||||||
expr : expr? | ||||||
label : id:label? |
| ||||||
expr : expr? | ||||||
label : id:label? |
| ||||||
expr : expr? | ||||||
op : id:op? |
| ||||||
op : id:op? | ||||||
expr : expr? |
| ||||||
type : type? | ||||||
expr : expr? |
| ||||||
term : (or/c type? expr?) |
| ||||||
left : expr? | ||||||
op : id:op? | ||||||
right : expr? |
| ||||||
left : expr? | ||||||
op : id:op? | ||||||
right : expr? |
| ||||||
left : expr? | ||||||
right : expr? |
| ||||||
test : expr? | ||||||
cons : expr? | ||||||
alt : expr? |
2.2.4 Statements
| ||||||
label : id:label? | ||||||
stmt : stmt? |
| ||||||
expr : expr? | ||||||
stmt : stmt? |
| ||||||
stmt : stmt? |
| ||||||
items : (listof (or/c decl? stmt?)) |
| ||||||
expr : expr? |
| ||||||
test : expr? | ||||||
cons : stmt? | ||||||
alt : (or/c stmt? #f) |
| ||||||
test : expr? | ||||||
body : stmt? |
| ||||||
test : expr? | ||||||
body : stmt? |
| ||||||
init : (or/c expr? decl? #f) | ||||||
test : (or/c expr? #f) | ||||||
update : (or/c expr? #f) | ||||||
body : stmt? |
| ||||||
label : id:label? |
|
|
| ||||||
result : (or/c expr? #f) |
|
2.2.5 Declarations
| ||||||
type : type? | ||||||
declarators : (listof declarator-context?) |
| ||||||
storage-class : (or/c id:storage? #f) | ||||||
type : (or/c type? #f) | ||||||
declarators : (listof declarator-context?) |
| ||||||
storage-class : (or/c id:storage? #f) | ||||||
type : (or/c type? #f) | ||||||
declarator : (or/c declarator-context? type-context?) |
| |||||||||||||||||||||||||||||||||||
storage-class : (or/c id:storage? #f) | |||||||||||||||||||||||||||||||||||
inline? : (or/c id:inline? #f) | |||||||||||||||||||||||||||||||||||
return-type : type? | |||||||||||||||||||||||||||||||||||
declarator : declarator-context? | |||||||||||||||||||||||||||||||||||
preamble : (or/c (listof decl?) #f) | |||||||||||||||||||||||||||||||||||
body : stmt:block? |
| ||||||
id : (or/c id:var? #f) | ||||||
type : (or/c type? #f) | ||||||
initializer : (or/c init? #f) |
(declarator-context? x) → boolean? |
x : any |
(complete-declarator? x) → boolean? |
x : any |
| ||||||
id : (or/c id:label? #f) | ||||||
type : (or/c type? #f) | ||||||
initializer : (or/c init? #f) | ||||||
bit-size : (or/c expr? #f) |
(member-declarator-context? x) → boolean? |
x : any |
(complete-member-declarator? x) → boolean? |
x : any |
| ||||||
type : (or/c type? #f) | ||||||
declarators : (listof decl:declarator?) |
2.2.6 Initializers
| ||||||
elements : (listof (or/c init? (cons (listof dtor?) init?))) |
| ||||||
expr : expr? |
2.2.7 Designators
| ||||||
expr : expr? |
| ||||||
label : id:label? |
2.2.8 Types
| ||||||
name : (or/c primitive-type-specifier? (listof primitive-type-specifier?)) |
'void, 'char, 'short, 'int, 'long, 'float, 'double, 'signed, 'unsigned, '_Bool, or '_Complex
'(signed char)
'(unsigned char)
'(signed short)
'(signed short int)
'(unsigned short)
'(unsigned short int)
'(signed int)
'(unsigned int)
'(signed long)
'(long int)
'(signed long int)
'(unsigned long)
'(unsigned long int)
'(long long)
'(signed long long)
'(long long int)
'(signed long long int)
'(unsigned long long)
'(unsigned long long int)
'(long double)
'(float _Complex)
'(double _Complex)
'(long double _Complex)
| ||||||
id : id:var? |
| ||||||
tag : id:label? | ||||||
fields : (or/c (listof decl:member?) #f) |
| ||||||
tag : id:label? | ||||||
variants : (or/c (listof decl:member?) #f) |
| ||||||
tag : id:label? | ||||||
variants : (or/c (listof (or/c id:var? (cons id:var? expr?))) #f) |
| ||||||
base : type? | ||||||
static? : (or/c id:static? #f) | ||||||
qualifiers : (listof id:qualifier?) | ||||||
length : (or/c expr? #f) | ||||||
star? : (or/c id:star? #f) |
| ||||||
base : type? | ||||||
qualifiers : (listof id:qualifier?) |
| ||||||
return : type? | ||||||
formals : (listof (or/c decl:formal? id:ellipsis?)) |
| ||||||
type : (or/c type? #f) | ||||||
qualifiers : (listof id:qualifier?) |
2.2.9 Type Contexts
typedef int A[32], *PA[32]; |
#f;
a type:pointer whose type:pointer-base field is a type context;
a type:array whose type:array-base field is a type context;
or a type:function whose type:function-return field is a type context.
(type-context? x) → boolean? |
x : any |
(complete-type? x) → boolean? |
x : any |
(apply-type-context context base) → complete-type? |
context : type-context? |
base : complete-type? |
(apply-declarator-context context base) → complete-declarator? |
context : declarator-context? |
base : complete-type? |
(apply-declarator-contexts contexts base) |
→ (listof complete-declarator?) |
contexts : (listof declarator-context?) |
base : complete-type? |
| ||||||||
→ complete-member-declarator? | ||||||||
context : declarator-context? | ||||||||
base : complete-type? |
| ||||||||
→ (listof complete-member-declarator?) | ||||||||
contexts : (listof member-declarator-context?) | ||||||||
base : complete-type? |