@@ -43,21 +43,20 @@ Execution of a program begins by creating a stack frame for the `main`
4343function and executing its function body. Before execution begins, the
4444function map and the initial memory have to be set up.
4545
46- ``` k
46+ All of this is done in the client code so we omit the initialisation code which was historically placed here.
47+
48+ ```
4749 // #init step, assuming a singleton in the K cell
48- rule <k> #init(_NAME:Symbol _ALLOCS:GlobalAllocs FUNCTIONS:FunctionNames ITEMS :MonoItems TYPES :TypeMappings _MACHINE:MachineInfo)
50+ rule <k> #init(_NAME:Symbol _ALLOCS:GlobalAllocs FUNCTIONS:FunctionNames _ITEMS :MonoItems _TYPES :TypeMappings _MACHINE:MachineInfo)
4951 =>
5052 #execFunction(#findItem(ITEMS, FUNCNAME), FUNCTIONS)
5153 </k>
52- <functions> _ => #mkFunctionMap(FUNCTIONS, ITEMS) </functions>
53- <start-symbol> FUNCNAME </start-symbol>
54- <types> _ => #mkTypeMap(.Map, TYPES) </types>
5554```
5655
5756The ` Map ` of types is static information used for decoding constants and allocated data into ` Value ` s.
5857It maps ` Ty ` IDs to ` TypeInfo ` that can be supplied to decoding and casting functions as well as operations involving ` Aggregate ` values (related to ` struct ` s and ` enum ` s).
5958
60- ``` k
59+ ```
6160 syntax Map ::= #mkTypeMap ( Map, TypeMappings ) [function, total, symbol("mkTypeMap")]
6261
6362 rule #mkTypeMap(ACC, .TypeMappings) => ACC
@@ -83,7 +82,7 @@ they are callee in a `Call` terminator within an `Item`).
8382
8483The function _ names_ and _ ids_ are not relevant for calls and therefore dropped.
8584
86- ``` k
85+ ```
8786 syntax Map ::= #mkFunctionMap ( FunctionNames, MonoItems ) [ function, total, symbol("mkFunctionMap") ]
8887 | #accumFunctions ( Map, Map, FunctionNames ) [ function, total ]
8988 | #accumItems ( Map, MonoItems ) [ function, total ]
@@ -138,7 +137,7 @@ structure from its function body and then execute the first basic
138137block of the body. The function's ` Ty ` index in the ` functions ` map must
139138be known to populate the ` currentFunc ` field.
140139
141- ``` k
140+ ```
142141 // find function through its MonoItemFn.name
143142 syntax MonoItem ::= #findItem ( MonoItems, Symbol ) [ function ]
144143
@@ -185,20 +184,9 @@ be known to populate the `currentFunc` field.
185184 [owise]
186185
187186 rule #tyFromName(_, .List) => ty(-1) // HACK see #mainIsMinusOne above
188-
189- syntax List ::= toKList(BasicBlocks) [function, total]
190-
191- rule toKList( .BasicBlocks ) => .List
192- rule toKList(B:BasicBlock REST:BasicBlocks) => ListItem(B) toKList(REST)
193-
194- syntax List ::= #reserveFor( LocalDecls ) [function, total]
195-
196- rule #reserveFor(.LocalDecls) => .List
197-
198- rule #reserveFor(localDecl(TY, _, MUT) REST:LocalDecls)
199- =>
200- ListItem(newLocal(TY, MUT)) #reserveFor(REST)
201187```
188+ #### Function Execution
189+
202190
203191Executing a function body consists of repeated calls to ` #execBlock `
204192for the basic blocks that, together, constitute the function body. The
@@ -345,7 +333,7 @@ If the local `_0` does not have a value (i.e., it remained uninitialised), the f
345333 </k>
346334 <currentFunc> _ => CALLER </currentFunc>
347335 //<currentFrame>
348- <currentBody> _ => #getBlocks(FUNCS, CALLER) </currentBody>
336+ <currentBody> _ => #getBlocks(CALLER) </currentBody>
349337 <caller> CALLER => NEWCALLER </caller>
350338 <dest> DEST => NEWDEST </dest>
351339 <target> someBasicBlockIdx(TARGET) => NEWTARGET </target>
@@ -354,9 +342,6 @@ If the local `_0` does not have a value (i.e., it remained uninitialised), the f
354342 //</currentFrame>
355343 // remaining call stack (without top frame)
356344 <stack> ListItem(StackFrame(NEWCALLER, NEWDEST, NEWTARGET, UNWIND, NEWLOCALS)) STACK => STACK </stack>
357- <functions> FUNCS </functions>
358- requires CALLER in_keys(FUNCS)
359- [preserves-definedness] // CALLER lookup defined
360345
361346 // no value to return, skip writing
362347 rule <k> #execTerminator(terminator(terminatorKindReturn, _SPAN)) ~> _
@@ -365,7 +350,7 @@ If the local `_0` does not have a value (i.e., it remained uninitialised), the f
365350 </k>
366351 <currentFunc> _ => CALLER </currentFunc>
367352 //<currentFrame>
368- <currentBody> _ => #getBlocks(FUNCS, CALLER) </currentBody>
353+ <currentBody> _ => #getBlocks(CALLER) </currentBody>
369354 <caller> CALLER => NEWCALLER </caller>
370355 <dest> _ => NEWDEST </dest>
371356 <target> someBasicBlockIdx(TARGET) => NEWTARGET </target>
@@ -374,15 +359,11 @@ If the local `_0` does not have a value (i.e., it remained uninitialised), the f
374359 //</currentFrame>
375360 // remaining call stack (without top frame)
376361 <stack> ListItem(StackFrame(NEWCALLER, NEWDEST, NEWTARGET, UNWIND, NEWLOCALS)) STACK => STACK </stack>
377- <functions> FUNCS </functions>
378- requires CALLER in_keys(FUNCS)
379- [preserves-definedness] // CALLER lookup defined
380362
381- syntax List ::= #getBlocks(Map, Ty) [function]
382- | #getBlocksAux(MonoItemKind) [function, total]
363+ syntax List ::= #getBlocks( Ty ) [function, total ]
364+ | #getBlocksAux( MonoItemKind ) [function, total]
383365
384- rule #getBlocks(FUNCS, ID) => #getBlocksAux({FUNCS[ID]}:>MonoItemKind)
385- requires ID in_keys(FUNCS)
366+ rule #getBlocks(TY) => #getBlocksAux(lookupFunction(TY))
386367
387368 // returns blocks from the body
388369 rule #getBlocksAux(monoItemFn(_, _, noBody)) => .List
@@ -391,6 +372,11 @@ If the local `_0` does not have a value (i.e., it remained uninitialised), the f
391372 rule #getBlocksAux(monoItemStatic(_, _, _)) => .List // should not occur in calls
392373 rule #getBlocksAux(monoItemGlobalAsm(_)) => .List // not supported
393374 rule #getBlocksAux(IntrinsicFunction(_)) => .List // intrinsics have no body
375+
376+ syntax List ::= toKList(BasicBlocks) [function, total]
377+ // ---------------------------------------------------
378+ rule toKList( .BasicBlocks ) => .List
379+ rule toKList(B:BasicBlock REST:BasicBlocks) => ListItem(B) toKList(REST)
394380```
395381
396382When a ` terminatorKindReturn ` is executed but the optional target is empty
@@ -434,18 +420,14 @@ where the returned result should go.
434420 // Intrinsic function call - execute directly without state switching
435421 rule <k> #execTerminator(terminator(terminatorKindCall(FUNC, ARGS, DEST, TARGET, _UNWIND), _SPAN)) ~> _
436422 =>
437- #execIntrinsic({FUNCTIONS[ #tyOfCall(FUNC)]}:>MonoItemKind , ARGS, DEST) ~> #continueAt(TARGET)
423+ #execIntrinsic(lookupFunction( #tyOfCall(FUNC)) , ARGS, DEST) ~> #continueAt(TARGET)
438424 </k>
439- <functions> FUNCTIONS </functions>
440- requires #tyOfCall(FUNC) in_keys(FUNCTIONS)
441- andBool isMonoItemKind(FUNCTIONS[#tyOfCall(FUNC)])
442- andBool isIntrinsicFunction({FUNCTIONS[#tyOfCall(FUNC)]}:>MonoItemKind)
443- [preserves-definedness] // callee lookup defined
425+ requires isIntrinsicFunction(lookupFunction(#tyOfCall(FUNC)))
444426
445427 // Regular function call - full state switching and stack setup
446428 rule <k> #execTerminator(terminator(terminatorKindCall(FUNC, ARGS, DEST, TARGET, UNWIND), _SPAN)) ~> _
447429 =>
448- #setUpCalleeData({FUNCTIONS[ #tyOfCall(FUNC)]}:>MonoItemKind , ARGS)
430+ #setUpCalleeData(lookupFunction( #tyOfCall(FUNC)) , ARGS)
449431 </k>
450432 <currentFunc> CALLER => #tyOfCall(FUNC) </currentFunc>
451433 <currentFrame>
@@ -457,11 +439,7 @@ where the returned result should go.
457439 <locals> LOCALS </locals>
458440 </currentFrame>
459441 <stack> STACK => ListItem(StackFrame(OLDCALLER, OLDDEST, OLDTARGET, OLDUNWIND, LOCALS)) STACK </stack>
460- <functions> FUNCTIONS </functions>
461- requires #tyOfCall(FUNC) in_keys(FUNCTIONS)
462- andBool isMonoItemKind(FUNCTIONS[#tyOfCall(FUNC)])
463- andBool notBool isIntrinsicFunction({FUNCTIONS[#tyOfCall(FUNC)]}:>MonoItemKind)
464- [preserves-definedness] // callee lookup defined
442+ requires notBool isIntrinsicFunction(lookupFunction(#tyOfCall(FUNC)))
465443
466444 syntax Bool ::= isIntrinsicFunction(MonoItemKind) [function]
467445 rule isIntrinsicFunction(IntrinsicFunction(_)) => true
@@ -506,6 +484,14 @@ An operand may be a `Reference` (the only way a function could access another fu
506484 </currentFrame>
507485 // TODO: Haven't handled "noBody" case
508486
487+ syntax List ::= #reserveFor( LocalDecls ) [function, total]
488+
489+ rule #reserveFor(.LocalDecls) => .List
490+
491+ rule #reserveFor(localDecl(TY, _, MUT) REST:LocalDecls)
492+ =>
493+ ListItem(newLocal(TY, MUT)) #reserveFor(REST)
494+
509495
510496 syntax KItem ::= #setArgsFromStack ( Int, Operands)
511497 | #setArgFromStack ( Int, Operand)
@@ -631,11 +617,10 @@ Execution gets stuck (no matching rule) when operands have different types or un
631617``` k
632618 // Raw eq: dereference operands, extract types, and delegate to typed comparison
633619 rule <k> #execIntrinsic(IntrinsicFunction(symbol("raw_eq")), ARG1:Operand ARG2:Operand .Operands, PLACE)
634- => #execRawEqTyped(PLACE, #withDeref(ARG1), #extractOperandType(#withDeref(ARG1), LOCALS, TYPEMAP ),
635- #withDeref(ARG2), #extractOperandType(#withDeref(ARG2), LOCALS, TYPEMAP ))
620+ => #execRawEqTyped(PLACE, #withDeref(ARG1), #extractOperandType(#withDeref(ARG1), LOCALS),
621+ #withDeref(ARG2), #extractOperandType(#withDeref(ARG2), LOCALS))
636622 ... </k>
637623 <locals> LOCALS </locals>
638- <types> TYPEMAP </types>
639624
640625 // Compare values only if types are identical
641626 syntax KItem ::= #execRawEqTyped(Place, Evaluation, MaybeTy, Evaluation, MaybeTy) [seqstrict(2,4)]
@@ -655,17 +640,17 @@ Execution gets stuck (no matching rule) when operands have different types or un
655640 rule #withDeref(OP) => OP [owise]
656641
657642 // Extract type from operands (locals with projections, constants, fallback to unknown)
658- syntax MaybeTy ::= #extractOperandType(Operand, List, Map ) [function, total]
659- rule #extractOperandType(operandCopy(place(local(I), PROJS)), LOCALS, TYPEMAP )
660- => getTyOf(tyOfLocal({LOCALS[I]}:>TypedLocal), PROJS, TYPEMAP )
643+ syntax MaybeTy ::= #extractOperandType(Operand, List) [function, total]
644+ rule #extractOperandType(operandCopy(place(local(I), PROJS)), LOCALS)
645+ => getTyOf(tyOfLocal({LOCALS[I]}:>TypedLocal), PROJS)
661646 requires 0 <=Int I andBool I <Int size(LOCALS) andBool isTypedLocal(LOCALS[I])
662647 [preserves-definedness]
663- rule #extractOperandType(operandMove(place(local(I), PROJS)), LOCALS, TYPEMAP )
664- => getTyOf(tyOfLocal({LOCALS[I]}:>TypedLocal), PROJS, TYPEMAP )
648+ rule #extractOperandType(operandMove(place(local(I), PROJS)), LOCALS)
649+ => getTyOf(tyOfLocal({LOCALS[I]}:>TypedLocal), PROJS)
665650 requires 0 <=Int I andBool I <Int size(LOCALS) andBool isTypedLocal(LOCALS[I])
666651 [preserves-definedness]
667- rule #extractOperandType(operandConstant(constOperand(_, _, mirConst(_, TY, _))), _, _ ) => TY
668- rule #extractOperandType(_, _, _ ) => TyUnknown [owise]
652+ rule #extractOperandType(operandConstant(constOperand(_, _, mirConst(_, TY, _))), _) => TY
653+ rule #extractOperandType(_, _) => TyUnknown [owise]
669654```
670655
671656### Stopping on Program Errors
@@ -694,6 +679,6 @@ The top-level module `KMIR` includes both the control flow constructs (and trans
694679module KMIR
695680 imports KMIR-CONTROL-FLOW
696681 imports KMIR-LEMMAS
697- imports KMIR-SYMBOLIC-LOCALS
682+ // imports KMIR-SYMBOLIC-LOCALS
698683
699684endmodule
0 commit comments