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 c/ast) | package: c-utils |
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.
struct
(struct src ( start-offset start-line start-col end-offset end-line end-col path) #:extra-constructor-name make-src) 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
procedure
(position-min p ...+) → position?
p : position?
procedure
(position-max p ...+) → position?
p : position?
procedure
(src->syntax x [datum original?]) → syntax?
x : src? datum : any = '... original? : boolean? = #t
procedure
(id->syntax id [original?]) → syntax?
id : id? original? : boolean? = #t
procedure
x : symbol?
procedure
(unary-operator? x) → boolean?
x : symbol?
procedure
(binary-operator? x) → boolean?
x : symbol?
procedure
(assignment-operator? x) → boolean?
x : symbol?
procedure
(increment-operator? x) → boolean?
x : symbol?
2.2.2 Identifiers
struct
(struct id:var id (name) #:extra-constructor-name make-id:var) name : symbol?
struct
(struct id:label id (name) #:extra-constructor-name make-id:label) name : symbol?
struct
(struct id:qualifier id (name) #:extra-constructor-name make-id:qualifier) name : (or/c 'const 'restrict 'volatile)
struct
(struct id:op id (name) #:extra-constructor-name make-id:op) name : (or/c unary-operator? binary-operator? assignment-operator? increment-operator?)
struct
(struct id:storage id (class) #:extra-constructor-name make-id:storage) class : (or/c 'typedef 'extern 'static 'auto 'register)
struct
(struct id:inline id () #:extra-constructor-name make-id:inline)
struct
(struct id:ellipsis id () #:extra-constructor-name make-id:ellipsis)
struct
(struct id:star id () #:extra-constructor-name make-id:star)
2.2.3 Expressions
struct
(struct expr:ref expr (id) #:extra-constructor-name make-expr:ref) id : id:var?
struct
(struct expr:int expr (value qualifiers) #:extra-constructor-name make-expr:int) value : integer? qualifiers : (listof id:qualifier?)
struct
(struct expr:float expr (value qualifiers) #:extra-constructor-name make-expr:float) value : inexact-real? qualifiers : (listof id:qualifier?)
struct
(struct expr:char expr (source wide?) #:extra-constructor-name make-expr:char) source : string? wide? : boolean?
> (parse-expression "'\\n'") '#s((expr:char expr 1) #s(src 1 1 0 5 1 4 #f) "\\n" #f)
struct
(struct expr:string expr (source wide?) #:extra-constructor-name make-expr:string) source : string? wide? : boolean?
> (parse-expression "\"foo\\nbar\"") '#s((expr:string expr 1) #s(src 1 1 0 11 1 10 #f) "foo\\nbar" #f)
struct
(struct expr:compound expr (type inits) #:extra-constructor-name make-expr:compound) type : type? inits : (listof (or/c init? (cons (listof dtor?) init?)))
struct
(struct expr:array-ref expr (expr offset) #:extra-constructor-name make-expr:array-ref) expr : expr? offset : expr?
struct
(struct expr:call expr (function arguments) #:extra-constructor-name make-expr:call) function : expr? arguments : (listof expr?)
struct
(struct expr:member expr (expr label) #:extra-constructor-name make-expr:member) expr : expr? label : id:label?
struct
(struct expr:pointer-member expr (expr label) #:extra-constructor-name make-expr:pointer-member) expr : expr? label : id:label?
struct
(struct expr:postfix expr (expr op) #:extra-constructor-name make-expr:postfix) expr : expr? op : id:op?
struct
(struct expr:prefix expr (op expr) #:extra-constructor-name make-expr:prefix) op : id:op? expr : expr?
struct
(struct expr:cast expr (type expr) #:extra-constructor-name make-expr:cast) type : type? expr : expr?
struct
(struct expr:sizeof expr (term) #:extra-constructor-name make-expr:sizeof) term : (or/c type? expr?)
struct
(struct expr:unop expr (op expr) #:extra-constructor-name make-expr:unop) op : id:op? expr : expr?
struct
(struct expr:binop expr (left op right) #:extra-constructor-name make-expr:binop) left : expr? op : id:op? right : expr?
struct
(struct expr:assign expr (left op right) #:extra-constructor-name make-expr:assign) left : expr? op : id:op? right : expr?
struct
(struct expr:begin expr (left right) #:extra-constructor-name make-expr:begin) left : expr? right : expr?
struct
(struct expr:if expr (test cons alt) #:extra-constructor-name make-expr:if) test : expr? cons : expr? alt : expr?
2.2.4 Statements
struct
(struct stmt:label stmt (label stmt) #:extra-constructor-name make-stmt:label) label : id:label? stmt : stmt?
struct
(struct stmt:case stmt (expr stmt) #:extra-constructor-name make-stmt:case) expr : expr? stmt : stmt?
struct
(struct stmt:default stmt (stmt) #:extra-constructor-name make-stmt:default) stmt : stmt?
struct
(struct stmt:block stmt (items) #:extra-constructor-name make-stmt:block) items : (listof (or/c decl? stmt?))
struct
(struct stmt:expr stmt (expr) #:extra-constructor-name make-stmt:expr) expr : expr?
struct
(struct stmt:if stmt (test cons alt) #:extra-constructor-name make-stmt:if) test : expr? cons : stmt? alt : (or/c stmt? #f)
struct
(struct stmt:switch stmt (test body) #:extra-constructor-name make-stmt:switch) test : expr? body : stmt?
struct
(struct stmt:while stmt (test body) #:extra-constructor-name make-stmt:while) test : expr? body : stmt?
struct
(struct stmt:do stmt (body test) #:extra-constructor-name make-stmt:do) body : stmt? test : expr?
struct
(struct stmt:for stmt (init test update body) #:extra-constructor-name make-stmt:for) init : (or/c expr? decl? #f) test : (or/c expr? #f) update : (or/c expr? #f) body : stmt?
struct
(struct stmt:goto stmt (label) #:extra-constructor-name make-stmt:goto) label : id:label?
struct
(struct stmt:continue stmt () #:extra-constructor-name make-stmt:continue)
struct
(struct stmt:break stmt () #:extra-constructor-name make-stmt:break)
struct
(struct stmt:return stmt (result) #:extra-constructor-name make-stmt:return) result : (or/c expr? #f)
struct
(struct stmt:empty stmt () #:extra-constructor-name make-stmt:empty)
2.2.5 Declarations
struct
(struct decl:typedef decl (type declarators) #:extra-constructor-name make-decl:typedef) type : type? declarators : (listof declarator-context?)
struct
(struct decl:vars decl (storage-class type declarators) #:extra-constructor-name make-decl:vars) storage-class : (or/c id:storage? #f) type : (or/c type? #f) declarators : (listof declarator-context?)
struct
(struct decl:formal decl (storage-class type declarator) #:extra-constructor-name make-decl:formal) storage-class : (or/c id:storage? #f) type : (or/c type? #f) declarator : (or/c declarator-context? type-context?)
struct
(struct decl:function decl ( storage-class inline? return-type declarator preamble body) #:extra-constructor-name make-decl:function) 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?
struct
(struct decl:declarator decl (id type initializer) #:extra-constructor-name make-decl:declarator) id : (or/c id:var? #f) type : (or/c type? #f) initializer : (or/c init? #f)
procedure
(declarator-context? x) → boolean?
x : any
procedure
(complete-declarator? x) → boolean?
x : any
struct
(struct decl:member-declarator decl (id type initializer bit-size) #:extra-constructor-name make-decl:member-declarator) id : (or/c id:label? #f) type : (or/c type? #f) initializer : (or/c init? #f) bit-size : (or/c expr? #f)
procedure
x : any
procedure
x : any
struct
(struct decl:member decl (type declarators) #:extra-constructor-name make-decl:member) type : (or/c type? #f) declarators : (listof decl:declarator?)
2.2.6 Initializers
struct
(struct init:compound init (elements) #:extra-constructor-name make-init:compound) elements : (listof (or/c init? (cons (listof dtor?) init?)))
struct
(struct init:expr init (expr) #:extra-constructor-name make-init:expr) expr : expr?
2.2.7 Designators
struct
(struct dtor:array dtor (expr) #:extra-constructor-name make-dtor:array) expr : expr?
struct
(struct dtor:member dtor (label) #:extra-constructor-name make-dtor:member) label : id:label?
2.2.8 Types
struct
(struct type:primitive type (name) #:extra-constructor-name make-type:primitive) 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)
struct
(struct type:ref type (id) #:extra-constructor-name make-type:ref) id : id:var?
struct
(struct type:struct type (tag fields) #:extra-constructor-name make-type:struct) tag : id:label? fields : (or/c (listof decl:member?) #f)
struct
(struct type:union type (tag variants) #:extra-constructor-name make-type:union) tag : id:label? variants : (or/c (listof decl:member?) #f)
struct
(struct type:enum type (tag variants) #:extra-constructor-name make-type:enum) tag : id:label? variants : (or/c (listof (or/c id:var? (cons id:var? expr?))) #f)
struct
(struct type:array type (base static? qualifiers length star?) #:extra-constructor-name make-type:array) base : type? static? : (or/c id:static? #f) qualifiers : (listof id:qualifier?) length : (or/c expr? #f) star? : (or/c id:star? #f)
struct
(struct type:pointer type (base qualifiers) #:extra-constructor-name make-type:pointer) base : type? qualifiers : (listof id:qualifier?)
struct
(struct type:function type (return formals) #:extra-constructor-name make-type:function) return : type? formals : (listof (or/c decl:formal? id:ellipsis?))
struct
(struct type:qualified type (type qualifiers) #:extra-constructor-name make-type:qualified) 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.
procedure
(type-context? x) → boolean?
x : any
procedure
(complete-type? x) → boolean?
x : any
procedure
(apply-type-context context base) → complete-type?
context : type-context? base : complete-type?
procedure
(apply-declarator-context context base) → complete-declarator?
context : declarator-context? base : complete-type?
procedure
(apply-declarator-contexts contexts base)
→ (listof complete-declarator?) contexts : (listof declarator-context?) base : complete-type?
procedure
(apply-member-declarator-context context base) → complete-member-declarator? context : declarator-context? base : complete-type?
procedure
(apply-member-declarator-contexts contexts base) → (listof complete-member-declarator?) contexts : (listof member-declarator-context?) base : complete-type?