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
The grammar provided in the ISO/IEC 9899:TC3 standard is mum about when typedef-name tokens can be used as identifier tokens. For example, all C parsers admit programs such as:
typedef int T; |
void proc(char T) { } |
despite the fact that T is a typedef-name and the grammar for procedure arguments requires argument declarator names to be identifier tokens.
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› ")" |
|
| | | ‹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› | ::= | "(" ‹DirectAbstractDeclarator› ")" |
|
| | | [‹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:2:1/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 |
(src-start src) → position? |
src : src? |
Extracts a source location’s start position as a position struct.
(src-end src) → position? |
src : src? |
Extracts a source location’s end position as a position struct.
(build-src start end path) → src? |
start : position? |
end : position? |
path : any |
Builds a source location struct from position structs.
(position-min p ) → position? |
p : position? |
Returns the least of the given positions p, i.e. the p with the least position-offset.
(position-max p ) → position? |
p : position? |
Returns the greatest of the given positions p, i.e. the p with the greatest position-offset.
(src-range src ) → src? |
src : src? |
Returns the smallest range that spans all the given source locations src.
(src->syntax x [datum original?]) → syntax? |
x : src? |
datum : any = '... |
original? : boolean? = #t |
Converts a source location to a syntax object, using datum as the syntax object’s underlying datum. If original? is #t, the generated syntax object has the syntax-original? property.
(id->syntax id [original?]) → syntax? |
id : id? |
original? : boolean? = #t |
Converts an identifier to a syntax object, using the identifier name as the syntax object’s underlying datum. If original? is #t, the generated syntax object has the syntax-original? property.
(primitive-type-specifier? x) → boolean? |
x : symbol? |
Indicates whether x is a primitive type specifier, which is one of the symbols 'void, 'char, 'short, 'int, 'long, 'float, 'double, 'signed, 'unsigned, '_Bool, or '_Complex.
(unary-operator? x) → boolean? |
x : symbol? |
Indicates whether x is a unary operator symbol, which is one of the symbols '&, '*, '+, '-, '~, or '!.
(binary-operator? x) → boolean? |
x : symbol? |
Indicates whether x is a binary operator symbol, which is one of the symbols '*, '/, '%, '+, '-, '<<, '>>, '<, '>, '<=, '>=, '==, '!=, '&, '^, '\|, '&&, or '\|\|.
(assignment-operator? x) → boolean? |
x : symbol? |
Indicates whether x is an assignment operator symbol, which is one of the symbols '=, '*=, '/=, '%=, '+=, '-=, '<<=, '>>=, '&=, '^=, or '\|=.
(increment-operator? x) → boolean? |
x : symbol? |
Indicates whether x is an increment/decrement operator symbol, which is one of the symbols '++ or '--.
2.2.2 Identifiers
(struct id (src)) |
src : (or/c src? #f) |
A C identifier, i.e., a variable name, type name, label name, or keyword.
(struct (id:var id) (name)) |
name : symbol? |
A variable or type name.
(struct (id:label id) (name)) |
name : symbol? |
A struct, union, or enum tag, a statement label, or a struct or union member name.
(struct (id:qualifier id) (name)) |
name : (or/c 'const 'restrict 'volatile) |
A type qualifier.
(struct (id:op id) (name)) |
name : (or/c unary-operator? binary-operator? assignment-operator? increment-operator?) |
A unary, binary, assignment, or increment/decrement operator.
(struct (id:storage id) (class)) |
class : (or/c 'typedef 'extern 'static 'auto 'register) |
A storage class specifier.
(struct (id:inline id) ()) |
The inline keyword.
(struct (id:ellipsis id) ()) |
The varargs keyword “...”.
(struct (id:star id) ()) |
The array-type modifier keyword “*”.
2.2.3 Expressions
(struct expr (src)) |
src : (or/c src? #f) |
A C expression.
(struct (expr:ref expr) (id)) |
id : id:var? |
A variable reference.
(struct (expr:int expr) (value qualifiers)) |
value : integer? |
qualifiers : (listof id:qualifier?) |
An integer literal.
(struct (expr:float expr) (value qualifiers)) |
value : inexact-real? |
qualifiers : (listof id:qualifier?) |
A floating-point literal.
(struct (expr:char expr) (source wide?)) |
source : string? |
wide? : boolean? |
A character literal.
(struct (expr:string expr) (source wide?)) |
source : string? |
wide? : boolean? |
A string literal.
(struct (expr:compound expr) (type inits)) |
type : type? |
inits : (listof (or/c init? (cons (listof dtor?) init?))) |
(struct (expr:array-ref expr) (expr offset)) |
expr : expr? |
offset : expr? |
An array dereference.
(struct (expr:call expr) (function arguments)) |
function : expr? |
arguments : (listof expr?) |
A function call.
(struct (expr:member expr) (expr label)) |
expr : expr? |
label : id:label? |
A struct or union member dereference.
(struct (expr:pointer-member expr) (expr label)) |
expr : expr? |
label : id:label? |
A struct- or union-pointer member dereference.
(struct (expr:postfix expr) (expr op)) |
expr : expr? |
op : increment-operator? |
A postfix increment or decrement.
(struct (expr:prefix expr) (op expr)) |
op : increment-operator? |
expr : expr? |
A prefix increment or decrement.
(struct (expr:cast expr) (type expr)) |
type : type? |
expr : expr? |
A type cast.
(struct (expr:sizeof expr) (term)) |
term : (or/c type? expr?) |
A sizeof expression.
(struct (expr:unop expr) (op expr)) |
op : unary-operator? |
expr : expr? |
A unary operator expression.
(struct (expr:binop expr) (left op right)) |
left : expr? |
op : binary-operator? |
right : expr? |
A binary operator expression.
(struct (expr:assign expr) (left op right)) |
left : expr? |
op : assignment-operator? |
right : expr? |
An assignment expression.
(struct (expr:begin expr) (left right)) |
left : expr? |
right : expr? |
A sequence expression.
(struct (expr:if expr) (test cons alt)) |
test : expr? |
cons : expr? |
alt : expr? |
A conditional expression.
2.2.4 Statements
(struct stmt (src)) |
src : (or/c src? #f) |
A C statement.
(struct (stmt:label stmt) (label stmt)) |
label : id:label? |
stmt : stmt? |
A labeled statement.
(struct (stmt:case stmt) (expr stmt)) |
expr : expr? |
stmt : stmt? |
A case statement.
(struct (stmt:default stmt) (stmt)) |
stmt : stmt? |
A default statement.
(struct (stmt:block stmt) (items)) |
items : (listof (or/c decl? stmt?)) |
A compound statement.
(struct (stmt:expr stmt) (expr)) |
expr : expr? |
An expression statement.
(struct (stmt:if stmt) (test cons alt)) |
test : expr? |
cons : stmt? |
alt : (or/c stmt? #f) |
An if statement.
(struct (stmt:switch stmt) (test body)) |
test : expr? |
body : stmt? |
A switch statement.
(struct (stmt:while stmt) (test body)) |
test : expr? |
body : stmt? |
A while statement.
(struct (stmt:do stmt) (body test)) |
body : stmt? |
test : expr? |
A do-while statement.
(struct (stmt:for stmt) (init test update body)) |
init : (or/c expr? decl? #f) |
test : (or/c expr? #f) |
update : (or/c expr? #f) |
body : stmt? |
A for statement.
(struct (stmt:goto stmt) (label)) |
label : id:label? |
A goto statement.
(struct (stmt:continue stmt) ()) |
A continue statement.
(struct (stmt:break stmt) ()) |
A break statement.
(struct (stmt:return stmt) (result)) |
result : (or/c expr? #f) |
A return statement.
(struct (stmt:empty stmt) ()) |
An empty statement.
2.2.5 Declarations
(struct decl (src)) |
src : (or/c src? #f) |
A C declaration.
(struct (decl:typedef decl) (type declarators)) |
type : type? |
declarators : (listof decl:declarator?) |
A type definition. Each of the declarators is a declarator context.
(struct (decl:vars decl) (storage-class type declarators)) |
storage-class : (or/c id:storage? #f) |
type : (or/c type? #f) |
declarators : (listof decl:declarator?) |
A variable declaration.
(struct (decl:formal decl) (storage-class type declarator)) |
storage-class : (or/c id:storage? #f) |
type : (or/c type? #f) |
declarator : decl:declarator? |
A formal argument declaration.
| ||||||||||||||||||||||||||||||
storage-class : (or/c id:storage? #f) | ||||||||||||||||||||||||||||||
inline? : (or/c id:inline? #f) | ||||||||||||||||||||||||||||||
return-type : type? | ||||||||||||||||||||||||||||||
formals : (listof decl:formal?) | ||||||||||||||||||||||||||||||
preamble : (or/c (listof decl?) #f) | ||||||||||||||||||||||||||||||
body : stmt:block? |
A function definition.
(struct (decl:declarator decl) (id type initializer)) |
id : (or/c id:var? #f) |
type : (or/c type? #f) |
initializer : (or/c init? #f) |
A declarator, i.e., a single variable binding within a variable declaration.
There are two classes of declarator:
A declarator context has a type context as its type field.
A complete declarator has a complete type as its type field.
(struct (decl:member-declarator decl) (id type initializer bit-size)) |
id : (or/c id:label? #f) |
type : (or/c type? #f) |
initializer : (or/c init? #f) |
bit-size : (or/c expr? #f) |
A member declarator, i.e., a single member definition within a struct or union definition. There are two classes of member declarator:
A member declarator context has a type context as its type field.
A complete member declarator has a complete type as its type field.
(struct (decl:member decl) (type declarators)) |
type : (or/c type? #f) |
declarators : (listof decl:declarator?) |
A member declaration within a struct or union definition.
2.2.6 Initializers
(struct init (src)) |
src : (or/c src? #f) |
A C initializer.
(struct (init:compound init) (elements)) |
elements : (listof (or/c init? (cons (listof dtor?) init?))) |
A C99 compound initializer.
(struct (init:expr init) (expr)) |
expr : expr? |
An expression initializer.
2.2.7 Designators
(struct dtor (src)) |
src : (or/c src? #f) |
A C99 designator.
(struct (dtor:array dtor) (expr)) |
expr : expr? |
An array designator.
(struct (dtor:member dtor) (label)) |
label : id:label? |
A struct or union member designator.
2.2.8 Types
(struct type (src)) |
src : (or/c src? #f) |
A C type.
(struct (type:primitive type) (name)) |
name : (or/c primitive-type-specifier? (listof primitive-type-specifier?)) |
A primitive type. The name field can be one of:
'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)
(struct (type:ref type) (id)) |
id : id:var? |
A reference to a typedef name.
(struct (type:struct type) (tag fields)) |
tag : id:label? |
fields : (or/c (listof decl:member?) #f) |
A struct type.
(struct (type:union type) (tag variants)) |
tag : id:label? |
variants : (or/c (listof decl:member?) #f) |
A union type.
(struct (type:enum type) (tag variants)) |
tag : id:label? |
variants : (or/c (listof (or/c id:var? (cons id:var? expr?))) #f) |
An enum type.
(struct (type:array type) (base static? qualifiers length star?)) |
base : type? |
static? : (or/c id:static? #f) |
qualifiers : (listof id:qualifier?) |
length : (or/c expr? #f) |
star? : (or/c id:star? #f) |
An array type.
(struct (type:pointer type) (base qualifiers)) |
base : type? |
qualifiers : (listof id:qualifier?) |
A pointer type.
(struct (type:function type) (return formals)) |
return : type? |
formals : (listof (or/c decl:formal? id:ellipsis?)) |
A function type.
(struct (type:qualified type) (type qualifiers)) |
type : (or/c type? #f) |
qualifiers : (listof id:qualifier?) |
A qualified type.
2.2.9 Type Contexts
The peculiar syntax of declarations in C leads to a particular notion of type context. A type context is a type with a “hole,” represented by the value #f. For example, in the C declaration
typedef int A[32], *PA[32]; |
there are two declared types, A and PA, each of which is formed by plugging the base type int into the respective type contexts __[32] and *__[32].
More precisely, a type context is one of:
#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.
A complete type is a type with no holes.
(apply-type-context context base) → complete type |
context : type context |
base : complete type |
Plugs the type base into the hole of context to obtain a complete type.
(apply-declarators base declarators) |
→ (listof complete declarator) |
base : complete type |
declarators : (listof declarator context) |
Plugs the type base into each of the holes of declarators to obtain a list of complete declarators.
(apply-member-declarators base declarators) |
→ (listof complete member declarator) |
base : complete type |
declarators : (listof member declarator context) |
Plugs the type base into each of the holes of declarators to obtain a list of complete member declarators.