Reduced dependencies to only stx:libbasic and stx:libcomp.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 30 Oct 2014 22:42:40 +0000
changeset 45 04a50b0d540a
parent 44 840c68a91cdd
child 46 2fb37cf149fb
Reduced dependencies to only stx:libbasic and stx:libcomp. The latter will wanish as soon as actual bytecode assemby is implemented.
IRDecompiler.st
IRFunction.st
Make.proto
Make.spec
bc.mak
ctu_ircompiler.st
ircompiler.rc
libInit.cc
tests/tests.rc
--- a/IRDecompiler.st	Thu Oct 30 22:27:09 2014 +0000
+++ b/IRDecompiler.st	Thu Oct 30 22:42:40 2014 +0000
@@ -49,61 +49,65 @@
 !
 
 decompileIR: ir 
-	| sequenceNode temps args goto seq value method |
-	scope isBlockScope 
-		ifTrue:[(scope addTemp: 'parent env') markArg]
-		ifFalse:[(scope addTemp: 'self') markArg].
-	ir tempKeys do: [:temp | scope tempVarAt: temp].
-	0 to: ir numRargs - 1 do: [:i | (scope tempVarAt: i) markArg].
-	self interpret: ir.
-	
-	self addTempToScope: ir.
-	self label: #return.
-	self Label: #return.
-	(self endCase: #lastReturn) ifFalse:[self Label: #return.].
-	goto := self Goto.
-	value := self ValueOrNone.
-	seq := self Sequence.
-	self removeClosureCreation: seq.
-	sp = 1 ifFalse: [stack explore. self error: 'error'].
-	value ifNotNil: [seq addNode: value].
-	sequenceNode := (self newBlock: seq return: goto) body.
-	temps := scope compactIndexTemps asArray.
-	ir tempKeys: temps.
-	args := (temps first: ir numRargs) allButFirst.
-	args := args collect: [:var | self newVar: var].
-	temps := temps allButFirst: ir numRargs.
-	sequenceNode temporaries: (temps collect: [:var | self newVar: var]), 
-		((scope capturedVars select:[:var | var name ~= 'self' and: [var sourceTemp == nil]]) 
-			collect:[:var | self newVar: var]).
-	method := (RBMethodNode new)
-				selectorParts: (self 
-							newSelectorParts: (self class dummySelector: args size));
-				arguments: args;
-				body: sequenceNode;
-				primitiveNode: ir primitiveNode;
-				scope: scope.
-	sequenceNode parent: method.
-	Preferences compileBlocksAsClosures 
-		ifFalse: [ASTFixDecompileBlockScope new visitNode: method].
-	^ method
+"/        | sequenceNode temps args goto seq value method |
+"/        scope isBlockScope 
+"/                ifTrue:[(scope addTemp: 'parent env') markArg]
+"/                ifFalse:[(scope addTemp: 'self') markArg].
+"/        ir tempKeys do: [:temp | scope tempVarAt: temp].
+"/        0 to: ir numRargs - 1 do: [:i | (scope tempVarAt: i) markArg].
+"/        self interpret: ir.
+"/        
+"/        self addTempToScope: ir.
+"/        self label: #return.
+"/        self Label: #return.
+"/        (self endCase: #lastReturn) ifFalse:[self Label: #return.].
+"/        goto := self Goto.
+"/        value := self ValueOrNone.
+"/        seq := self Sequence.
+"/        self removeClosureCreation: seq.
+"/        sp = 1 ifFalse: [stack explore. self error: 'error'].
+"/        value ifNotNil: [seq addNode: value].
+"/        sequenceNode := (self newBlock: seq return: goto) body.
+"/        temps := scope compactIndexTemps asArray.
+"/        ir tempKeys: temps.
+"/        args := (temps first: ir numRargs) allButFirst.
+"/        args := args collect: [:var | self newVar: var].
+"/        temps := temps allButFirst: ir numRargs.
+"/        sequenceNode temporaries: (temps collect: [:var | self newVar: var]), 
+"/                ((scope capturedVars select:[:var | var name ~= 'self' and: [var sourceTemp == nil]]) 
+"/                        collect:[:var | self newVar: var]).
+"/        method := (RBMethodNode new)
+"/                                selectorParts: (self 
+"/                                                        newSelectorParts: (self class dummySelector: args size));
+"/                                arguments: args;
+"/                                body: sequenceNode;
+"/                                primitiveNode: ir primitiveNode;
+"/                                scope: scope.
+"/        sequenceNode parent: method.
+"/        Preferences compileBlocksAsClosures 
+"/                ifFalse: [ASTFixDecompileBlockScope new visitNode: method].
+"/        ^ method
+
+    "Modified: / 30-10-2014 / 22:36:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 removeClosureCreation: seq 
-	(Preferences compileBlocksAsClosures 
-		and: [seq statements size > 0]
-		and: [seq statements first isClosureEnvironmentCreation]) ifTrue: [
-			seq statements removeFirst.
-			(seq statements size > 0
-				and: [seq statements first isClosureEnvironmentRegistration])
-				ifTrue: [seq statements removeFirst]].
-			
-	[Preferences compileBlocksAsClosures
-		and: [seq statements size > 0]
-		and: [seq statements first isClosureRegistrationAndCreation
-			or: [seq statements first isSelfClosureRegistration]
-			or: [seq statements first isTempClosureRegistration]]]
-					whileTrue: [seq statements removeFirst]
+        ("Preferences compileBlocksAsClosures"true
+                and: [seq statements size > 0]
+                and: [seq statements first isClosureEnvironmentCreation]) ifTrue: [
+                        seq statements removeFirst.
+                        (seq statements size > 0
+                                and: [seq statements first isClosureEnvironmentRegistration])
+                                ifTrue: [seq statements removeFirst]].
+                        
+        ["Preferences compileBlocksAsClosures"true
+                and: [seq statements size > 0]
+                and: [seq statements first isClosureRegistrationAndCreation
+                        or: [seq statements first isSelfClosureRegistration]
+                        or: [seq statements first isTempClosureRegistration]]]
+                                        whileTrue: [seq statements removeFirst]
+
+    "Modified: / 30-10-2014 / 22:37:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 scope: aLexicalScope
@@ -235,7 +239,7 @@
                 ^self cascade] on: Abort do:[^false]
         ].
 
