Génération de code assembleur, solutions

L’énoncé est ici.

Linéarisation du code

Parcours en profondeur d’abord

  (* Keep track of the labels that have been visited. *)

  let visited =
    ref Label.Set.empty
  in

  (* Allocate a reference cell that holds the sequence of instructions
     generated so far. Define a function that allows generating a new
     instruction. Instructions are held in the list in reverse order,
     for efficiency. The list is reversed once generation is over. *)

  let instructions =
    ref []
  in

  let generate instruction =
    instructions := instruction :: !instructions
  in

  (* Traverse the control flow graph. A simple depth-first traversal
     is implemented here. *)

  let rec visit l =

    (* Label [l] has been visited before, so an [ILabel l] instruction
       has been issued. We must now generate an [IGoto] instruction
       that transfers control to this place. *)

    if Label.Set.mem l !visited then begin
      generate (LIN.IGoto l)
    end
    else
      visit_fresh l

  and visit_fresh l =

    (* Label [l] has never been visited before. First, record that it
       now has been visited, so as to avoid looping, and generate an
       [ILabel l] instruction. This instruction is useless if [l]
       turns out not to be the target of a branch, but this is taken
       care of later. Then, translate the instruction found at [l] in
       the source program. In most cases, this involves first
       translating the instruction itself, then translating its
       immediate successor, in sequence. *)

    visited := Label.Set.add l !visited;
    generate (LIN.ILabel l);

    match Label.Map.find l graph with

    | LTL.INewFrame l ->
        generate LIN.INewFrame;
        visit l

    | LTL.IDeleteFrame l ->
        generate LIN.IDeleteFrame;
        visit l

    | LTL.IGetStack (r, slot, l) ->
        generate (LIN.IGetStack (r, slot));
        visit l

    | LTL.ISetStack (slot, r, l) ->
        generate (LIN.ISetStack (slot, r));
        visit l

    | LTL.IConst (r, i, l) ->
        generate (LIN.IConst (r, i));
        visit l

    | LTL.IUnOp (op, r1, r2, l) ->
        generate (LIN.IUnOp (op, r1, r2));
        visit l

    | LTL.IBinOp (op, r, r1, r2, l) ->
        generate (LIN.IBinOp (op, r, r1, r2));
        visit l

    | LTL.ICall (callee, l) ->
        generate (LIN.ICall callee);
        visit l

    | LTL.ILoad (r1, r2, o, l) ->
        generate (LIN.ILoad (r1, r2, o));
        visit l

    | LTL.IStore (r1, o, r2, l) ->
        generate (LIN.IStore (r1, o, r2));
        visit l

    | LTL.IGoto l ->
        visit l

      (* Conditional branches. The label that is reached by falling
         through in [LIN] is [l2], which means that it must be
         translated first, so that its instructions are contiguous
         with the [LIN] branch instruction.

         Code for [l1] is generated, if required, after we are done
         dealing with [l2]. Visiting [l1] is not required if it has
         been visited before: visiting it again would only produce an
         unreachable [IGoto] instruction. *)

    | LTL.IUnBranch (cond, r, l1, l2) ->
        generate (LIN.IUnBranch (cond, r, l1));
        visit l2;
        if not (Label.Set.mem l1 !visited) then
          visit_fresh l1

    | LTL.IBinBranch (cond, r1, r2, l1, l2) ->
        generate (LIN.IBinBranch (cond, r1, r2, l1));
        visit l2;
        if not (Label.Set.mem l1 !visited) then
          visit_fresh l1

    | LTL.IReturn ->
        generate LIN.IReturn

Enlever les labels inutiles

