Expressions et registres, solutions

L’énoncé est ici.

Un cas simple

La traduction est immédiate :

    (* Constants. Generate a [IConst] instruction directly into
       the destination register, and branch to the destination
       label. *)

  | UPP.EConst i ->
      generate (RTL.IConst (destr, i, destl))

Expressions

Variables globales et appels de fonctions

Pas de difficulté spéciale, surtout si on s’inspire des instructions correspondantes UPP.ISetVar et UPP.IProcCall.

    (* Global variable access. *)

  | UPP.EGetGlobal offset ->
      generate (RTL.IGetGlobal (destr, offset, destl))

    (* Function calls. *)

  | UPP.EFunCall (callee, actuals) ->
      translate_call (Some destr) callee actuals destl

Variables locales

On utilise l’addition immédiate de zéro pour simuler une affectation entre registres.

Cela donne dans translate_expression :

    (* Local variable access. Copy the contents of the register that
       holds the variable into the destination register. On the MIPS,
       data movement is implemented using [addi 0]. *)

  | UPP.EGetVar x ->
      let sourcer = lookup x in
      generate (RTL.IUnOp (UOpAddi 0l, destr, sourcer, destl))

Et dans translate_instruction :

    (* Local variable update. We evaluate [e] directly into the
       register that holds the variable. *)

  | UPP.ISetVar (x, e) ->
      let destr = Env.lookup x in
      translate_expression destr e destl

Opérations unaires/binaires

En faisant attention à l’ordre des instructions générées, cela donne :

    (* Unary operator applications. First, evaluate the expression
       into a temporary register; then, generate a unary operator
       instruction into the destination register. *)

  | UPP.EUnOp (op, e) ->
      let temporary = allocate() in
      translate_expression temporary e (
      generate (RTL.IUnOp (op, destr, temporary, destl))
      )

    (* Binary operator applications. Analogous to the unary case.
       One must be careful to evaluate [e1] first and [e2] next. *)

  | UPP.EBinOp (op, e1, e2) ->
      let temporary1 = allocate()
      and temporary2 = allocate() in
      translate_expression temporary1 e1 (
      translate_expression temporary2 e2 (
      generate (RTL.IBinOp (op, destr, temporary1, temporary2, destl))
      ))

    (* Memory reads. This is much like a unary operator. *)

  | UPP.ELoad (e, offset) ->
      let temporary = allocate() in
      translate_expression temporary e (
      generate (RTL.ILoad (destr, temporary, offset, destl))
      )

Conditions

Une première traduction

La difficulté principale est le traitement des opérations paresseuses.

Cela donne pour translate_condition :

(* Translating conditions. *)

(* [translate_condition c truel falsel] generates new [RTL]
   instructions whose effect is to evaluate the condition [c] and to
   transfer control to one of the labels [truel] and [falsel],
   depending on the condition's value. It returns the entry label of
   the newly generated instructions. *)

let rec translate_condition
   (c : UPP.condition)
   (truel : Label.t)
   (falsel : Label.t)
    : Label.t =

  match c with

    (* Here is the general case for Boolean expressions. The
       expression [e] can evaluate only to [true] or [false], which we
       have represented as [1] and [0], respectively. We evaluate [e]
       into a register and test its value using a unary conditional
       branch. *)

  | UPP.CExpression e ->
      mkunbranch e UConGtz truel falsel

    (* Boolean negation. This is implemented, without generating any
       code, simply by exchanging the two destination labels. *)

  | UPP.CNot c ->
      translate_condition c falsel truel

    (* Boolean conjunction. The semantics of the conjunction operator
       is non-strict, that is, the second condition is not evaluated
       at all if the first condition evaluates to [false]. *)

  | UPP.CAnd (c1, c2) ->
      translate_condition c1
        (translate_condition c2 truel falsel)
        falsel

    (* Boolean disjunction. The semantics of the disjunction operator
       is non-strict, that is, the second condition is not evaluated
       at all if the first condition evaluates to [true]. *)

  | UPP.COr (c1, c2) ->
      translate_condition c1
        truel
        (translate_condition c2 truel falsel)

Et dans translate_instruction :

    (* Conditional. Observe how the destination label [destl] is
       duplicated, so that both branches of the [if] construct meet
       again after their execution is over. *)

  | UPP.IIf (c, i1, i2) ->
      translate_condition c
        (translate_instruction i1 destl)
        (translate_instruction i2 destl)

Optimisations

Voici le code de translate_condition avec toutes les optimisations demandées :

(* Translating conditions. *)

(* [translate_condition c truel falsel] generates new [RTL]
   instructions whose effect is to evaluate the condition [c] and to
   transfer control to one of the labels [truel] and [falsel],
   depending on the condition's value. It returns the entry label of
   the newly generated instructions. *)

