"This takes a restricted, low-level oriented usage of Slate code, and transforms it into embeddable (human-readable) C program code." C addPrototype: #SimpleGenerator derivedFrom: {C Writer}. "Generates C code from flattened IR code or restricted-use Slate source code. The results are collected into the program Module, which also maintains its own structural information." C SimpleGenerator addSlot: #inlining valued: True. "Whether to perform inlining of function calls." C SimpleGenerator addSlot: #asserting valued: False. "Whether to include assert: calls as C assertions." C SimpleGenerator addSlot: #verbose valued: False. "Whether to print verbose notes in the output." C SimpleGenerator addSlot: #useSymbolicConstants valued: True. "Whether the generate C constant declarations or fold the values in." C SimpleGenerator addSlot: #useRightShiftForDivide valued: True. "Whether to attempt to generate optimized shift-based division code." C SimpleGenerator addSlot: #generateDeadCode valued: False. "Whether to not eliminate dead code." C SimpleGenerator addSlot: #methodCalls valued: Bag newEmpty. "The number of times each Method is called." C SimpleGenerator addSlot: #module. "The Module currently being generated." C SimpleGenerator addSlot: #scope valued: Stack newEmpty. "The stack of scopes (FunctionDefs and Blocks)." g@(C SimpleGenerator traits) newEmpty [| newG | newG: g clone. newG methodCalls: g methodCalls newEmpty. newG scope: g scope newEmpty. newG ]. "Maps common Slate binary selectors to String names for C functions which indicate the same operation." C SimpleGenerator traits addSlot: #binarySelectorNames valued: (IdentityDictionary newSize: 17). { #= -> 'Equals'. #+ -> 'Plus'. #- -> 'Minus'. #* -> 'Times'. #/ -> 'DivideBy'. #\\ -> 'RemainderWith'. #>> -> 'RightArithmeticShiftBy'. #>> -> 'RightShiftBy'. #<< -> 'LeftShiftBy'. #/\ -> 'And'. #\/ -> 'Or'. #< -> 'LessThan'. #> -> 'GreaterThan'. #<= -> 'LessThanOrEqual'. #>= -> 'GreaterThanOrEqual' } do: [| :each | C SimpleGenerator traits binarySelectorNames add: each]. "Maps Slate selectors equivalent to primitive C operations into those operations' names." C SimpleGenerator traits addSlot: #selectorToInfixCNames valued: (IdentityDictionary newSize: 11). { #+ -> #+ . #- -> #- . #* -> #* . #/ -> #/ . #// -> #/ . #\\ -> #% . #\/ -> #'||' . #/\ -> #'&&' . #= -> #== . #~= -> #'!=' . #> -> #> . #< -> #< . #>= -> #>= . #<= -> #<= . #<< -> #<< . #>> -> #>> . #bitAnd: -> #'&' . #bitOr: -> #'|' . #bitXor: -> #^ . #mod: -> #% } do: [| :each | C SimpleGenerator traits selectorToInfixCNames add: each]. C SimpleGenerator traits addSlot: #selectorToPrefixCNames valued: (IdentityDictionary newSize: 2). { #not -> #'!' . #bitNot -> #~ . #negated -> #- . } do: [| :each | C SimpleGenerator traits selectorToPrefixCNames add: each]. obj@(Root traits) addSlot: slotName type: _ "This is a dummy method which discards the type for now. In pidgin, it is evaluated and added as an attribute of the structure." [obj addSlot: slotName]. store@(Syntax StoreVariable traits) isUpdatingAssignment "Returns whether the sub-tree just performs one binary operation on the variable and stores the result back in to the same variable." [| expr | expr: store value. (expr is: Syntax BinaryMessage) and: [expr arguments first isSameAs: Syntax LoadVariable] and: [expr arguments first name = store variable name] and: [C Syntax OpAssignment selectors includes: expr selector] ]. store@(Syntax StoreVariable traits) isIncrementOrDecrement "Determines whether this is a candidate for C's increment/decrement operations. ASSUME: store isUpdatingAssignment = True." [ ({#+. #-} includes: store value selector) and: [store value arguments second isSameAs: Syntax Literal] and: [store value arguments second value = 1] ]. g@(C SimpleGenerator traits) callCountOf: function "Uses the methodCalls Bag to quickly find the number of calls." [ g methodCalls occurrencesOf: function selector ]. g@(C SimpleGenerator traits) shouldInline: function "Answer whether the generator should inline the given function. It's based on the body expression's size and the number of times it is called (a heuristic to avoid bloating the code too much)." [ function body nodeCount * (g callCountOf: function) <= 200 ]. g@(C SimpleGenerator traits) cNameForRole: obj "The word used in a function name to delineate the dispatch variation for the object." [ obj == NoRole ifTrue: [''] ifFalse: [g cNameForRole: (obj cName as: String)] ]. g@(C SimpleGenerator traits) cNameForRole: str@(String traits) [ (str includesAnyOf: ' ') ifTrue: [(str splitWith: ' ') reduce: [| :x :y | x ; y capitalize]] ifFalse: [str] ]. _@(C SimpleGenerator traits) cNameForRole: _@Nil [ '' ]. g@(C SimpleGenerator traits) cNameForRole: p@(Types C Pointer) [ 'P' ; (g cNameForRole: p targetType) ]. _@(C SimpleGenerator traits) cNameForRole: s@(Types C Structure) [ 'S' ; (s cName as: String) ]. g@(C SimpleGenerator traits) cFunctionNameFor: method on: roleObjects "Generates a String function name for the method, using selector and arguments or argument types." [| sel selReader result | sel: method selector. selReader: sel name reader. result: (String newSizeOf: selReader collection) writer. sel isUnarySelector ifTrue: [ sel name first = $_ ifTrue: [result ; sel name] ifFalse: [result ; (g cNameForRole: roleObjects first) ; '_' ; sel name] ]. sel isBinarySelector ifTrue: [result ; (g cNameForRole: roleObjects first) ; '_' ; (g binarySelectorNames at: sel) ; '_' ; (g cNameForRole: roleObjects second)]. "Now handle the keyword case." sel isKeywordSelector ifTrue: [result ; (g cNameForRole: roleObjects first) ; '_'. roleObjects allButFirst: 1 do: [| :arg | selReader atEnd ifFalse: [result ; (selReader upTo: $:)]. result ; (g cNameForRole: arg) ; '_']]. result contents intern ]. g@(C SimpleGenerator traits) process: node@(Syntax Node traits) "The Pidgin toy evaluator; root method." [node evaluateIn: g]. _@(Syntax ImplicitArgument traits) evaluateIn: _@(C SimpleGenerator traits) [ C currentModule ifNil: [lobby] ifNotNil: [C currentModule namespace] ]. method@(Syntax MethodDefinition traits) evaluateIn: g@(C SimpleGenerator traits) "This sets up the C-generation state for a particular method." [| newFun targetName roleObjects | roleObjects: (method roles with: method inputVariables collect: [| :role :var type | type: (role evaluateIn: g). type == NoRole ifFalse: [var type: type]. var type == Types Any ifTrue: [var type: Types C UnsignedLongInt]. type ]). targetName: (g cFunctionNameFor: method on: roleObjects). Console ; 'Processing method ' ; (targetName as: String) ; '...\n'. newFun: (C Syntax FunctionDef of: targetName on: (method inputVariables collect: [| :var | C Syntax VariableDef of: var name init: Nil type: var type]) type: (method type == Types Any ifTrue: [Types C Void] ifFalse: [method type])). newFun body: method. C currentModule ifNil: [error: 'C method not defined in a module!']. C currentModule methods at: targetName put: newFun. [| *_ | newFun] asMethod: method selector on: (roleObjects collect: [| :type | type == NoRole ifTrue: [NoRole] ifFalse: [type dispatcher]]). [| *_ | newFun type] asMethod: method selector on: (roleObjects collect: [| :type | type == NoRole ifTrue: [NoRole] ifFalse: [type rules]]). newFun ]. g@(C SimpleGenerator traits) generateCStatementFor: node "The default case: handle it as an expression." [Console ; 'statement fallback...\n'. g generateCFor: node]. g@(C SimpleGenerator traits) generateCFor: ann@(Syntax Annotation traits) [g generateCFor: ann value]. g@(C SimpleGenerator traits) generateCFor: literal@(Syntax Literal traits) [ literal value as: C Syntax Literal ]. g@(C SimpleGenerator traits) generateCStatementFor: literal@(Syntax Literal traits) [ C Syntax Empty ]. g@(C SimpleGenerator traits) generateCFor: function@(C Syntax FunctionDef traits) [ Console ; 'generating function...\n'. function body: (g generateCFor: function body). function ]. g@(C SimpleGenerator traits) generateCFor: selector@(Symbol traits) on: arguments [| type opSymbol args fun | Console ; 'checking infixes...\n'. opSymbol: (g selectorToInfixCNames at: selector ifAbsent: [Nil]). opSymbol ifNotNil: [^ (C Syntax Infix calling: opSymbol on: (arguments collect: [| :arg | g generateCFor: arg]))]. Console ; 'checking prefixes...\n'. opSymbol: (g selectorToPrefixCNames at: selector ifAbsent: [Nil]). opSymbol ifNotNil: [^ (C Syntax Prefix calling: opSymbol on: (g generateCFor: arguments first))]. Console ; 'checking accessors...\n'. arguments first == Syntax ImplicitArgument ifTrue: [| ref | arguments size = 2 ifTrue: [selector: selector name allButLast intern]. g module constants at: selector ifPresent: [| :const | ref: (C Syntax ConstantRef of: const name type: const type)]. g module globals at: selector ifPresent: [| :global | ref: (C Syntax GlobalRef of: global name type: global type)]. ref ifNil: [error: 'Undefined variable reference: ' ; (selector as: String)]. arguments size = 1 ifTrue: [^ ref] ifFalse: [^ (C Syntax Assignment of: (g generateCFor: arguments second) into: ref)] ]. type: arguments first type. ((type isSameAs: Types C Structure) or: [(type isSameAs: Types C Pointer) and: [(type: type targetType) isSameAs: Types C Structure]]) ifTrue: [| name | Console ; 'generating access...\n'. name: (selector name last = $: ifTrue: [selector name allButLast intern] ifFalse: [selector]). (type elementSpecs detect: [| :spec | spec cName = name]) ifNotNil: [| element | (arguments first type isSameAs: Types C Pointer) ifTrue: [element: (C Syntax PointAt from: (g generateCFor: arguments first) type: type named: name)] ifFalse: [element: (C Syntax Select from: (g generateCFor: arguments first) type: type named: name)]. Console ; 'generated load of ' ; name name ; '!\n'. arguments size = 1 ifTrue: [^ element]. Console ; 'generating mutation...\n'. ^ (C Syntax Assignment of: (g generateCFor: arguments second) into: element) ] ]. Console ; 'searching for function ' ; selector name ; '...\n'. fun: (selector findOn: (arguments collect: [| :arg | (arg type is: Types C Type) ifTrue: [arg type dispatcher] ifFalse: [Types C UnsignedLongInt dispatcher] ])). fun ifNil: [error: 'A method translation wasn\'t found for ' ; selector name ; '.']. fun: (fun applyTo: arguments). Console ; 'generating call arguments...\n'. args: (arguments with: fun args collect: [| :arg :param | Console ; 'generating argument...\n'. arg type = param type ifTrue: [g generateCFor: arg] ifFalse: [Console ; 'casting...\n'. C Syntax Cast of: (g generateCFor: arg) to: param type] ]). Console ; 'done with function call!\n'. g methodCalls add: fun. C Syntax FunctionCall applying: fun to: args ]. g@(C SimpleGenerator traits) generateCStatementFor: selector@(Symbol traits) on: arguments "Most syntax forms don't have a statement/expression variation." [Console ; 'on: fallback...\n'. g generateCFor: selector on: arguments]. g@(C SimpleGenerator traits) generateCFor: _@#directly on: args [ C Syntax Direct for: args first value ]. g@(C SimpleGenerator traits) generateCFor: _@#applyTo: on: args [ C Syntax FunctionCall applying: (g generateCFor: args first) to: (args second statements collect: [| :arg | g generateCFor: arg]) ]. g@(C SimpleGenerator traits) generateCFor: _@#assert: on: args [ C Syntax FunctionCall applying: #ASSERT to: {g generateCFor: args second} ]. g@(C SimpleGenerator traits) generateCFor: _@#error: on: args [ C Syntax FunctionCall applying: #error to: {args second value} ]. g@(C SimpleGenerator traits) generateCFor: _@#break on: args [ C Syntax Break ]. g@(C SimpleGenerator traits) generateCFor: _@#address on: args [ C Syntax AddressOf of: (g generateCFor: args first) ]. g@(C SimpleGenerator traits) generateCFor: _@#load on: args [ C Syntax Dereference of: (g generateCFor: args first) ]. g@(C SimpleGenerator traits) generateCFor: _@#store: on: args [ C Syntax Assignment of: (g generateCFor: args second) into: (C Syntax Dereference of: (g generateCFor: args first)) ]. g@(C SimpleGenerator traits) generateCStatementFor: _@#ifTrue: on: args [ C Syntax IfThenElse on: (g generateCFor: args first) then: (g generateCFor: args second) ]. g@(C SimpleGenerator traits) generateCStatementFor: _@#ifFalse: on: args [ C Syntax IfThenElse on: (g generateCFor: args first) then: Nil else: (g generateCFor: args second) ]. g@(C SimpleGenerator traits) generateCStatementFor: _@#ifTrue:ifFalse: on: args [ C Syntax IfThenElse on: (g generateCFor: args first) then: (g generateCFor: args second) else: (g generateCFor: args third) ]. g@(C SimpleGenerator traits) generateCFor: _@#ifTrue: on: args [ C Syntax Conditional on: (g generateCFor: args first) then: (g generateCFor: args second statements first) ]. g@(C SimpleGenerator traits) generateCFor: _@#ifFalse: on: args [ C Syntax Conditional on: (g generateCFor: args first) then: Nil else: (g generateCFor: args second statements first) ]. g@(C SimpleGenerator traits) generateCFor: _@#ifTrue:ifFalse: on: args [ C Syntax Conditional on: (g generateCFor: args first) then: (g generateCFor: args second statements first) else: (g generateCFor: args third statements first) ]. g@(C SimpleGenerator traits) generateCFor: _@#whileTrue: on: args [ C Syntax WhileLoop doing: (g generateCStatementFor: args second) while: (g generateCFor: args first) ]. g@(C SimpleGenerator traits) generateCFor: _@#whileTrue on: args [| scope body test | scope: C Syntax Block newEmpty. body: (g generateCFor: args first). scope declarations: body declarations. body declarations: body declarations newEmpty. test: body statements last. body statements: body statements allButLast. scope statements: { C Syntax DoWhileLoop doing: body while: test }. scope ]. g@(C SimpleGenerator traits) generateCFor: _@#whileFalse: on: args [ C Syntax WhileLoop doing: (g generateCStatementFor: args second) while: (g generateCFor: args first) not ]. g@(C SimpleGenerator traits) generateCFor: _@#whileFalse on: args [| scope body test | scope: C Syntax Block newEmpty. body: (g generateCFor: args first). scope declarations: body declarations. body declarations: body declarations newEmpty. test: body statements last. body statements: body statements allButLast. scope statements: { C Syntax DoWhileLoop doing: body while: test not }. scope ]. g@(C SimpleGenerator traits) generateCFor: _@#loop on: args [ C Syntax WhileLoop doing: (g generateCStatementFor: args first) while: (g generateCFor: (Syntax Literal for: True)) ]. g@(C SimpleGenerator traits) generateCFor: _@#max: on: args [| arguments | arguments: (args collect: [| :arg | g generateCFor: arg]). C Syntax Conditional on: (C Syntax Infix calling: #< on: arguments) then: arguments second else: arguments first ]. g@(C SimpleGenerator traits) generateCFor: _@#min: on: args [| arguments | arguments: (args collect: [| :arg | g generateCFor: arg]). C Syntax Conditional on: (C Syntax Infix calling: #< on: arguments) then: arguments first else: arguments second ]. g@(C SimpleGenerator traits) generateCFor: _@#upTo:do: on: args [ g generateCFor: #to:by:do: on: {args first. args second. Syntax Literal for: 1. args third} ]. g@(C SimpleGenerator traits) generateCFor: _@#downTo:do: on: args [ g generateCFor: #to:by:do: on: {args first. args second. Syntax Literal for: -1. args third} ]. g@(C SimpleGenerator traits) generateCFor: _@#below:do: on: args [ g generateCFor: #to:by:do: on: {args first. Syntax Message sending: #- to: {args second. Syntax Literal for: 1}. Syntax Literal for: 1. args third} ]. g@(C SimpleGenerator traits) generateCFor: _@#above:do: on: args [ g generateCFor: #to:by:do: on: {args first. Syntax Message sending: #+ to: {args second. Syntax Literal for: 1}. Syntax Literal for: -1. args third} ]. g@(C SimpleGenerator traits) generateCFor: _@#to:by:do: on: args [| scope body arguments counterVar stopVar iterVar | arguments: (args collect: [| :arg | g generateCFor: arg]). iterVar: (arguments fourth variableNamed: args fourth inputVariables first name). arguments last declarations removeKey: iterVar name. scope: C Syntax Block newEmpty. counterVar: (scope define: #_i_ as: arguments first type: iterVar type). stopVar: (scope define: #_j_ as: (C Syntax Infix calling: #+ on: {arguments second. arguments third}) type: iterVar type). body: C Syntax Block newEmpty. body declarations at: iterVar name put: iterVar. body statements: { arguments fourth }. iterVar init: (C Syntax VariableRef of: counterVar name type: counterVar type). scope statements: { C Syntax ForLoop from: C Syntax Empty while: (((arguments third is: C Syntax Literal) ifTrue: [C Syntax Comparison forOp: (arguments third value > 0 ifTrue: [#<] ifFalse: [#>])] ifFalse: [C Syntax NotEquals]) on: {C Syntax VariableRef of: counterVar name type: counterVar type. C Syntax VariableRef of: stopVar name type: stopVar type}) by: (C Syntax OpAssignment of: #+= into: (C Syntax VariableRef of: counterVar name type: counterVar type) by: arguments third) doing: body }. scope ]. g@(C SimpleGenerator traits) generateCFor: _@#caseOf: on: args "Generates a CaseSwitch statement. This does not insert the required break; statements because the printer does this for us." [| switch | switch: C Syntax CaseSwitch clone. switch value: (g generateCFor: args first). switch cases: (switch cases newSizeOf: args second statements). args second statements doWithIndex: [| :each :index key | "Ensure constants' literal values are used here instead of constant refs so C compilers won't barf." key: (g generateCFor: each arguments first). (key isSameAs: C Syntax ConstantRef) ifTrue: [key: (g module constants at: key name) init]. switch cases at: index put: key -> (g generateCFor: each arguments second)]. switch ]. g@(C SimpleGenerator traits) generateCFor: _@#caseOf:otherwise: on: args "Generates a CaseSwitch statement. This does not insert the required break; statements because the printer does this for us." [| switch | switch: (g generateCFor: #caseOf on: args allButLast). switch otherwise: (g generateCFor: args third). switch ]. g@(C SimpleGenerator traits) generateCFor: _@#at: on: args [| arguments | arguments: (args collect: [| :arg | g generateCFor: arg]). arguments first at: arguments second ]. g@(C SimpleGenerator traits) generateCFor: _@#at:put: on: args "TODO: check and handle OpAssignment." [| arguments | arguments: (args collect: [| :arg | g generateCFor: arg]). C Syntax Assignment of: arguments third into: (arguments first at: arguments second) ]. g@(C SimpleGenerator traits) generateCFor: _@#cast on: args [C Syntax Cast of: (g generateCFor: args first) to: args first type]. g@(C SimpleGenerator traits) generateCFor: _@#longAt: on: args [g generateCFor: #at: on: {C Syntax Cast of: args first to: Types C UnsignedLongInt pointer. args second}]. g@(C SimpleGenerator traits) generateCFor: _@#longAt:put: on: args [g generateCFor: #at:put: on: {C Syntax Cast of: args first to: Types C UnsignedLongInt pointer. args second. args third}]. g@(C SimpleGenerator traits) generateCFor: _@#isNil on: args [ C Syntax Equals on: {g generateCFor: args first. C Syntax ConstantRef of: #Nil type: args first type} ]. g@(C SimpleGenerator traits) generateCFor: _@#isNotNil on: args [ C Syntax NotEquals on: {g generateCFor: args first. C Syntax ConstantRef of: #Nil type: args first type} ]. g@(C SimpleGenerator traits) generateCStatementFor: _@#ifNil: on: args [ C Syntax IfThenElse on: (g generateCFor: #isNil on: {args first}) then: (g generateCFor: args second) ]. g@(C SimpleGenerator traits) generateCStatementFor: _@#ifNotNil: on: args [ C Syntax IfThenElse on: (g generateCFor: #isNotNil on: {args first}) then: (g generateCFor: args second) ]. g@(C SimpleGenerator traits) generateCStatementFor: _@#ifNil:ifNotNil: on: args [ C Syntax IfThenElse on: (g generateCFor: #isNil on: {args first}) then: (g generateCFor: args second) else: (g generateCFor: args third) ]. g@(C SimpleGenerator traits) generateCFor: _@#ifNil: on: args [ C Syntax Conditional on: (g generateCFor: #isNil on: {args first}) then: (g generateCFor: args second statements first) ]. g@(C SimpleGenerator traits) generateCFor: _@#ifNotNil: on: args [ C Syntax Conditional on: (g generateCFor: #isNotNil on: {args first}) then: (g generateCFor: args second statements first) ]. g@(C SimpleGenerator traits) generateCFor: _@#ifNil:ifNotNil: on: args [ C Syntax Conditional on: (g generateCFor: #isNil on: {args first}) then: (g generateCFor: args second statements first) else: (g generateCFor: args third statements first) ]. g@(C SimpleGenerator traits) generateCFor: p@(Syntax Parenthesis traits) [ p statements size = 1 ifFalse: [error: 'Parentheses with more than one (or no) statement(s) are not supported.']. g generateCFor: p statements first ]. g@(C SimpleGenerator traits) generateCFor: m@(Syntax Message traits) [ Console ; 'generating message ' ; m selector name ; '\n'. g generateCFor: m selector on: m arguments ]. g@(C SimpleGenerator traits) generateCStatementFor: m@(Syntax Message traits) [ Console ; 'generating message statement ' ; m selector name ; '\n'. g generateCStatementFor: m selector on: m arguments ]. g@(C SimpleGenerator traits) generateCFor: store@(Syntax StoreVariable traits) [ Console ; 'generating store...\n'. store isUpdatingAssignment ifTrue: [store isIncrementOrDecrement ifTrue: [^ (C Syntax Prefix calling: (store value selector == #+ ifTrue: [#++] ifFalse: [#--]) on: store variable)]. C Syntax OpAssignment of: (store value selector name ; '=') intern into: store variable name by: (g generateCFor: store value arguments second)] ifFalse: [C Syntax Assignment of: (g generateCFor: store value) into: store variable name] ]. g@(C SimpleGenerator traits) variableNamed: name [ g scope reverseDo: [| :scope | (scope variableNamed: name) ifNotNilDo: [| :var | ^ var] ]. error: 'Unknown variable: ' ; (name as: String) ; '.' ]. g@(C SimpleGenerator traits) generateCFor: load@(Syntax LoadVariable traits) [ Console ; 'generating load of ' ; load variable name name ; '...\n'. C Syntax VariableRef of: load variable name type: (g variableNamed: load variable name) type ]. g@(C SimpleGenerator traits) generateCFor: comment@(Syntax Comment traits) "Ignore the comment and answer the C for the annotated Node." [Console ; 'generating comment...\n'. g generateCFor: comment value]. g@(C SimpleGenerator traits) generateCFor: ret@(Syntax Return traits) [Console ; 'generating return...\n'. g scope first type == Types C Void ifTrue: [| block | block: C Syntax Block newEmpty. block statements: { g generateCStatementFor: ret value. C Syntax Return of: Nil }. block ] ifFalse: [C Syntax Return of: (g generateCFor: ret value)] ]. g@(C SimpleGenerator traits) generateCFor: def@(Syntax MethodDefinition traits) [| body | body: resend. Console ; 'checking statements...\n'. body statements isEmpty ifTrue: [^ body]. Console ; 'checking return...\n'. ((body statements last isSameAs: C Syntax Return) or: [g scope first type == Types C Void]) ifFalse: [ g scope push: body. Console ; 'adding return...\n'. body statements at: body statements size - 1 put: (C Syntax Return of: (g generateCFor: def statements last)). g scope pop ]. Console ; 'done with method!\n'. body ]. g@(C SimpleGenerator traits) generateCFor: block@(Syntax Block traits) "Blocks turn into C blocks. All locals are moved into the block's header, and inputs are just handled as locals." [| newBlock | "If we can do this in one statement, do so. Let the printer handle it." Console ; 'generating block...\n'. (block statements size = 1 and: [block inputVariables isEmpty and: [block localVariables isEmpty]]) ifTrue: [^ (g generateCStatementFor: block statements first)]. newBlock: C Syntax Block newEmpty. block localVariables do: [| :var | ((block isSameAs: Syntax Block) not and: [block inputVariables includes: var]) ifFalse: [newBlock define: var name type: var type]]. Console ; 'generating block statements...\n'. g scope push: newBlock. newBlock statements: (block statements collect: [| :statement | Console ; 'generating block statement...\n'. g generateCStatementFor: statement]). g scope pop. Console ; 'done with block!\n'. newBlock ]. g@(C SimpleGenerator traits) generateCFor: mode@(Syntax Mode traits) [ mode mode = Syntax Mode Primitive ifTrue: [^ (g generateCFor: mode value)]. mode mode = Syntax Mode Slate ifTrue: [^ (g generateSlateFor: mode value)]. error: 'Unhandled mode.' ]. g@(C SimpleGenerator traits) generate: module [ g module: module. Console ; 'generating functions...\n'. module methods do: [| :fun | Console ; 'generating function ' ; (fun name as: String) ; '\n'. Console ; 'inferring types...\n'. fun body inferTypesIn: module. Console ; 'generate parse tree...\n'. g scope push: fun. fun body: (g generateCFor: fun body). g scope pop ] ]. g@(C SimpleGenerator traits) emitConstants: module on: s "Store the constants' declarations on the given stream." [ s ; '/*** Constants ***/\n'. module constants do: [| :const | g printDefinition: const on: s ]. s nextPut: $\n ]. g@(C SimpleGenerator traits) emitMethods: module on: s "Store the method bodies on the given stream." [ s ; '/*** Methods ***/\n'. module methods do: [| :method | method isInline ifTrue: [g printDefinition: method on: s] ]. module methods do: [| :method | method isInline ifFalse: [g printDefinition: method on: s] ]. s nextPut: $\n ]. g@(C SimpleGenerator traits) emitGlobals: module on: s "Store the global variable declarations on the given stream." [ s ; '/*** Globals ***/\n'. module globals do: [| :global | g printDefinition: global on: s ]. s nextPut: $\n ]. g@(C SimpleGenerator traits) emitTypes: types on: s [| emitted changed | emitted: Set newEmpty. [emitted size < types size] whileTrue: [changed: False. types do: [| :type | ((emitted includes: type) not and: [emitted includesAllOf: type dependencies]) ifTrue: [g printDefinition: type on: s. emitted include: type. changed: True]]. changed ifFalse: [error: 'Vicious cycles are present in type definitions.'] ] ]. g@(C SimpleGenerator traits) emitPrototypes: module on: s "Store the method prototypes on the given stream." [ s ; '/*** Prototypes ***/\n'. module types do: [| :type | g printPrototype: type on: s]. g emitTypes: module types on: s. module methods do: [| :method | g printPrototype: method on: s]. s nextPut: $\n ]. g@(C SimpleGenerator traits) emitPrologue: module on: stream "Includes any standard information needed by the runtime for this." [ module headers do: [| :headerName | stream ; '\n#include ' ; headerName ; '\n'] ]. g@(C SimpleGenerator traits) emitHeader: module on: s [ g emitPrologue: module on: s. Console ; 'prototyping types...\n'. module types do: [| :type | type isExported ifTrue: [g printPrototype: type on: s] ]. g emitTypes: (module types valueSet select: [| :type | type isExported]) on: s. Console ; 'prototyping constants...\n'. module constants do: [| :const | const isExported ifTrue: [g printPrototype: const on: s] ]. Console ; 'prototyping globals...\n'. module globals do: [| :global | global isExported ifTrue: [g printPrototype: global on: s] ]. Console ; 'prototyping methods...\n'. module methods do: [| :method | method isExported ifTrue: [g printPrototype: method on: s] ]. module methods do: [| :method | (method isExported and: [method isInline]) ifTrue: [g printDefinition: method on: s] ] ]. g@(C SimpleGenerator traits) emit: module on: stream "Emit C code for all methods in the code base onto the given stream. All inlined method calls should already have been expanded." [ Console ; 'printing warnings...\n'. g verbose ifTrue: [g printUnboundCallWarnings. g printUnboundSlotRefWarnings]. "methods: g module methods. clean out no longer valid variable names and then handle any global variable usage in each method Console ; 'checking global usage...\n'. methods do: [| :m | g checkForGlobalUsageBy: m removeUnusedTemps in: m]. Console ; 'localizing globals...\n'. g module localizeGlobals. " Console ; 'emitting prologue...\n'. g emitPrologue: module on: stream. Console ; 'emitting prototypes...\n'. g emitPrototypes: module on: stream. Console ; 'emitting constants...\n'. g emitConstants: module on: stream. Console ; 'emitting variables...\n'. g emitGlobals: module on: stream. Console ; 'emitting methods...\n'. g emitMethods: module on: stream ].