-        Preferences compileBlocksAsClosures 
+        "Preferences compileBlocksAsClosures"true
                         ifTrue: [ (rcvr isLiteral and: [selector = #createBlock:]) ifTrue: [
                                          ^ self block: rcvr value env: args first]]
                         ifFalse: [ (selector = #blockCopy:) ifTrue: [
@@ -247,6 +251,7 @@
                 arguments: args)).
 
     "Created: / 01-12-2008 / 19:40:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 30-10-2014 / 22:38:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 send: selector numArgs: numArgs toSuperOf: behavior
@@ -383,14 +388,17 @@
 !IRDecompiler methodsFor:'priv instructions'!
 
 addReturn: statements from: goto
+"/    |  |
 
-		| ret |
-		statements last isReturn ifTrue:[^self].
-		ret := RBReturnNode value: statements last.
-		Preferences compileBlocksAsClosures ifTrue:[
-			scope isHome ifFalse: [ret homeBinding: scope outerEnvScope thisEnvVar]].
-		goto mapInstr sourceNode: ret.
-		statements atLast: 1 put: ret.
+    self error: 'IRDecompiler is an unfinished code'.    
+"/    statements last isReturn ifTrue:[^self].
+"/    ret := RBReturnNode value: statements last.
+"/    Preferences compileBlocksAsClosures ifTrue:[
+"/            scope isHome ifFalse: [ret homeBinding: scope outerEnvScope thisEnvVar]].
+"/    goto mapInstr sourceNode: ret.
+"/    statements atLast: 1 put: ret.
+
+    "Modified: / 30-10-2014 / 22:35:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 block: method env: envRefNode
@@ -779,55 +787,57 @@
 
 endToDo: seqNum
 
-	| start limit incr iter step loopBlock o if test limitExpr init |
-	[
-		start := self Goto destination.
-		limit := self Value.
-		incr := self Assignment.
-		iter := incr variable.
-		(incr value isMessage and:
-		 [incr value selector == #+ and:
-		  [incr value receiver isVariable and: 
-		   [incr value receiver binding == iter binding]]]
-		) ifFalse: [self abort].
-		step := incr value arguments first.
-		loopBlock := self Sequence.
-		o := self Label destination.
-		if := self IfGoto: seqNum otherwise: o.
-		test := self Value.
-		(test isMessage and:
-		 [(test selector == #<= or: [test selector == #>=]) and:
-		  [(valueLabelMap at: test arguments first ifAbsent: [self abort]) destination = start]]
-		) ifFalse: [self abort].
-		limitExpr := test arguments first.
-		limitExpr isAssignment ifTrue: [
-			(limitExpr variable binding index == limit binding index 
-				and:[limitExpr variable binding scope == limit binding scope]) ifFalse: [self abort].
-			limitExpr := limitExpr value.
-		].
-		init := test receiver.
-		(init isAssignment and: [init variable binding == iter binding])
-			ifFalse: [self abort].
-	] on: Abort do: [^ false].
-	limit isVariable 
-		ifTrue:[scope 
-			removeTemp: limit binding 
-			ifAbsent:[Preferences compileBlocksAsClosures 
-				ifFalse:[scope removeTempFromOldBlock: limit]]].
-	loopBlock := self newBlock: loopBlock.
-	loopBlock arguments: {iter}.
-	self stackPush: ((step isLiteral: [:c | c = 1])
-		ifTrue: [RBMessageNode
-				receiver: init value
-				selector: #to:do:
-				arguments: {limitExpr. loopBlock}]
-		ifFalse: [RBMessageNode
-				receiver: init value
-				selector: #to:by:do:
-				arguments: {limitExpr. step. loopBlock}]).
-	self popTop.
-	self goto: seqNum.
-	^ true
+        | start limit incr iter step loopBlock o if test limitExpr init |
+        [
+                start := self Goto destination.
+                limit := self Value.
+                incr := self Assignment.
+                iter := incr variable.
+                (incr value isMessage and:
+                 [incr value selector == #+ and:
+                  [incr value receiver isVariable and: 
+                   [incr value receiver binding == iter binding]]]
+                ) ifFalse: [self abort].
+                step := incr value arguments first.
+                loopBlock := self Sequence.
+                o := self Label destination.
+                if := self IfGoto: seqNum otherwise: o.
+                test := self Value.
+                (test isMessage and:
+                 [(test selector == #<= or: [test selector == #>=]) and:
+                  [(valueLabelMap at: test arguments first ifAbsent: [self abort]) destination = start]]
+                ) ifFalse: [self abort].
+                limitExpr := test arguments first.
+                limitExpr isAssignment ifTrue: [
+                        (limitExpr variable binding index == limit binding index 
+                                and:[limitExpr variable binding scope == limit binding scope]) ifFalse: [self abort].
+                        limitExpr := limitExpr value.
+                ].
+                init := test receiver.
+                (init isAssignment and: [init variable binding == iter binding])
+                        ifFalse: [self abort].
+        ] on: Abort do: [^ false].
+        limit isVariable 
+                ifTrue:[scope 
+                        removeTemp: limit binding 
+                        ifAbsent:["Preferences compileBlocksAsClosures"true
+                                ifFalse:[scope removeTempFromOldBlock: limit]]].
+        loopBlock := self newBlock: loopBlock.
+        loopBlock arguments: {iter}.
+        self stackPush: ((step isLiteral: [:c | c = 1])
+                ifTrue: [RBMessageNode
+                                receiver: init value
+                                selector: #to:do:
+                                arguments: {limitExpr. loopBlock}]
+                ifFalse: [RBMessageNode
+                                receiver: init value
+                                selector: #to:by:do:
+                                arguments: {limitExpr. step. loopBlock}]).
+        self popTop.
+        self goto: seqNum.
+        ^ true
+
+    "Modified: / 30-10-2014 / 22:37:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 endWhile2: seqNum
@@ -923,11 +933,13 @@
 
 isExplicitReturn: goto
 
-	Preferences compileBlocksAsClosures 
-		ifTrue:[^ goto isRet 
-			and: [goto mapInstr notNil] 
-			and: [goto mapInstr isRemote or: [scope isBlockScope not]]]
-		ifFalse: [^goto isRet and: [goto mapInstr isBlockReturnTop not]]
+        "Preferences compileBlocksAsClosures"true
+                ifTrue:[^ goto isRet 
+                        and: [goto mapInstr notNil] 
+                        and: [goto mapInstr isRemote or: [scope isBlockScope not]]]
+                ifFalse: [^goto isRet and: [goto mapInstr isBlockReturnTop not]]
+
+    "Modified: / 30-10-2014 / 22:37:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 mapNode: node
@@ -945,16 +957,18 @@
 
 newBlock: sequence return: goto
 
-	| statements block |
-	statements := sequence statements.
-	(goto notNil and: [self isExplicitReturn: goto]) ifTrue: [
-		self addReturn: statements from: goto
-	].
-	sequence statements: statements.
-	block := RBBlockNode body: sequence.
-	sequence parent: block.
-	Preferences compileBlocksAsClosures ifFalse: [block scope: scope].
-	^block
+        | statements block |
+        statements := sequence statements.
+        (goto notNil and: [self isExplicitReturn: goto]) ifTrue: [
+                self addReturn: statements from: goto
+        ].
+        sequence statements: statements.
+        block := RBBlockNode body: sequence.
+        sequence parent: block.
+        "Preferences compileBlocksAsClosures"true ifFalse: [block scope: scope].
+        ^block
+
+    "Modified: / 30-10-2014 / 22:37:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 newLiteral: literal
--- a/IRFunction.st	Thu Oct 30 22:27:09 2014 +0000
+++ b/IRFunction.st	Thu Oct 30 22:42:40 2014 +0000
@@ -172,13 +172,16 @@
 !IRFunction methodsFor:'debugging support'!
 
 inspector2TabIRCode
+    <inspector2Tab>
 
-    ^Tools::Inspector2Tab new
-	label: 'IR Code';
-	priority: 75;
-	view: ((ScrollableView for:TextView) contents: self longPrintString; yourself)
+    ^(Smalltalk at: #Tools::Inspector2Tab) new
+        label: 'IR Code';
+        priority: 75;
+        text: [ self longPrintString ];
+        yourself
 
     "Created: / 11-06-2008 / 01:05:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 30-10-2014 / 22:33:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !IRFunction methodsFor:'decompiling'!
--- a/Make.proto	Thu Oct 30 22:27:09 2014 +0000
+++ b/Make.proto	Thu Oct 30 22:42:40 2014 +0000
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/refactoryBrowser/parser -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libcomp -I$(INCLUDE_TOP)/stx/libcompat -I$(INCLUDE_TOP)/stx/libtool -I$(INCLUDE_TOP)/stx/libwidg
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libcomp
 
 
 # if you need any additional defines for embedded C code,
@@ -155,7 +155,6 @@
 $(OUTDIR)IRAccess.$(O) IRAccess.$(H): IRAccess.st $(INCLUDE_TOP)/ctu/ircompiler/IRInstruction.$(H) $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)IRClosure.$(O) IRClosure.$(H): IRClosure.st $(INCLUDE_TOP)/ctu/ircompiler/IRFunction.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)IRConstant.$(O) IRConstant.$(H): IRConstant.st $(INCLUDE_TOP)/ctu/ircompiler/IRInstruction.$(H) $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)IRDecompiler.$(O) IRDecompiler.$(H): IRDecompiler.st $(INCLUDE_TOP)/ctu/ircompiler/IRInterpreter.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)IRDup.$(O) IRDup.$(H): IRDup.st $(INCLUDE_TOP)/ctu/ircompiler/IRInstruction.$(H) $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)IRJump.$(O) IRJump.$(H): IRJump.st $(INCLUDE_TOP)/ctu/ircompiler/IRInstruction.$(H) $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)IRLine.$(O) IRLine.$(H): IRLine.st $(INCLUDE_TOP)/ctu/ircompiler/IRInstruction.$(H) $(INCLUDE_TOP)/stx/libbasic/Link.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/Make.spec	Thu Oct 30 22:27:09 2014 +0000
