File: mdl-gen-asm.sml

package info (click to toggle)
mlton 20210117%2Bdfsg-3
  • links: PTS, VCS
  • area: main
  • in suites: sid
  • size: 58,464 kB
  • sloc: ansic: 27,682; sh: 4,455; asm: 3,569; lisp: 2,879; makefile: 2,347; perl: 1,169; python: 191; pascal: 68; javascript: 7
file content (280 lines) | stat: -rw-r--r-- 11,736 bytes parent folder | download | duplicates (6)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
(* 
 * This module generates the assembler of an architecture 
 * given a machine description.
 *
 *)
functor MDLGenAsm(Comp : MDL_COMPILE) : MDL_GEN_MODULE =
struct
   structure Comp = Comp
   structure Env  = Comp.Env
   structure Ast  = Comp.Ast
   structure R    = Comp.Rewriter
   structure T    = Comp.Trans

   open Ast Comp.Util Comp.Error

   fun gen md =
   let (* name of the functor and signature *)
       val strName = Comp.strname md "AsmEmitter"
       val sigName = "INSTRUCTION_EMITTER"

       (* Arguments of the functor *)
       val args = ["structure S : INSTRUCTION_STREAM",
		   "structure Instr : "^Comp.signame md "INSTR",
		   "   where T = S.P.T",
                   "structure Shuffle : "^Comp.signame md "SHUFFLE",
                   "   where I = Instr",
                   "structure MLTreeEval : MLTREE_EVAL",
		   "   where T = Instr.T"
                  ]
       val args = SEQdecl[$args,Comp.fctArgOf md "Assembly"]

       (* Cellkinds declared by the user *)   
       val cellKinds = Comp.cells md

       (* Assembly case *)
       val asmCase = Comp.asmCase md

       (* How to make a string expression *)
       fun mkString s =
           STRINGexp(case asmCase of VERBATIM  => s
                                   | LOWERCASE => String.map Char.toLower s
                                   | UPPERCASE => String.map Char.toUpper s)

       (* The Instruction structure *)
       val env = Env.lookupStr (Comp.env md) (IDENT([], "Instruction"))

       (* All datatype definitions in this structure *)
       val datatypeDefinitions = Env.datatypeDefinitions env

       (*
        * There are three assembly modes:
        *   EMIT: directly emit to stream
        *   ASM:  convert to string
        *   NOTHING: do nothing
        *)
       datatype mode = EMIT | ASM | NOTHING

       (*
        * Find out which assembly mode a datatype should use
        *)
       fun modeOf(DATATYPEbind{cbs, asm, ...}) = 
           let val mode = if asm then ASM else NOTHING
               fun loop([], m) = m
                 | loop(_, EMIT) = EMIT
                 | loop(CONSbind{asm=NONE, ...}::cbs, m) = loop(cbs, m)
                 | loop(CONSbind{asm=SOME(STRINGasm _), ...}::cbs, _)=
                      loop(cbs, ASM)
                 | loop(CONSbind{asm=SOME(ASMasm a), ...}::cbs, m)=
                      loop(cbs, loop2(a, ASM))
               and loop2([], m) = m
                 | loop2(EXPasm _::_, _) = EMIT
                 | loop2(_::a, m) = loop2(a, m)
           in  loop(cbs, mode) end 


       (*
        * Names of emit and assembly functions. 
        * The assembly function converts something into a string.
        * The emit function prints that to the stream for side effect.
        *)
       fun emit id = "emit_"^id
       fun asm  id = "asm_"^id 

       (*
        * How to emit special types 
        *)
       fun emitTy(id,IDty(IDENT(prefix,t)), e) =
            (case (prefix, t) of
               ([], "int")    => APP(emit t, e)
             | ([], "string") => APP("emit", e)
             | (["Constant"],"const") => APP(emit t, e)
             | (["Label"],"label") => APP(emit t, e)
             | (["T"],"labexp") => APP(emit t, e)
             | (["Region"],"region") => APP(emit t, e)
             | _ =>
                if List.exists(fn db as DATATYPEbind{id=id', ...}=> 
                                 t = id' andalso modeOf db <> NOTHING) 
                   datatypeDefinitions then
                   APP(emit t, e)
                else
                   APP(emit id, e)
            )
         | emitTy(_,CELLty "cellset", e) = APP("emit_cellset", e)
         | emitTy(_,CELLty k, e) = APP("emitCell", e)
         | emitTy(id, _, e) = APP(emit id, e)

       (* 
        * Functions to convert assembly annotations to code 
        *)
       fun mkAsms([], fbs) = rev fbs 
         | mkAsms((db as DATATYPEbind{id, cbs, ...})::dbs, fbs) = 
           (case modeOf db of
              NOTHING => mkAsms(dbs, fbs)
            | EMIT    => mkAsms(dbs, FUNbind(emit id,mkAsm(EMIT,cbs))::fbs)
            | ASM     => mkAsms(dbs, mkEmit id::
                                     FUNbind(asm id,mkAsm(ASM,cbs))::fbs)
           )

           (* fun emitXXX x = emit(asmXXX x) *)
       and mkEmit id = 
           FUNbind(emit id,[CLAUSE([IDpat "x"],NONE,
                              APP("emit",APP(asm id,ID "x")))]) 

           (* Translate backquoted expression *)
       and mkAsm(mode, cbs) = 
           let fun emitIt e =
                    if mode = EMIT then APP("emit",e) else e
               fun asmToExp E (TEXTasm s) = emitIt(mkString s) 
                 | asmToExp E (EXPasm(IDexp(IDENT([],x)))) = 
                    (let val (e, ty) = E x
                     in  emitTy(x, ty, e) end
                     handle e => 
                        fail("unknown assembly field <"^x^">")
                    )
                 | asmToExp E (EXPasm e) = 
                   let fun exp _ (ASMexp(STRINGasm s)) = emitIt(mkString s)
                         | exp _ (ASMexp(ASMasm a)) = SEQexp(map (asmToExp E) a)
                         | exp _ e = e
                   in #exp(R.rewrite{exp=exp,
                                     ty=R.noRewrite,
                                     pat=R.noRewrite,
                                     sexp=R.noRewrite,
                                     decl=R.noRewrite
                                    }
                          ) e
                   end
               fun mkClause(cb as CONSbind{id, asm, ...}) = 
               let val exp = 
                     case asm of
                       NONE => emitIt(mkString id)
                     | SOME(STRINGasm s) => emitIt(mkString s)
                     | SOME(ASMasm a) =>
                       let val consEnv = T.consBindings cb
                       in  SEQexp(map (asmToExp consEnv) a) end
               in  T.mapConsToClause {prefix=["I"],pat=fn p=>p, exp=exp} cb
               end
           in  map mkClause cbs end 

       (* 
        * For each datatype defined in the structure Instruction that
        * has pretty printing annotations attached, generate an assembly
        * function and an emit function.
        *)
       val asmFuns = FUNdecl(mkAsms(datatypeDefinitions, []))

       (* Main function for emitting an instruction *)
       val emitInstrFun = 
           let val instructions = Comp.instructions md
           in  FUN("emitInstr'", IDpat "instr", 
                           CASEexp(ID "instr", mkAsm(EMIT, instructions))
                  )
           end

       val body =
       [$["structure I  = Instr",
          "structure C  = I.C",
          "structure T  = I.T",
          "structure S  = S",
          "structure P  = S.P",
          "structure Constant = I.Constant",
          "",
          "open AsmFlags",
          ""
        ],
        Comp.errorHandler md "AsmEmitter",
       $[ "",
          "fun makeStream formatAnnotations =",
          "let val stream = !AsmStream.asmOutStream",
          "    fun emit' s = TextIO.output(stream,s)",
          "    val newline = ref true",
          "    val tabs = ref 0",
          "    fun tabbing 0 = ()",
          "      | tabbing n = (emit' \"\\t\"; tabbing(n-1))",
          "    fun emit s = (tabbing(!tabs); tabs := 0; newline := false; emit' s)",
          "    fun nl() = (tabs := 0; if !newline then () else (newline := true; emit' \"\\n\"))",
          "    fun comma() = emit \",\"",
          "    fun tab() = tabs := 1",
          "    fun indent() = tabs := 2",
          "    fun ms n = let val s = Int.toString n",
          "               in  if n<0 then \"-\"^String.substring(s,1,size s-1)",
          "                   else s",
          "               end",
          "    fun emit_label lab = emit(P.Client.AsmPseudoOps.lexpToString(T.LABEL lab))",
	  "    fun emit_labexp le = emit(P.Client.AsmPseudoOps.lexpToString (T.LABEXP le))",
          "    fun emit_const c = emit(Constant.toString c)",
          "    fun emit_int i = emit(ms i)",
          "    fun paren f = (emit \"(\"; f(); emit \")\")",
          "    fun defineLabel lab = emit(P.Client.AsmPseudoOps.defineLabel lab^\"\\n\")",
          "    fun entryLabel lab = defineLabel lab",
          "    fun comment msg = (tab(); emit(\"/* \" ^ msg ^ \" */\"); nl())",
          "    fun annotation a = comment(Annotations.toString a)",
          "    fun getAnnotations() = error \"getAnnotations\"",
          "    fun doNothing _ = ()",
	  "    fun fail _ = raise Fail \"AsmEmitter\"",
          "    fun emit_region mem = comment(I.Region.toString mem)",
          "    val emit_region = ",
          "       if !show_region then emit_region else doNothing",
          "    fun pseudoOp pOp = (emit(P.toString pOp); emit \"\\n\")",
          "    fun init size = (comment(\"Code Size = \" ^ ms size); nl())",
          "    val emitCellInfo = AsmFormatUtil.reginfo",
          "                             (emit,formatAnnotations)",
          "    fun emitCell r = (emit(CellsBasis.toString r); emitCellInfo r)",
          "    fun emit_cellset(title,cellset) =",
          "      (nl(); comment(title^CellsBasis.CellSet.toString cellset))",
          "    val emit_cellset = ",
          "      if !show_cellset then emit_cellset else doNothing",
          "    fun emit_defs cellset = emit_cellset(\"defs: \",cellset)",
          "    fun emit_uses cellset = emit_cellset(\"uses: \",cellset)",
          "    val emit_cutsTo = ",
          "      if !show_cutsTo then AsmFormatUtil.emit_cutsTo emit",
          "      else doNothing",
          "    fun emitter instr =",
          "    let"
         ],
        asmFuns,
        Comp.declOf md "Assembly",
        emitInstrFun,
        $["   in  tab(); emitInstr' instr; nl()",
          "   end (* emitter *)",
          "   and emitInstrIndented i = (indent(); emitInstr i; nl())",
          "   and emitInstrs instrs =",
          "        app (if !indent_copies then emitInstrIndented",
          "             else emitInstr) instrs",
          "",
          "   and emitInstr(I.ANNOTATION{i,a}) =",
	  "        ( comment(Annotations.toString a);",
	  "           nl();",
          "           emitInstr i )",
          "     | emitInstr(I.LIVE{regs, spilled})  = ",
	  "         comment(\"live= \" ^ CellsBasis.CellSet.toString regs ^",
	  "                 \"spilled= \" ^ CellsBasis.CellSet.toString spilled)",
          "     | emitInstr(I.KILL{regs, spilled})  = ",
	  "         comment(\"killed:: \" ^ CellsBasis.CellSet.toString regs ^",
	  "                 \"spilled:: \" ^ CellsBasis.CellSet.toString spilled)",
          "     | emitInstr(I.INSTR i) = emitter i",  
          "     | emitInstr(I.COPY{k=CellsBasis.GP, sz, src, dst, tmp}) =",
	  "        emitInstrs(Shuffle.shuffle{tmp=tmp, src=src, dst=dst})",
          "     | emitInstr(I.COPY{k=CellsBasis.FP, sz, src, dst, tmp}) =",
	  "        emitInstrs(Shuffle.shufflefp{tmp=tmp, src=src, dst=dst})",
	  "     | emitInstr _ = error \"emitInstr\"", 
          "", 
          "in  S.STREAM{beginCluster=init,",
          "             pseudoOp=pseudoOp,",
          "             emit=emitInstr,",
          "             endCluster=fail,",
          "             defineLabel=defineLabel,",
          "             entryLabel=entryLabel,",
          "             comment=comment,",
          "             exitBlock=doNothing,",
          "             annotation=annotation,",
          "             getAnnotations=getAnnotations",
          "            }",
          "end"
         ]
       ]

   in  Comp.codegen md "emit/Asm"
         [Comp.mkFct' md "AsmEmitter" args sigName body]
   end
end