let rec translate_condition
   (c : UPP.condition)
   (truel : Label.t)
   (falsel : Label.t)
    : Label.t =

  match c with

    (* The general compilation scheme for Boolean expressions, which
       follows, evaluates the expression into a temporary register,
       then performs a conditional branch, depending on whether the
       register is [0] or [1]. Yet, some special cases of Boolean
       expressions can be translated more efficiently. That is, if the
       expression is an application of a comparison operator, and if
       it can be mapped into a branch condition (consult the types
       [RTL.uncon] and [RTL.bincon]), then we do not need a temporary
       register: we can issue a conditional branch instruction that
       directly tests the desired condition. *)

    (* First, here are the cases where we can generate a unary
       conditional branch instruction. *)

  | UPP.CExpression (UPP.EBinOp (OpGe, e, UPP.EConst 0l))
  | UPP.CExpression (UPP.EBinOp (OpLe, UPP.EConst 0l, e)) ->
      mkunbranch e UConGez truel falsel

  | UPP.CExpression (UPP.EBinOp (OpGt, e, UPP.EConst 0l))
  | UPP.CExpression (UPP.EBinOp (OpLt, UPP.EConst 0l, e)) ->
      mkunbranch e UConGtz truel falsel

  | UPP.CExpression (UPP.EBinOp (OpLe, e, UPP.EConst 0l))
  | UPP.CExpression (UPP.EBinOp (OpGe, UPP.EConst 0l, e)) ->
      mkunbranch e UConLez truel falsel

  | UPP.CExpression (UPP.EBinOp (OpLt, e, UPP.EConst 0l))
  | UPP.CExpression (UPP.EBinOp (OpGt, UPP.EConst 0l, e)) ->
      mkunbranch e UConLtz truel falsel

    (* Next, here are the cases where we can generate a binary
       conditional branch instruction. *)

  | UPP.CExpression (UPP.EBinOp (OpEq, e1, e2)) ->
      mkbinbranch e1 e2 ConEq truel falsel

  | UPP.CExpression (UPP.EBinOp (OpNe, e1, e2)) ->
      mkbinbranch e1 e2 ConNe truel falsel

    (* Last, here is the general case for Boolean expressions. The
       expression [e] can evaluate only to [true] or [false], which we
       have represented as [1] and [0], respectively. We evaluate [e]
       into a register and test its value using a unary conditional
       branch. *)

  | UPP.CExpression e ->
      mkunbranch e UConGtz truel falsel

    (* Boolean negation. This is implemented, without generating any
       code, simply by exchanging the two destination labels. *)

  | UPP.CNot c ->
      translate_condition c falsel truel

    (* Boolean conjunction. The semantics of the conjunction operator
       is non-strict, that is, the second condition is not evaluated
       at all if the first condition evaluates to [false]. *)

  | UPP.CAnd (c1, c2) ->
      translate_condition c1
        (translate_condition c2 truel falsel)
        falsel

    (* Boolean disjunction. The semantics of the disjunction operator
       is non-strict, that is, the second condition is not evaluated
       at all if the first condition evaluates to [true]. *)

  | UPP.COr (c1, c2) ->
      translate_condition c1
        truel
        (translate_condition c2 truel falsel)

Boucles

Traduction de la boucle

Après une longue explication du problème, la solution paraît facile !

    (* Loop. We first transfer control to a fresh label, called
       [entry], which represents the loop's entry point. At that
       point, we test the condition [c]. If it holds, we execute the
       instruction [i] and transfer control back to
       [entry]. Otherwise, we exit the loop by transferring control to
       our destination label [destl]. *)

    (* We do not attempt to optimize [while true]. This idiom is not
       very useful in a language that does not have any kind of
       non-local control transfer, so it is unlikely to be used by
       Pseudo-Pascal programmers. *)

  | UPP.IWhile (c, i) ->
      loop (fun entry ->
        translate_condition c
          (translate_instruction i entry)
          destl
      )

Fonction loop

La fonction loop n’est cependant pas évidente. Elle fait référence au graphe de flot de contrôle graph, caché par l’utilisation de la fonction generate. Allez voir atomSig.mli pour plus de détails. C’est la signature commune des registres et des labels, cf les fichiers register.mli et label.mli.

  (* Define a function that adds an [IGoto] instruction at a fresh
     label [label] to the control flow graph. The construction is
     recursive, in the sense that the target label of the branch
     instruction is provided by a computation that is allowed to use
     [label] itself. This allows creating cycles in the control flow
     graph.

     The definition of this function is made somewhat subtle by the
     fact that the [target] function is allowed to alter the graph.
     Thus, the definition of [t] cannot be inlined into the next
     line. *)

  let loop target =
    let label = Label.fresh luniverse in
    let t = target label in
    graph := Label.Map.add label (RTL.IGoto t) !graph;
    label


Ce document a été traduit de LATEX par HEVEA