+++ b/Make.spec	Thu Oct 30 22:42:40 2014 +0000
@@ -61,7 +61,6 @@
 	IRAccess \
 	IRClosure \
 	IRConstant \
-	IRDecompiler \
 	IRDup \
 	IRJump \
 	IRLine \
@@ -99,7 +98,6 @@
     $(OUTDIR_SLASH)IRAccess.$(O) \
     $(OUTDIR_SLASH)IRClosure.$(O) \
     $(OUTDIR_SLASH)IRConstant.$(O) \
-    $(OUTDIR_SLASH)IRDecompiler.$(O) \
     $(OUTDIR_SLASH)IRDup.$(O) \
     $(OUTDIR_SLASH)IRJump.$(O) \
     $(OUTDIR_SLASH)IRLine.$(O) \
--- a/bc.mak	Thu Oct 30 22:27:09 2014 +0000
+++ b/bc.mak	Thu Oct 30 22:42:40 2014 +0000
@@ -34,7 +34,7 @@
 
 
 
-LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\refactoryBrowser\parser -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libcomp -I$(INCLUDE_TOP)\stx\libcompat -I$(INCLUDE_TOP)\stx\libtool -I$(INCLUDE_TOP)\stx\libwidg
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libcomp
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
@@ -79,7 +79,6 @@
 $(OUTDIR)IRAccess.$(O) IRAccess.$(H): IRAccess.st $(INCLUDE_TOP)\ctu\ircompiler\IRInstruction.$(H) $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)IRClosure.$(O) IRClosure.$(H): IRClosure.st $(INCLUDE_TOP)\ctu\ircompiler\IRFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)IRConstant.$(O) IRConstant.$(H): IRConstant.st $(INCLUDE_TOP)\ctu\ircompiler\IRInstruction.$(H) $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)IRDecompiler.$(O) IRDecompiler.$(H): IRDecompiler.st $(INCLUDE_TOP)\ctu\ircompiler\IRInterpreter.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)IRDup.$(O) IRDup.$(H): IRDup.st $(INCLUDE_TOP)\ctu\ircompiler\IRInstruction.$(H) $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)IRJump.$(O) IRJump.$(H): IRJump.st $(INCLUDE_TOP)\ctu\ircompiler\IRInstruction.$(H) $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)IRLine.$(O) IRLine.$(H): IRLine.st $(INCLUDE_TOP)\ctu\ircompiler\IRInstruction.$(H) $(INCLUDE_TOP)\stx\libbasic\Link.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/ctu_ircompiler.st	Thu Oct 30 22:27:09 2014 +0000
