mips-cc

A little C compiler
git clone git@git.mpah.dev/mips-cc.git
Log | Files | Refs | README

ast.ml (4359B)


      1 type type_t =
      2   | Int_t
      3   | Float_t
      4   | Char_t
      5   | Str_t
      6   | Void_t
      7   | Bool_t
      8   | Func_t of type_t * type_t list
      9 
     10 let rec string_of_type_t t =
     11   match t with
     12   | Int_t -> "int"
     13   | Float_t -> "float"
     14   | Str_t -> "string"
     15   | Char_t -> "char"
     16   | Void_t -> "void"
     17   | Bool_t -> "bool"
     18   | Func_t (r, a) ->
     19      (if (List.length a) > 1 then "(" else "")
     20      ^ (String.concat ", " (List.map string_of_type_t a))
     21      ^ (if (List.length a) > 1 then ")" else "")
     22      ^ " -> " ^ (string_of_type_t r)
     23 
     24 module Syntax = struct
     25   type ident = string
     26   type expr =
     27     | Void   of { pos: Lexing.position }
     28     | Bool   of { value: bool
     29               ; pos: Lexing.position }
     30     | Int    of { value: int
     31               ; pos: Lexing.position }
     32     | Float  of { value: float
     33               ; pos: Lexing.position }
     34     | Char   of { value: string
     35               ; pos: Lexing.position }
     36     | Str   of { value: string
     37               ; pos: Lexing.position }
     38     | Var  of { name: ident
     39               ; pos: Lexing.position }
     40     | Call of { func: ident
     41               ; args: expr list
     42               ; pos: Lexing.position }
     43 
     44   type instr =
     45     | Assign of { var: ident
     46                 ; expr: expr
     47                 ; pos: Lexing.position }
     48     | Return of { expr: expr
     49                 ; pos: Lexing.position }
     50     | Decl of { var: ident
     51               ; type_: type_t
     52               ; pos: Lexing.position }
     53     | Expr of { expr: expr
     54               ; pos: Lexing.position }
     55 
     56     | Cond of { expr: expr
     57               ; b1: block
     58               ; b2: block
     59               ; pos: Lexing.position }
     60 
     61     | Loop of { expr: expr
     62                ; b: block
     63                ; pos: Lexing.position }
     64 
     65   and block = instr list
     66 
     67   type def =
     68       Func of { ftype: type_t
     69               ; name: ident
     70               ; args: (type_t * ident) list
     71               ; body: block
     72               ; pos: Lexing.position }
     73   and prog = def list
     74 end
     75 
     76 module IR = struct
     77   type ident = string
     78   type expr =
     79     | Void
     80     | Int  of int
     81     | Float of float
     82     | Bool of bool
     83     | Char of string
     84     | Str of string
     85     | Var  of ident
     86     | Call of ident * expr list
     87   type instr =
     88     | Assign of ident * expr
     89     | Return of expr
     90     | Decl of ident
     91     | Expr   of expr
     92     | Cond   of expr * block * block
     93     | Loop of expr *  block
     94   and block = instr list
     95 
     96   type def =
     97       Func of ident * ident list * block
     98   and prog = def list
     99 
    100   let string_of_ir ast =
    101     let rec fmt_e = function
    102       | Void          -> "Void"
    103       | Bool  b       -> "Bool " ^ (string_of_bool b)
    104       | Int   n       -> "Int " ^ (string_of_int n)
    105       | Float n       -> "Float " ^ (string_of_float n)
    106       | Char  c       -> "Char " ^ c
    107       | Str   s       -> "Str \"" ^ s ^ "\""
    108       | Var   v       -> "Var \"" ^ v ^ "\""
    109       | Call  (f, a)  -> "Call (\"" ^ f ^ "\", [ "
    110                          ^ (String.concat " ; " (List.map fmt_e a))
    111                          ^ " ])"
    112     and fmt_i = function
    113       | Loop (e, b)    -> "Loop (" ^ (fmt_e e) ^ ", " ^ (fmt_b b) ^ ")" 
    114       | Cond (e, b1, b2) -> "Cond (" ^ (fmt_e e) ^ ", " ^ (fmt_b b1) ^ ", " ^ (fmt_b b2) ^ ")" 
    115       | Decl v        -> "Decl \"" ^ v ^ "\""
    116       | Assign (v, e) -> "Assign (\"" ^ v ^ "\", " ^ (fmt_e e) ^ ")"
    117       | Return e      -> "Return (" ^ (fmt_e e) ^ ")"
    118       | Expr e        -> "Expr (" ^ (fmt_e e) ^ ")"
    119 
    120     and fmt_b b = "\t[ " ^ (String.concat "\n\t; " (List.map fmt_i b)) ^ " ]"
    121     and fmt_arg a = "\"" ^ a ^ "\""
    122     and fmt_d = function
    123         | Func (name, args, b) -> "[ Func (\"" ^ name ^ "\", " ^ "[ " ^
    124                                   (String.concat "; " (List.map fmt_arg args)) ^ " ],\n" ^
    125                                   fmt_b b ^ ")" ^ "]"
    126     and fmt_p p = "[\n " ^ (String.concat "\n " (List.map fmt_d p)) ^ "\n]"
    127     in fmt_p ast
    128 end
    129 
    130 module IR2 = struct
    131   type ident = string
    132   type expr =
    133     | Nil
    134     | Bool of bool
    135     | Int  of int
    136     | Float of float
    137     | Char of char
    138     | Data of string
    139     | Var   of ident
    140     | Call  of ident * expr list
    141 (*
    142   type lvalue =
    143      | LVar  of ident
    144      | LAddr of expr
    145 *)
    146   type instr =
    147     | Decl   of ident
    148     | Return of expr
    149     | Expr   of expr
    150     | Assign of expr * expr
    151     | Cond   of expr * block * block
    152     | Loop   of expr * block
    153   and block = instr list
    154   type def =
    155     | Func of ident * ident list * block
    156   type prog = def list
    157 end