VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
9 messages Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-rmacnak.1595.mcz

commits-2
 
Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1595.mcz

==================== Summary ====================

Name: VMMaker.oscog-rmacnak.1595
Author: rmacnak
Time: 14 December 2015, 7:29:18.283 pm
UUID: 3aac3671-b1ff-45b9-8ed0-f3ecc5bca0b3
Ancestors: VMMaker.oscog-eem.1594

MIPS: Complete simulation of the Newspeak test suite! (~30 billion instructions) (Modulo Aliens, which don't work under the IA32 simulation either.)

Fix off-by-8 in patching I-type branches. Bug had the effect of skipping loading the cPIC address for a cPIC miss if the cPIC was created for an MNU case.

Handle PushCw in storeLiteral:beforeFollowingAddress:.

Add the GC's variant of rewriteInlineCacheTag:at:.

Fix MNU in followForwardingPointersInScheduler.

=============== Diff against VMMaker.oscog-eem.1594 ===============

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteITypeBranchAtAddress:target: (in category 'inline cacheing') -----
  rewriteITypeBranchAtAddress: mcpc target: newTarget
+ | newDisplacement oldInstruction newInstruction |
+ newDisplacement := newTarget - (mcpc + 4). "Displacement is relative to delay slot."
+ newDisplacement := newDisplacement >> 2. "Displacement is in words."
- | newDisplacement oldInstruction newInstruction |
- newDisplacement := newTarget - (mcpc - 4). "Displacement relative to delay slot"
- newDisplacement := newDisplacement >> 2.
 
  self assert: (newDisplacement between: -16r8000 and: 16r7FFF).
  newDisplacement < 0
  ifTrue: [newDisplacement := newDisplacement + 16r10000]
  ifFalse: [newDisplacement := newDisplacement].
  self assert: (newDisplacement between: 0 and: 16rFFFF).
 
  oldInstruction := objectMemory longAt: mcpc.
  newInstruction := (oldInstruction bitAnd: 16rFFFF0000) bitOr: newDisplacement.
 
  objectMemory longAt: mcpc put: newInstruction.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>rewriteInlineCacheTag:at: (in category 'inline cacheing') -----
+ rewriteInlineCacheTag: cacheTag at: callSiteReturnAddress
+ "Rewrite an inline cache with a new tag.  This variant is used
+ by the garbage collector."
+
+ "MoveCwR ClassReg selectorIndex/expectedClass
+ Call: unlinked send stub/expectedTarget
+ Push ReceiverResult <-- callSiteReturnAddress"
+
+ "lui s3, selector/tagHigh
+ ori s3, s3, selector/tagLow
+ lui t9, stub/targetHigh
+ ori t9, t9, stub/targetLow
+ jalr t9
+ nop (delay slot)
+ ...  <-- callSiteReturnAddress"
+
+ <var: #callSiteReturnAddress type: #usqInt>
+ <var: #callTargetAddress type: #usqInt>
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
+ self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
+ self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
+ "cogit disassembleFrom: callSiteReturnAddress - 24 to: callSiteReturnAddress."
+
+ self literalAtAddress: callSiteReturnAddress - 20 put: cacheTag.
+
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
+ self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
+ self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
+ self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
+ "cogit disassembleFrom: callSiteReturnAddress - 24 to: callSiteReturnAddress."!

Item was changed:
  ----- Method: CogMIPSELCompiler>>storeLiteral:beforeFollowingAddress: (in category 'inline cacheing') -----
  storeLiteral: literal beforeFollowingAddress: followingAddress
  "Rewrite the long constant loaded by a MoveCwR or PushCwR before the given address"
- | lastOpcode lastFunction oriAddress |
  self flag: #bogus. "The caller ought to know what it is patching, and this should be split into separate methods with stricter checking."
 
+ "Cmp/MoveCwR
+ pc-8 lui rx, uper
+ pc-4 ori rx, rx, lower"
+ (self opcodeAtAddress: followingAddress - 4) = ORI ifTrue:
+ [^self literalAtAddress: followingAddress - 4 put: literal].
+
+ "PushCw
+ pc-16 lui at, upper
+ pc-12 ori at, at, lower
+ pc-8 addiu sp, sp, -4
+ pc-4 sw at, 0(sp)"
+ ((self opcodeAtAddress: followingAddress - 4) = SW and:
+ [(self opcodeAtAddress: followingAddress - 8) = ADDIU]) ifTrue:
+ [^self literalAtAddress: followingAddress - 12 put: literal].
+
+ self unreachable.
+ ^0!
- lastOpcode := self opcodeAtAddress: followingAddress - 4.
- lastFunction := self functionAtAddress: followingAddress - 4.
- oriAddress := 0.
- lastOpcode = ORI ifTrue: [oriAddress := followingAddress - 4].
- lastOpcode = ADDIU ifTrue: [oriAddress := followingAddress - 16].
- lastOpcode = SPECIAL ifTrue: [lastFunction = SUBU ifTrue: [oriAddress := followingAddress - 8]].
- self assert: oriAddress ~= 0.
- ^self literalAtAddress: oriAddress put: literal!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInScheduler (in category 'object memory support') -----
  followForwardingPointersInScheduler
  | schedAssoc sched procLists |
  schedAssoc := objectMemory splObj: SchedulerAssociation.
  "the GC follows pointers in the special objects array for us."
  self assert: (objectMemory isForwarded: schedAssoc) not.
 
  "Make sure the active process has been followed."
+ objectMemory followForwardedObjectFields: schedAssoc toDepth: 1.
- self followForwardedObjectFields: schedAssoc toDepth: 1.
 
  sched := objectMemory fetchPointer: ValueIndex ofObject: schedAssoc.
 
  procLists := objectMemory followObjField: ProcessListsIndex ofObject: sched.
 
  "Follow all links in the process list to ensure the lists are valid."
  0 to: (objectMemory numSlotsOf: procLists) - 1 do:
  [:i| | list first last next |
  list := objectMemory followObjField: i ofObject: procLists.
  first := objectMemory followObjField: FirstLinkIndex ofObject: list.
  last := objectMemory followObjField: LastLinkIndex ofObject: list.
  [first ~= last] whileTrue:
  [next := objectMemory followObjField: NextLinkIndex ofObject: first.
  first := next]]
  !

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Eliot Miranda-2



> On Dec 15, 2015, at 12:15 AM, [hidden email] wrote:
>
>
> Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1595.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-rmacnak.1595
> Author: rmacnak
> Time: 14 December 2015, 7:29:18.283 pm
> UUID: 3aac3671-b1ff-45b9-8ed0-f3ecc5bca0b3
> Ancestors: VMMaker.oscog-eem.1594
>
> MIPS: Complete simulation of the Newspeak test suite! (~30 billion instructions) (Modulo Aliens, which don't work under the IA32 simulation either.)

Woot!!


> Fix off-by-8 in patching I-type branches. Bug had the effect of skipping loading the cPIC address for a cPIC miss if the cPIC was created for an MNU case.
>
> Handle PushCw in storeLiteral:beforeFollowingAddress:.
>
> Add the GC's variant of rewriteInlineCacheTag:at:.
>
> Fix MNU in followForwardingPointersInScheduler.
>
> =============== Diff against VMMaker.oscog-eem.1594 ===============
>
> Item was changed:
>  ----- Method: CogMIPSELCompiler>>rewriteITypeBranchAtAddress:target: (in category 'inline cacheing') -----
>  rewriteITypeBranchAtAddress: mcpc target: newTarget
> +    | newDisplacement oldInstruction newInstruction |
> +    newDisplacement := newTarget - (mcpc + 4). "Displacement is relative to delay slot."
> +    newDisplacement := newDisplacement >> 2. "Displacement is in words."
> -    | newDisplacement oldInstruction newInstruction |    
> -    newDisplacement := newTarget - (mcpc - 4). "Displacement relative to delay slot"
> -    newDisplacement := newDisplacement >> 2.
>      
>      self assert: (newDisplacement between: -16r8000 and: 16r7FFF).
>      newDisplacement < 0
>          ifTrue: [newDisplacement := newDisplacement + 16r10000]
>          ifFalse: [newDisplacement := newDisplacement].
>      self assert: (newDisplacement between: 0 and: 16rFFFF).
>
>      oldInstruction := objectMemory longAt: mcpc.
>      newInstruction := (oldInstruction bitAnd: 16rFFFF0000) bitOr: newDisplacement.
>      
>      objectMemory longAt: mcpc put: newInstruction.!
>
> Item was added:
> + ----- Method: CogMIPSELCompiler>>rewriteInlineCacheTag:at: (in category 'inline cacheing') -----
> + rewriteInlineCacheTag: cacheTag at: callSiteReturnAddress
> +    "Rewrite an inline cache with a new tag.  This variant is used
> +     by the garbage collector."
> +    
> +    "MoveCwR ClassReg selectorIndex/expectedClass
> +     Call: unlinked send stub/expectedTarget
> +     Push ReceiverResult <-- callSiteReturnAddress"
> +    
> +    "lui s3, selector/tagHigh
> +     ori s3, s3, selector/tagLow
> +     lui t9, stub/targetHigh
> +     ori t9, t9, stub/targetLow
> +     jalr t9
> +     nop (delay slot)
> +     ...  <-- callSiteReturnAddress"
> +    
> +    <var: #callSiteReturnAddress type: #usqInt>
> +    <var: #callTargetAddress type: #usqInt>
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
> +    self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
> +    self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
> +    "cogit disassembleFrom: callSiteReturnAddress - 24 to: callSiteReturnAddress."
> +
> +    self literalAtAddress: callSiteReturnAddress - 20 put: cacheTag.
> +
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
> +    self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
> +    self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
> +    self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
> +    "cogit disassembleFrom: callSiteReturnAddress - 24 to: callSiteReturnAddress."!
>
> Item was changed:
>  ----- Method: CogMIPSELCompiler>>storeLiteral:beforeFollowingAddress: (in category 'inline cacheing') -----
>  storeLiteral: literal beforeFollowingAddress: followingAddress
>      "Rewrite the long constant loaded by a MoveCwR or PushCwR before the given address"
> -    | lastOpcode lastFunction oriAddress |
>      self flag: #bogus. "The caller ought to know what it is patching, and this should be split into separate methods with stricter checking."
>      
> +    "Cmp/MoveCwR
> +     pc-8    lui rx, uper
> +     pc-4    ori rx, rx, lower"
> +    (self opcodeAtAddress: followingAddress - 4) = ORI ifTrue:
> +        [^self literalAtAddress: followingAddress - 4 put: literal].
> +
> +    "PushCw
> +     pc-16    lui at, upper
> +     pc-12    ori at, at, lower
> +     pc-8    addiu sp, sp, -4
> +     pc-4    sw at, 0(sp)"
> +    ((self opcodeAtAddress: followingAddress - 4) = SW and:
> +        [(self opcodeAtAddress: followingAddress - 8) = ADDIU]) ifTrue:
> +            [^self literalAtAddress: followingAddress - 12 put: literal].
> +    
> +    self unreachable.
> +    ^0!
> -    lastOpcode := self opcodeAtAddress: followingAddress - 4.
> -    lastFunction := self functionAtAddress: followingAddress - 4.
> -    oriAddress := 0.
> -    lastOpcode = ORI ifTrue: [oriAddress := followingAddress - 4].
> -    lastOpcode = ADDIU ifTrue: [oriAddress := followingAddress - 16].
> -    lastOpcode = SPECIAL ifTrue: [lastFunction = SUBU ifTrue: [oriAddress := followingAddress - 8]].
> -    self assert: oriAddress ~= 0.
> -    ^self literalAtAddress: oriAddress put: literal!
>
> Item was changed:
>  ----- Method: StackInterpreter>>followForwardingPointersInScheduler (in category 'object memory support') -----
>  followForwardingPointersInScheduler
>      | schedAssoc sched procLists |
>      schedAssoc := objectMemory splObj: SchedulerAssociation.
>      "the GC follows pointers in the special objects array for us."
>      self assert: (objectMemory isForwarded: schedAssoc) not.
>
>      "Make sure the active process has been followed."
> +    objectMemory followForwardedObjectFields: schedAssoc toDepth: 1.
> -    self followForwardedObjectFields: schedAssoc toDepth: 1.
>
>      sched := objectMemory fetchPointer: ValueIndex ofObject: schedAssoc.
>
>      procLists := objectMemory followObjField: ProcessListsIndex ofObject: sched.
>
>      "Follow all links in the process list to ensure the lists are valid."
>      0 to: (objectMemory numSlotsOf: procLists) - 1 do:
>          [:i| | list first last next |
>          list := objectMemory followObjField: i ofObject: procLists.
>          first := objectMemory followObjField: FirstLinkIndex ofObject: list.
>          last := objectMemory followObjField: LastLinkIndex ofObject: list.
>          [first ~= last] whileTrue:
>              [next := objectMemory followObjField: NextLinkIndex ofObject: first.
>               first := next]]
>  !
>
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Eliot Miranda-2
In reply to this post by commits-2
 
Hi Ryan,

On Mon, Dec 14, 2015 at 7:32 PM, <[hidden email]> wrote:

Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1595.mcz

==================== Summary ====================

Name: VMMaker.oscog-rmacnak.1595
Author: rmacnak
Time: 14 December 2015, 7:29:18.283 pm
UUID: 3aac3671-b1ff-45b9-8ed0-f3ecc5bca0b3
Ancestors: VMMaker.oscog-eem.1594

MIPS: Complete simulation of the Newspeak test suite! (~30 billion instructions) (Modulo Aliens, which don't work under the IA32 simulation either.)

Can you say a little bit more about this?  How long did the simulation take?  What machine(s) did you run it on?  I *love* that you caught the MNU in followForwardingPointersInScheduler. I want to set this up for Squeak but never had the patience/.resources before.

 
Fix off-by-8 in patching I-type branches. Bug had the effect of skipping loading the cPIC address for a cPIC miss if the cPIC was created for an MNU case.

Handle PushCw in storeLiteral:beforeFollowingAddress:.

Add the GC's variant of rewriteInlineCacheTag:at:.

Fix MNU in followForwardingPointersInScheduler.

=============== Diff against VMMaker.oscog-eem.1594 ===============

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteITypeBranchAtAddress:target: (in category 'inline cacheing') -----
  rewriteITypeBranchAtAddress: mcpc target: newTarget
+       | newDisplacement oldInstruction newInstruction |
+       newDisplacement := newTarget - (mcpc + 4). "Displacement is relative to delay slot."
+       newDisplacement := newDisplacement >> 2. "Displacement is in words."
-       | newDisplacement oldInstruction newInstruction |
-       newDisplacement := newTarget - (mcpc - 4). "Displacement relative to delay slot"
-       newDisplacement := newDisplacement >> 2.

        self assert: (newDisplacement between: -16r8000 and: 16r7FFF).
        newDisplacement < 0
                ifTrue: [newDisplacement := newDisplacement + 16r10000]
                ifFalse: [newDisplacement := newDisplacement].
        self assert: (newDisplacement between: 0 and: 16rFFFF).

        oldInstruction := objectMemory longAt: mcpc.
        newInstruction := (oldInstruction bitAnd: 16rFFFF0000) bitOr: newDisplacement.

        objectMemory longAt: mcpc put: newInstruction.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>rewriteInlineCacheTag:at: (in category 'inline cacheing') -----
+ rewriteInlineCacheTag: cacheTag at: callSiteReturnAddress
+       "Rewrite an inline cache with a new tag.  This variant is used
+        by the garbage collector."
+
+       "MoveCwR ClassReg selectorIndex/expectedClass
+        Call: unlinked send stub/expectedTarget
+        Push ReceiverResult <-- callSiteReturnAddress"
+
+       "lui s3, selector/tagHigh
+        ori s3, s3, selector/tagLow
+        lui t9, stub/targetHigh
+        ori t9, t9, stub/targetLow
+        jalr t9
+        nop (delay slot)
+        ...  <-- callSiteReturnAddress"
+
+       <var: #callSiteReturnAddress type: #usqInt>
+       <var: #callTargetAddress type: #usqInt>
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
+       self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
+       self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
+       "cogit disassembleFrom: callSiteReturnAddress - 24 to: callSiteReturnAddress."
+
+       self literalAtAddress: callSiteReturnAddress - 20 put: cacheTag.
+
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
+       self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
+       self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
+       self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
+       "cogit disassembleFrom: callSiteReturnAddress - 24 to: callSiteReturnAddress."!

Item was changed:
  ----- Method: CogMIPSELCompiler>>storeLiteral:beforeFollowingAddress: (in category 'inline cacheing') -----
  storeLiteral: literal beforeFollowingAddress: followingAddress
        "Rewrite the long constant loaded by a MoveCwR or PushCwR before the given address"
-       | lastOpcode lastFunction oriAddress |
        self flag: #bogus. "The caller ought to know what it is patching, and this should be split into separate methods with stricter checking."

+       "Cmp/MoveCwR
+        pc-8   lui rx, uper
+        pc-4   ori rx, rx, lower"
+       (self opcodeAtAddress: followingAddress - 4) = ORI ifTrue:
+               [^self literalAtAddress: followingAddress - 4 put: literal].
+
+       "PushCw
+        pc-16  lui at, upper
+        pc-12  ori at, at, lower
+        pc-8   addiu sp, sp, -4
+        pc-4   sw at, 0(sp)"
+       ((self opcodeAtAddress: followingAddress - 4) = SW and:
+               [(self opcodeAtAddress: followingAddress - 8) = ADDIU]) ifTrue:
+                       [^self literalAtAddress: followingAddress - 12 put: literal].
+
+       self unreachable.
+       ^0!
-       lastOpcode := self opcodeAtAddress: followingAddress - 4.
-       lastFunction := self functionAtAddress: followingAddress - 4.
-       oriAddress := 0.
-       lastOpcode = ORI ifTrue: [oriAddress := followingAddress - 4].
-       lastOpcode = ADDIU ifTrue: [oriAddress := followingAddress - 16].
-       lastOpcode = SPECIAL ifTrue: [lastFunction = SUBU ifTrue: [oriAddress := followingAddress - 8]].
-       self assert: oriAddress ~= 0.
-       ^self literalAtAddress: oriAddress put: literal!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInScheduler (in category 'object memory support') -----
  followForwardingPointersInScheduler
        | schedAssoc sched procLists |
        schedAssoc := objectMemory splObj: SchedulerAssociation.
        "the GC follows pointers in the special objects array for us."
        self assert: (objectMemory isForwarded: schedAssoc) not.

        "Make sure the active process has been followed."
+       objectMemory followForwardedObjectFields: schedAssoc toDepth: 1.
-       self followForwardedObjectFields: schedAssoc toDepth: 1.

        sched := objectMemory fetchPointer: ValueIndex ofObject: schedAssoc.

        procLists := objectMemory followObjField: ProcessListsIndex ofObject: sched.

        "Follow all links in the process list to ensure the lists are valid."
        0 to: (objectMemory numSlotsOf: procLists) - 1 do:
                [:i| | list first last next |
                list := objectMemory followObjField: i ofObject: procLists.
                first := objectMemory followObjField: FirstLinkIndex ofObject: list.
                last := objectMemory followObjField: LastLinkIndex ofObject: list.
                [first ~= last] whileTrue:
                        [next := objectMemory followObjField: NextLinkIndex ofObject: first.
                         first := next]]
  !




--
_,,,^..^,,,_
best, Eliot
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Ryan Macnak
 
On Tue, Dec 15, 2015 at 10:50 AM, Eliot Miranda <[hidden email]> wrote:
 
Hi Ryan,

On Mon, Dec 14, 2015 at 7:32 PM, <[hidden email]> wrote:

Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1595.mcz

==================== Summary ====================

Name: VMMaker.oscog-rmacnak.1595
Author: rmacnak
Time: 14 December 2015, 7:29:18.283 pm
UUID: 3aac3671-b1ff-45b9-8ed0-f3ecc5bca0b3
Ancestors: VMMaker.oscog-eem.1594

MIPS: Complete simulation of the Newspeak test suite! (~30 billion instructions) (Modulo Aliens, which don't work under the IA32 simulation either.)

Can you say a little bit more about this?  How long did the simulation take?  What machine(s) did you run it on?  I *love* that you caught the MNU in followForwardingPointersInScheduler. I want to set this up for Squeak but never had the patience/.resources before.

This was a Newspeak image setup to run the test suite at startup and display the results on the Transcript, running the normal VM simulation setup on my Mac. I think the process had ~19 hours of CPU time when it was finished, but this is an overestimate because the simulation stopped for each of those bugs in the last commit. The IA32 simulation is an order of magnitude faster, Bochs being written in C and my MIPS simulator being written in Smalltalk with gratuitous asserts. Of course the MIPS one is much easier to add a jump buffer to and get a limited form of back-in-time debugging...

I don't think this process is well-suited to automatic testing. Both the VM simulator and the Squeak-based system it's running have too many assumptions that they are running interactively. In the simulator I had to disable prompts that trigger on code compaction, primitiveExecuteMethod, etc. The test harness being run had to be altered to report to the Transcript. And if an unhandled exception had occurred in the simulated image that simulator wouldn't have known to stop. This is tolerable as a one-off to bring a new backend up, but not a productive way to test that the system stays working.

What would be more helpful is if the VM build was fixed to work with a cross compiler, so it would compile fast enough to test ARM and MIPS on Travis CI alongside IA32 and X64. It would also help if the top-of-tree Intel VMs were always kept working so we'd know which change broke something. Moving the Subversion repository to a more reliable host (which likely means migrating to Git) would also cut down on the false positives Travis reports because the Subversion server has a habit of dropping connections.
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Ben Coman

On Wed, Dec 16, 2015 at 10:43 AM, Ryan Macnak <[hidden email]> wrote:

>
> On Tue, Dec 15, 2015 at 10:50 AM, Eliot Miranda <[hidden email]> wrote:
>>
>>
>> Hi Ryan,
>>
>> On Mon, Dec 14, 2015 at 7:32 PM, <[hidden email]> wrote:
>>>
>>>
>>> Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
>>> http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1595.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: VMMaker.oscog-rmacnak.1595
>>> Author: rmacnak
>>> Time: 14 December 2015, 7:29:18.283 pm
>>> UUID: 3aac3671-b1ff-45b9-8ed0-f3ecc5bca0b3
>>> Ancestors: VMMaker.oscog-eem.1594
>>>
>>> MIPS: Complete simulation of the Newspeak test suite! (~30 billion instructions) (Modulo Aliens, which don't work under the IA32 simulation either.)
>>
>>
>> Can you say a little bit more about this?  How long did the simulation take?  What machine(s) did you run it on?  I *love* that you caught the MNU in followForwardingPointersInScheduler. I want to set this up for Squeak but never had the patience/.resources before.
>
>
> This was a Newspeak image setup to run the test suite at startup and display the results on the Transcript, running the normal VM simulation setup on my Mac. I think the process had ~19 hours of CPU time when it was finished, but this is an overestimate because the simulation stopped for each of those bugs in the last commit. The IA32 simulation is an order of magnitude faster, Bochs being written in C and my MIPS simulator being written in Smalltalk with gratuitous asserts. Of course the MIPS one is much easier to add a jump buffer to and get a limited form of back-in-time debugging...
>
> I don't think this process is well-suited to automatic testing. Both the VM simulator and the Squeak-based system it's running have too many assumptions that they are running interactively. In the simulator I had to disable prompts that trigger on code compaction, primitiveExecuteMethod, etc. The test harness being run had to be altered to report to the Transcript. And if an unhandled exception had occurred in the simulated image that simulator wouldn't have known to stop. This is tolerable as a one-off to bring a new backend up, but not a productive way to test that the system stays working.
>
> What would be more helpful is if the VM build was fixed to work with a cross compiler, so it would compile fast enough to test ARM and MIPS on Travis CI alongside IA32 and X64.

As I recently reported, I successfully cross compiled a VM using
CMakeVMMaker on pharo-vm from github, from Debian to (NetBSD based)
RumpKernel.
   https://github.com/pharo-project/pharo-vm

I'll be wanting to do the same targeting ARM later on, per...
   https://github.com/rumpkernel/wiki/wiki/Howto:-Cross-compiling
and even cross-execute it...
   https://github.com/rumpkernel/wiki/wiki/Howto:-Cross-architecture-execution

Except did I read somewhere that Cog doesn't run on top of QEMU?  I
can't find the post I thought I saw describing why.

Right now I'm having a go at cross compiling to RUmpkernel using...
   http://www.mirandabanda.org/cogblog/compiling-the-vm/
   svn co http://www.squeakvm.org/svn/squeak/branches/Cog oscogvm
I've encountered a few things in the autoconf that are incompatible
with cross compiling, which I'm trying to fix and will report soon.

btw, what was the outcome of developing the CMake builds for the svn sources.

cheers -ben


> It would also help if the top-of-tree Intel VMs were always kept working so we'd know which change broke something. Moving the Subversion repository to a more reliable host (which likely means migrating to Git) would also cut down on the false positives Travis reports because the Subversion server has a habit of dropping connections.

+1 github :)
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Eliot Miranda-2
 


On Wed, Dec 16, 2015 at 1:00 AM, Ben Coman <[hidden email]> wrote:

On Wed, Dec 16, 2015 at 10:43 AM, Ryan Macnak <[hidden email]> wrote:
>
> On Tue, Dec 15, 2015 at 10:50 AM, Eliot Miranda <[hidden email]> wrote:
>>
>>
>> Hi Ryan,
>>
>> On Mon, Dec 14, 2015 at 7:32 PM, <[hidden email]> wrote:
>>>
>>>
>>> Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
>>> http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1595.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: VMMaker.oscog-rmacnak.1595
>>> Author: rmacnak
>>> Time: 14 December 2015, 7:29:18.283 pm
>>> UUID: 3aac3671-b1ff-45b9-8ed0-f3ecc5bca0b3
>>> Ancestors: VMMaker.oscog-eem.1594
>>>
>>> MIPS: Complete simulation of the Newspeak test suite! (~30 billion instructions) (Modulo Aliens, which don't work under the IA32 simulation either.)
>>
>>
>> Can you say a little bit more about this?  How long did the simulation take?  What machine(s) did you run it on?  I *love* that you caught the MNU in followForwardingPointersInScheduler. I want to set this up for Squeak but never had the patience/.resources before.
>
>
> This was a Newspeak image setup to run the test suite at startup and display the results on the Transcript, running the normal VM simulation setup on my Mac. I think the process had ~19 hours of CPU time when it was finished, but this is an overestimate because the simulation stopped for each of those bugs in the last commit. The IA32 simulation is an order of magnitude faster, Bochs being written in C and my MIPS simulator being written in Smalltalk with gratuitous asserts. Of course the MIPS one is much easier to add a jump buffer to and get a limited form of back-in-time debugging...
>
> I don't think this process is well-suited to automatic testing. Both the VM simulator and the Squeak-based system it's running have too many assumptions that they are running interactively. In the simulator I had to disable prompts that trigger on code compaction, primitiveExecuteMethod, etc. The test harness being run had to be altered to report to the Transcript. And if an unhandled exception had occurred in the simulated image that simulator wouldn't have known to stop. This is tolerable as a one-off to bring a new backend up, but not a productive way to test that the system stays working.
>
> What would be more helpful is if the VM build was fixed to work with a cross compiler, so it would compile fast enough to test ARM and MIPS on Travis CI alongside IA32 and X64.

As I recently reported, I successfully cross compiled a VM using
CMakeVMMaker on pharo-vm from github, from Debian to (NetBSD based)
RumpKernel.
   https://github.com/pharo-project/pharo-vm

I'll be wanting to do the same targeting ARM later on, per...
   https://github.com/rumpkernel/wiki/wiki/Howto:-Cross-compiling
and even cross-execute it...
   https://github.com/rumpkernel/wiki/wiki/Howto:-Cross-architecture-execution

Except did I read somewhere that Cog doesn't run on top of QEMU?  I
can't find the post I thought I saw describing why.

Right now I'm having a go at cross compiling to RUmpkernel using...
   http://www.mirandabanda.org/cogblog/compiling-the-vm/
   svn co http://www.squeakvm.org/svn/squeak/branches/Cog oscogvm
I've encountered a few things in the autoconf that are incompatible
with cross compiling, which I'm trying to fix and will report soon.

btw, what was the outcome of developing the CMake builds for the svn sources.

The person doing it dropped out of the conversation.  I fear I didn't give him enough time or feedback.  They contributed input support for the simulator which I'm now using, but it was some months after the contribution that I was able to integrate it.

cheers -ben


> It would also help if the top-of-tree Intel VMs were always kept working so we'd know which change broke something. Moving the Subversion repository to a more reliable host (which likely means migrating to Git) would also cut down on the false positives Travis reports because the Subversion server has a habit of dropping connections.

+1 github :)



--
_,,,^..^,,,_
best, Eliot
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Ben Coman
 
On Thu, Dec 17, 2015 at 1:15 AM, Eliot Miranda <[hidden email]> wrote:
>
> On Wed, Dec 16, 2015 at 1:00 AM, Ben Coman <[hidden email]> wrote:
>>
>> btw, what was the outcome of developing the CMake builds for the svn sources.
>
> The person doing it dropped out of the conversation.  I fear I didn't give him enough time or feedback.  They contributed input support for the simulator which I'm now using, but it was some months after the contribution that I was able to integrate it.

Okay.  (I asked this a slightly different way on another post before I
saw your answer)
Where do I find it?  It still looks like autoconf under per...
http://www.mirandabanda.org/cogblog/compiling-the-vm/

$ svn co http://www.squeakvm.org/svn/squeak/branches/Cog oscogvm
$ find oscogvm -iname "*cmake*"
shows only...
./image/old/BuildSqueak46TrunkCMakeVMMakerImage.st
./image/old/buildsqueakcmakeimage.sh
./image/old/CMakeVMMakerSqueak.text
./image/old/README.buildsqueakcmakeimage
./image/old/BuildSqueak46CMakeVMMakerImage.st
./processors/ARM/gdb-7.10/zlib/CMakeLists.txt
./processors/ARM/gdb-7.10/zlib/zconf.h.cmakein
./processors/ARM/gdb-7.10/zlib/zlib.pc.cmakein
./platforms/unix/vm-sound-pulse/config.cmake
./platforms/unix/plugins/XDisplayControlPlugin/config.cmake
./platforms/unix/plugins/XDisplayControlPlugin/build.cmake
./platforms/unix/plugins/SqueakSSL/config.cmake

Is that it under "old" ?

cheers -ben
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Eliot Miranda-2
In reply to this post by Ryan Macnak
 
Hi Ryan,

    I'll just respond to your point about keeping VMs working for now.

On Tue, Dec 15, 2015 at 6:43 PM, Ryan Macnak <[hidden email]> wrote:
 
On Tue, Dec 15, 2015 at 10:50 AM, Eliot Miranda <[hidden email]> wrote:
 
Hi Ryan,

On Mon, Dec 14, 2015 at 7:32 PM, <[hidden email]> wrote:

Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1595.mcz

==================== Summary ====================

Name: VMMaker.oscog-rmacnak.1595
Author: rmacnak
Time: 14 December 2015, 7:29:18.283 pm
UUID: 3aac3671-b1ff-45b9-8ed0-f3ecc5bca0b3
Ancestors: VMMaker.oscog-eem.1594

MIPS: Complete simulation of the Newspeak test suite! (~30 billion instructions) (Modulo Aliens, which don't work under the IA32 simulation either.)

Can you say a little bit more about this?  How long did the simulation take?  What machine(s) did you run it on?  I *love* that you caught the MNU in followForwardingPointersInScheduler. I want to set this up for Squeak but never had the patience/.resources before.

This was a Newspeak image setup to run the test suite at startup and display the results on the Transcript, running the normal VM simulation setup on my Mac. I think the process had ~19 hours of CPU time when it was finished, but this is an overestimate because the simulation stopped for each of those bugs in the last commit. The IA32 simulation is an order of magnitude faster, Bochs being written in C and my MIPS simulator being written in Smalltalk with gratuitous asserts. Of course the MIPS one is much easier to add a jump buffer to and get a limited form of back-in-time debugging...

I don't think this process is well-suited to automatic testing. Both the VM simulator and the Squeak-based system it's running have too many assumptions that they are running interactively. In the simulator I had to disable prompts that trigger on code compaction, primitiveExecuteMethod, etc. The test harness being run had to be altered to report to the Transcript. And if an unhandled exception had occurred in the simulated image that simulator wouldn't have known to stop. This is tolerable as a one-off to bring a new backend up, but not a productive way to test that the system stays working.

What would be more helpful is if the VM build was fixed to work with a cross compiler, so it would compile fast enough to test ARM and MIPS on Travis CI alongside IA32 and X64. It would also help if the top-of-tree Intel VMs were always kept working so we'd know which change broke something.

I very much agree.  Apologies for the current situation.  AFAICT the build is broken for reasons other than that the basic VM isn't correct.  I'm able to build and run on macos32x86 and macos64x64 now.  As soon as I've got the x64 up and running (should be today) I'll fix the builds.  Better, I promise to attend to the builds tomorrow at the latest.


Moving the Subversion repository to a more reliable host (which likely means migrating to Git) would also cut down on the false positives Travis reports because the Subversion server has a habit of dropping connections.




--
_,,,^..^,,,_
best, Eliot
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker.oscog-rmacnak.1595.mcz

Ben Coman
In reply to this post by Eliot Miranda-2

> On Wed, Dec 16, 2015 at 1:00 AM, Ben Coman <[hidden email]> wrote:
>>
>>
>> On Wed, Dec 16, 2015 at 10:43 AM, Ryan Macnak <[hidden email]> wrote:
>> >
>> > What would be more helpful is if the VM build was fixed to work with a cross compiler, so it would compile fast enough to test ARM and MIPS on Travis CI alongside IA32 and X64.
>> >
>> > It would also help if the top-of-tree Intel VMs were always kept working so we'd know which change broke something. Moving the Subversion repository to a more reliable host (which likely means migrating to Git) would also cut down on the false positives Travis reports because the Subversion server has a habit of dropping connections.
>>
>> +1 github :)

btw, Did you know that github supports subversion clients since 2011 [1]?
Here are supported features [2].  Are these sufficient for your
current svn workflows?
Potentially we could have ONE repository and those liking subversion
can stick with it and those liking git can use that.  Of course, this
would need to be proven.

[4] Provides pragmatic advice for cutting over.  Esteban appears to
have done similar to step 1 and 2 [3] - but it seem sometimes his
modifications directly update this mirror so its not clear to see when
that branch is an *exact* copy of the current svn trunk.  So I'd love
to see a github repository that is always an *exact* mirror of the svn
repository, with any pharo mods occurring in a branch off that.  Even
better if the repository for svn users resides on github in place of
that mirror.

I've been googling around for problems reported using github via an
svn client, and haven't found any smoking guns.
Is this something we can trial?  I'm willing to put some effort into
it.  A key requirement would be not interrupting Eliots work on
Spur-64.  Potentially we could stay for months on step 3 [4] with the
CI infrastructure running on the git side, but code check-ins
continuing onthe svn side.

btw2, [5] provides a use case for the advantages of a full switch.

cheers -ben

[1] https://github.com/blog/966-improved-subversion-client-support
[2] https://help.github.com/articles/support-for-subversion-clients/
[3] https://github.com/pharo-project/pharo-vm/network
[4] http://blogs.atlassian.com/2013/01/atlassian-svn-to-git-migration-technical-side/
[5] http://blogs.atlassian.com/2013/01/svn-to-git-how-atlassian-made-the-switch-without-sacrificing-active-development/