+++ b/ctu_ircompiler.st	Thu Oct 30 22:42:40 2014 +0000
@@ -21,7 +21,10 @@
      my classes is considered to be a prerequisite package."
 
     ^ #(
+        #'stx:goodies/refactoryBrowser/parser'    "RBArrayNode - referenced by IRDecompiler>>endCase:"
     )
+
+    "Modified: / 30-10-2014 / 22:29:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 mandatoryPreRequisites
@@ -46,10 +49,6 @@
      by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        #'stx:goodies/refactoryBrowser/parser'    "RBArrayNode - referenced by IRDecompiler>>endCase:"
-        #'stx:libcompat'    "Preferences - referenced by IRDecompiler>>addReturn:from:"
-        #'stx:libtool'    "Tools::Inspector2Tab - referenced by IRFunction>>inspector2TabIRCode"
-        #'stx:libwidg'    "ScrollableView - referenced by IRFunction>>inspector2TabIRCode"
     )
 !
 
@@ -84,7 +83,7 @@
         IRAccess
         IRClosure
         IRConstant
-        IRDecompiler
+        (IRDecompiler autoload)
         IRDup
         IRJump
         IRLine
--- a/ircompiler.rc	Thu Oct 30 22:27:09 2014 +0000
+++ b/ircompiler.rc	Thu Oct 30 22:42:40 2014 +0000
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Jan Vrany & Mathieu Suen 2008\0"
       VALUE "ProductName", "NewCompiler\0"
       VALUE "ProductVersion", "6.2.4.0\0"
