39
Bee Smalltalk RunTime: anchor's aweigh Javier Pimás DISARMISTA S.R.L.

Bee Smalltalk RunTime: anchor's aweigh

  • Upload
    esug

  • View
    269

  • Download
    1

Embed Size (px)

DESCRIPTION

Title: Bee Smalltalk RunTime: anchor's aweigh Speaker: Javier Pimás Wed, August 20, 3:00pm – 3:30pm Video Part1: https://www.youtube.com/watch?v=82nZ1Oo2LF0 Video Part2: https://www.youtube.com/watch?v=eQ6r5ETskKE Description Abstract: Bee is a Smalltalk dialect. Its runtime is exceptional in that it is completely written in Smalltalk. Bee includes a minimal kernel with on-demand loaded libraries, a JIT compiler, an FFI interface, an optimizing SSA-based compiler, a garbage collector, and native threading support among other things. Despite being written in Smalltalk, Bee achieves promising performance levels. Bio: Javier Pimas has been programming since he was a kid. Years ago he entered Smalltalk world and started studying topics both high and low-level related. As part of his MSc thesis he studied and extended SqueakNOS operating system, and has been working on VMs and JIT compilers since then.

Citation preview

Page 1: Bee Smalltalk RunTime: anchor's aweigh

Bee Smalltalk RunTime:anchor's aweigh

Javier Pimás

DISARMISTA S.R.L.

Page 2: Bee Smalltalk RunTime: anchor's aweigh

Bits of Bee history

Gerardo Richarte Javier Burroni

Page 3: Bee Smalltalk RunTime: anchor's aweigh

Bits of Bee history

1. a JIT in smalltalk

2. added underprimitives and a GC

3. can we get rid of the VM?

Page 4: Bee Smalltalk RunTime: anchor's aweigh

How to start?

Page 5: Bee Smalltalk RunTime: anchor's aweigh

Start afresh

With Objects :)

BeeLibrary

Page 6: Bee Smalltalk RunTime: anchor's aweigh

Start afresh

With Objects :)

BeeLibraryBeeLibrary

SKernel

Page 7: Bee Smalltalk RunTime: anchor's aweigh

Start afresh

With Objects :)

BeeLibraryBeeLibrarySKernel

NativeCode

Array variableSubclass: #CompiledMethod instanceVariableNames: ' bytecodes nativeCode class

selector source flags '

Page 8: Bee Smalltalk RunTime: anchor's aweigh

Start afresh

With Objects :)

BeeLibraryBeeLibrarySKernel

NativeCode

Object subclass: #NativeCode instanceVariableNames: ' code references isFresh'

Page 9: Bee Smalltalk RunTime: anchor's aweigh

Start afresh

How to start?

With Objects :)

BeeLibrary

<16r0000> A8 01 75 0B 81 78 FC 60 C4 AB 00 75 0E EB 1B 81<16r0010> 3D 67 C4 AB 00 60 C4 AB 00 74 0F B9 60 C4 AB 00<16r0020> E9 48 C4 AB 00 90 90 90 90 90 55 8B EC 50 8B<16r0030> 68 60 C4 AB 00 68 60 C4 AB 00 68 60 C4 AB 00 68 <16r0040> 60 C4 AB 00 A1 60 C4 AB 00 68 60 C4 AB 00 FF 15 <16r0050> 60 C4 AB 00 89 45 F4 A1 60 C4 AB 00 68 60 C4 AB<16r0060> 00 FF 15 60 C4 AB 00 89 45 F0 A1 60 C4 AB 00 68<16r0070> 60 C4 AB 00 FF 15 60 C4 AB 00 50 8B 45 F0 68 60<16r0080> C4 AB 00 FF 15 60 C4 AB 00 FF 75 08 FF 75 F4 FF<16r0090> 75 F0 8B 45 E4 68 60 C4 AB 00 FF 15 60 C4 AB 00<16r00A0> 58 68 60 C4 AB 00 FF 15 60 C4 AB 00 8B 45 F4 68 <16r00B0> 60 C4 AB 00 FF 15 60 C4 AB 00 89 45 EC FF 35 60<16r00C0> C4 AB 00 8B 45 EC 68 60 C4 AB 00 FF 15 60 C4 AB<16r00D0> 00 50 8B 45 E8 68 60 C4 AB 00 FF 15 60 C4 AB 00<16r00E0> 83 C4 04 89 06 50 8B 45 EC 68 60 C4 AB 00 FF 15<16r00F0> 60 C4 AB 00 50 FF 75 EC 8B 45 E8 68 60 C4 AB 00<16r0100> FF 15 60 C4 AB 00 83 C4 04 8B 45 F4 68 60 C4 AB<16r0110> 00 FF 15 60 C4 AB 00 89 46 04 8B C6 68 60 C4 AB<16r0120> 00 FF 15 60 C4 AB 00 8B C6 8B E5 5D 8B 75 FC C2<16r0130> 04 00