let translate entry graph =

  [...]

  (* Keep track of the labels that must be explicitly named within the
     [LIN] code. These are the targets of [LIN] branch instructions
     and, as a special case, the graph's entry point. *)

  let explicit =
    ref (Label.Set.singleton entry)
  in

  let mark label =
    explicit := Label.Set.add label !explicit
  in

  (* Traverse the control flow graph. A simple depth-first traversal
     is implemented here. *)

  let rec visit l =

    (* Label [l] has been visited before, so an [ILabel l] instruction
       has been issued. We must now generate an [IGoto] instruction
       that transfers control to this place. Because [l] is the target
       of a branch instruction, we record the fact that it should be
       explicit. *)

    if Label.Set.mem l !visited then begin
      mark l;
      generate (LIN.IGoto l)
    end
    else
      visit_fresh l

  and visit_fresh l =

    [...]

    | LTL.IUnBranch (cond, r, l1, l2) ->
        mark l1;
        [...]

    | LTL.IBinBranch (cond, r1, r2, l1, l2) ->
        mark l1;
        [...]

    [...]

  in
  visit entry;

  (* Now, get rid of the labels that do not need to be explicit. Also,
     reverse the list to reestablish the correct order. *)

  List.filter (function
    | LIN.ILabel l ->
        Label.Set.mem l !explicit
    | _ ->
        true
  ) (List.rev !instructions)

Génération de code assembleur

Calcul des déplacements

(* In order to translate [IGetStack] and [ISetStack], one must
   understand the actual layout of stack frames. 

   The MIPS stack grows towards low addresses. I will speak of the
   high limit address of the stack frame (that is, the address of the
   previous stack frame) as the ``top of the stack frame'' and of the
   low limit address of the stack frame as the ``bottom of the stack
   frame''.

   The top of the stack frame is the initial value of [$sp] when the
   procedure is entered. The bottom of the stack frame is the new
   value of [$sp] that the procedure installs. The difference between
   the two corresponds to the parameters that are passed on the stack
   and to the procedure's local stack storage area. We refer to this
   value as the size of the frame.

   Thus, the top of the stack frame is at [$sp + locals + formals],
   where [locals] is the size of the local storage area and [formals]
   is the size of the formal parameters area, both expressed in bytes.
   The parameters are between [$sp + locals] and [$sp + locals +
   formals]. Local storage lies between [$sp] and [$sp + locals].

   A [SlotIncoming] stack slot is translated into an offset into the
   frame's parameters area. A [SlotLocal] stack slot is translated
   into an offset into the frame's local storage area. A
   [SlotOutgoing] stack slot is translated into an offset into the
   callee's parameters area, which lies below [$sp]. We translate
   higher offsets to lower addresses: this is made necessary by the
   fact that the size of the outgoing area is not recorded in our
   instructions. *)

(* [locals proc] is the size of the [proc]'s local stack area. *)

let locals proc =
  proc.LIN.locals

(* [formals proc] is the size of the [proc]'s incoming stack area.  It
   consists of only the parameters that are not passed in hardware
   registers. *)

let formals proc =
  MIPS.word * (max 0l (proc.LIN.formals - Misc.length MIPS.parameters))

(* [translate_slot proc slot] translates [slot] into an offset off
   [$sp]. *)

let translate_slot proc = function
  | LIN.SlotLocal offset ->
      locals proc - (offset + MIPS.word)
  | LIN.SlotIncoming offset ->
      locals proc + formals proc - (offset + MIPS.word)
  | LIN.SlotOutgoing offset ->
      - (offset + MIPS.word)

(* [adjust offset] generates an [ASM] instruction that adjusts the
   stack pointer [sp] by [offset]. *)

let adjust offset =
  if offset = 0l then
    ASM.INop
  else
    ASM.IUnOp (MIPSOps.UOpAddi offset, MIPS.sp, MIPS.sp)

Traduction en assembleur

(* [translate_instruction p proc i] translates the instruction [i].
   The program [p] is used when translating procedure calls: it
   provides a mapping of procedure names to labels. The current
   procedure [proc] is used when translating stack accesses. Labels
   are mapped to globally unique strings using [Label.print]. *)

let translate_instruction
    (p : LIN.program)
    (proc : LIN.procedure)
    (instruction : LIN.instruction)
    : ASM.instruction
    =
  match instruction with

  | LIN.INewFrame ->
      adjust (-(locals proc + formals proc))

  | LIN.IDeleteFrame ->
      adjust (locals proc + formals proc)

  | LIN.IGetStack (r, slot) ->
      let offset = translate_slot proc slot in
      ASM.ILoad (r, MIPS.sp, offset)

  | LIN.ISetStack (slot, r) ->
      let offset = translate_slot proc slot in
      ASM.IStore (MIPS.sp, offset, r)

  | LIN.IConst (r, i) ->
      ASM.IConst (r, i)

  | LIN.IUnOp (op, r1, r2) ->
      ASM.IUnOp (op, r1, r2)

  | LIN.IBinOp (op, r, r1, r2) ->
      ASM.IBinOp (op, r, r1, r2)

  | LIN.ICall (CUserFunction f) ->
      ASM.ICall (Label.print (proc2label p f))

  | LIN.ICall (CPrimitiveFunction p) ->
      ASM.ICall (prim2label p)

  | LIN.ILoad (r1, r2, o) ->
      ASM.ILoad (r1, r2, o)

  | LIN.IStore (r1, o, r2) ->
      ASM.IStore (r1, o, r2)

  | LIN.IGoto l ->
      ASM.IGoto (Label.print l)

  | LIN.IUnBranch (cond, r, l) ->
      ASM.IUnBranch (cond, r, Label.print l)

  | LIN.IBinBranch (cond, r1, r2, l) ->
      ASM.IBinBranch (cond, r1, r2, Label.print l)

  | LIN.IReturn ->
      ASM.IReturn

  | LIN.ILabel l ->
      ASM.ILabel (Label.print l)


Ce document a été traduit de LATEX par HEVEA