-      VALUE "ProductDate", "Thu, 30 Oct 2014 22:24:49 GMT\0"
+      VALUE "ProductDate", "Thu, 30 Oct 2014 22:40:10 GMT\0"
     END
 
   END
--- a/libInit.cc	Thu Oct 30 22:27:09 2014 +0000
+++ b/libInit.cc	Thu Oct 30 22:42:40 2014 +0000
@@ -38,7 +38,6 @@
 _IRAccess_Init(pass,__pRT__,snd);
 _IRClosure_Init(pass,__pRT__,snd);
 _IRConstant_Init(pass,__pRT__,snd);
-_IRDecompiler_Init(pass,__pRT__,snd);
 _IRDup_Init(pass,__pRT__,snd);
 _IRJump_Init(pass,__pRT__,snd);
 _IRLine_Init(pass,__pRT__,snd);
--- a/tests/tests.rc	Thu Oct 30 22:27:09 2014 +0000
+++ b/tests/tests.rc	Thu Oct 30 22:42:40 2014 +0000
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "My CopyRight or CopyLeft\0"
       VALUE "ProductName", "LibraryName\0"
       VALUE "ProductVersion", "6.2.4.0\0"
-      VALUE "ProductDate", "Thu, 30 Oct 2014 22:24:51 GMT\0"
+      VALUE "ProductDate", "Thu, 30 Oct 2014 22:40:12 GMT\0"
     END
 
   END