Object subclass: #NativeCode instanceVariableNames: ' code references isFresh'

Page 10: Bee Smalltalk RunTime: anchor's aweigh

Start afresh

How to start?

With Objects :)

BeeLibrary

Object subclass: #NativeCode instanceVariableNames: ' code references isFresh'

test AL 1 jnz F cmp [EAX-4], ABC460 jnz 1B jmp 2A cmp [ABC467], ABC460 jz 2A mov ECX, ABC460 jmp ABC46D nop nop nop nop nop push EBP mov EBP, ESP push EAX mov ESI, EAX push ABC460 push ABC460 push ABC460 push ABC460 mov EAX, [ABC460] push ABC460 call MemNear pusha les EBP

Page 11: Bee Smalltalk RunTime: anchor's aweigh

Start afresh

How to start?

With Objects :)

BeeLibrary

Object subclass: #NativeCode instanceVariableNames: ' code references isFresh'

test AL 1 jnz F cmp [EAX-4], ABC460 jnz 1B jmp 2A cmp [ABC467], ABC460 jz 2A mov ECX, ABC460 jmp ABC46D nop nop nop nop nop push EBP mov EBP, ESP push EAX mov ESI, EAX push ABC460 push ABC460 push ABC460 push ABC460 mov EAX, [ABC460] push ABC460 call MemNear pusha les EBP

Page 12: Bee Smalltalk RunTime: anchor's aweigh

So we got rid of the VM, right?

Page 13: Bee Smalltalk RunTime: anchor's aweigh

NO!

Page 14: Bee Smalltalk RunTime: anchor's aweigh

Working hypothesis:HostVM leverage

● Basic objects● Method lookup● Primitives● Native Helpers

Page 15: Bee Smalltalk RunTime: anchor's aweigh

for instance:– true– false– nil– characters – Array

HostVM leverage – Basic Objects

LoadTrueBytecode>>#assembleself loadTrue

Page 16: Bee Smalltalk RunTime: anchor's aweigh

Direct access to VM functions

HostVM leverage – Method lookup

lookupAndCall| selector |selector := self compiledMethod selector.assembler loadSelector: selector oop.self holdReferenceTo: selector.assembler jumpTo: #VM_lookupAndCall from: #hostVM.dll'

Page 17: Bee Smalltalk RunTime: anchor's aweigh

We used HostVM' primitives as a way to have bit-a-bit compatibility

HostVM leverage - Primitives

SmalltalkBytecode>>#prepareFrameprimitive := self nextByte.cm := self compiledMethod.assembler loadTempPointer: cm oop.self holdReferenceTo: cm; callPrimitive: primitive.super prepareFrame

Page 18: Bee Smalltalk RunTime: anchor's aweigh

Small pieces of code in the HostVM acting as primitives but without their protocol.

as a bit-a-bit compatible JIT, we were using those helpers

HostVM leverage - Native Helpers

callNewArrayself emitCallTo: #VM_newArray from: #'hostVM.dll'

Page 19: Bee Smalltalk RunTime: anchor's aweigh

Connecting methods: lookup

BeeLibraryBeeLibrarySKernel

NativeCode

Object>>#_lookupAndInvoke: aSymbol

lookup

Page 20: Bee Smalltalk RunTime: anchor's aweigh

Connecting methods: lookupmov eax, off_427090push offset aGetcommandline ; "getCommandLine"call Object__lookupAndInvokeNativeCode

Object>>#_lookupAndInvoke: aSymbol| cm |cm := self _lookup: aSymbol.cm == nil ifTrue: [

cm := self _lookup: #doesNotUnderstand:.self _transferControlTo: cm noClassCheckEntrypoint _asNative].

cm prepareForExecution; patchClassCheckTo: self behavior.self

_transferControlDiscardingLastArgAndPatchingTo: cm noClassCheckEntrypoint _asNative

LookupNativizer

Page 21: Bee Smalltalk RunTime: anchor's aweigh

assembleTestSmallInteger| integer |integer := assembler testAndJumpIfInteger.self loadObject: false.assembler uncontionalSkip: [

assembler jumpDestinationFor: integer.self loadObject: true]

Smalltalk semantics: underprimitives

behavior^self _isSmallInteger

ifTrue: [SmallInteger methodDictionaries]ifFalse: [self _basicAt: 0]

assembleBasicAt| nonInteger |nonInteger := assembler convertArgToIntegerOrJumpassembler

framelessSlotAtArg;jumpDestinationFor: nonInteger

Page 22: Bee Smalltalk RunTime: anchor's aweigh

BlockClosure>>#primitiveBeeValueself argumentCount = 0 ifFalse: [^self primitiveFailed].self _transferControlTo: self code

Connecting methods: BlockClosureanySatisfy: aBlock

self detect: aBlock ifNone: [^false].^true

Page 23: Bee Smalltalk RunTime: anchor's aweigh

Creating objects: new

Object new

BeeLibraryBeeLibrarySKernel

NativeCode

lookupinitialarena

free big arena

external memory

Page 24: Bee Smalltalk RunTime: anchor's aweigh

Behavior>>#primitiveNew^self primitiveNewPointers: self instSize

Object new

Behavior>>#primitiveNewPointers: size| object |object := self allocate: size * 4 size: size.self isFixed ifTrue: [object _beFixed; _beNamed].1 to: size do: [:i | object _basicAt: i put: nil].^object

Creating objects: new

Page 25: Bee Smalltalk RunTime: anchor's aweigh

More primitives

BeeLibraryBeeLibrarySKernel

NativeCode

relatedTo:

lookuparena

primitives

Symbol String

perform:

FFI

Object

IntegerExternalMemory

FFI

Et cetera

Page 26: Bee Smalltalk RunTime: anchor's aweigh

Putting things together

BeeLibraryBeeLibrarySKernel.EXE

NativeCode

lookuparena

primitives

start| result |result := self initializeBee; run.self exit: result

generateFullKernel| closure filename |

builder := KernelLibraryBuilder newNamed: 'bee'.project := SmalltalkProject getProject: 'Skernel'.project buildLibraryOn: builder.

self addFutureSmalltalk; addTrueFalseAndNil;

addBeeKernelClasses;addMinimalKernelMethods;addLookup;addPrimitives;addArena;remapCharactersArray.

aBlock value.^builder

storeNativeCode;useDllMode;writeBSL

Page 27: Bee Smalltalk RunTime: anchor's aweigh

Some magic

BeeLibraryBeeLibrarySKernel

NativeCode

lookuparena

primitives

PEFile new

Page 28: Bee Smalltalk RunTime: anchor's aweigh

BeeLibraryBeeLibrarySKernel.EXE

NativeCode

lookuparena

primitives

PEFile new

Some magic

Page 29: Bee Smalltalk RunTime: anchor's aweigh

Some magic

BeeLibraryBeeLibrarySKernel

NativeCode

lookuparena

primitives

PEFile new

Page 30: Bee Smalltalk RunTime: anchor's aweigh

BeeLibraryBeeLibrarySKernel.EXE

NativeCode

lookuparena

primitives

PEFile new

Some magic

Page 31: Bee Smalltalk RunTime: anchor's aweigh

Bee-ing minimal

Page 32: Bee Smalltalk RunTime: anchor's aweigh

Many small libraries

BeeLibraryBeeLibrarybee.exe

NativeCode

BeeLibraryBeeLibraryapp.bsl

NativeCode

Page 33: Bee Smalltalk RunTime: anchor's aweigh

Adding nativizer support

BeeLibraryBeeLibrarybee.exe

NativeCode

BeeLibraryBeeLibrarylib.bslBeeLibraryBeeLibraryJIT.bsl

NativeCode

Page 34: Bee Smalltalk RunTime: anchor's aweigh

Adding compiler support

BeeLibraryBeeLibrarybee.exe

NativeCode

BeeLibraryBeeLibrarycmpilr.bslBeeLibraryBeeLibraryJIT.bsl

NativeCode

fooTranscript show: 'hello'

Page 35: Bee Smalltalk RunTime: anchor's aweigh

Demo

Page 36: Bee Smalltalk RunTime: anchor's aweigh

BeeLibraryBeeLibrarySKernel.EXE

NativeCode

lookuparena

primitives

Multithread

Browsers

Perf

Working on:

Opening

Page 37: Bee Smalltalk RunTime: anchor's aweigh

BeeLibraryBeeLibrarySKernel.EXE

NativeCode

lookuparena

primitives

Multithread

GC

Dbg

Remoting

Future:

Browsers

Performnc

Opening

Page 38: Bee Smalltalk RunTime: anchor's aweigh

BeeLibraryBeeLibrarySKernel.EXE

NativeCode

lookuparena

primitives

Multithread

GC

Dbg

Remoting

+ Perf

ARM

64 bits

(hoping not so) far future:

Browsers

Performnc

Opening

Page 39: Bee Smalltalk RunTime: anchor's aweigh

[Audience hasQuestions] whileTrue: [self answer: Audience nextQuestion].

Audience do: [:you | self thank: you].

self returnTo: Audience