Be bug compatible with gcc by returning MMX values in RAX.
[oota-llvm.git] / lib / Target / PIC16 / PIC16InstrInfo.td
1 //===- PIC16InstrInfo.td - PIC16 Instruction defs -------------*- tblgen-*-===//
2 //
3 //                     The LLVM Compiler Infrastructure
4 //
5 // This file is distributed under the University of Illinois Open Source 
6 // License. See LICENSE.TXT for details.
7 //
8 //===----------------------------------------------------------------------===//
9 //
10 // This file describes the PIC16 instructions in TableGen format.
11 //
12 //===----------------------------------------------------------------------===//
13
14 //===----------------------------------------------------------------------===//
15 // PIC16 Specific Type Constraints.
16 //===----------------------------------------------------------------------===//
17 class SDTCisI8<int OpNum> : SDTCisVT<OpNum, i8>;
18 class SDTCisI16<int OpNum> : SDTCisVT<OpNum, i16>;
19
20 //===----------------------------------------------------------------------===//
21 // PIC16 Specific Type Profiles.
22 //===----------------------------------------------------------------------===//
23
24 // Generic type profiles for i8/i16 unary/binary operations.
25 // Taking one i8 or i16 and producing void.
26 def SDTI8VoidOp : SDTypeProfile<0, 1, [SDTCisI8<0>]>;
27 def SDTI16VoidOp : SDTypeProfile<0, 1, [SDTCisI16<0>]>;
28
29 // Taking one value and producing an output of same type.
30 def SDTI8UnaryOp : SDTypeProfile<1, 1, [SDTCisI8<0>, SDTCisI8<1>]>;
31 def SDTI16UnaryOp : SDTypeProfile<1, 1, [SDTCisI16<0>, SDTCisI16<1>]>;
32
33 // Taking two values and producing an output of same type.
34 def SDTI8BinOp : SDTypeProfile<1, 2, [SDTCisI8<0>, SDTCisI8<1>, SDTCisI8<2>]>;
35 def SDTI16BinOp : SDTypeProfile<1, 2, [SDTCisI16<0>, SDTCisI16<1>, 
36                                        SDTCisI16<2>]>;
37
38 // Node specific type profiles.
39 def SDT_PIC16Load : SDTypeProfile<1, 3, [SDTCisI8<0>, SDTCisI8<1>, 
40                                           SDTCisI8<2>, SDTCisI8<3>]>;
41
42 def SDT_PIC16Store : SDTypeProfile<0, 4, [SDTCisI8<0>, SDTCisI8<1>, 
43                                           SDTCisI8<2>, SDTCisI8<3>]>;
44
45 // PIC16ISD::CALL type prorile
46 def SDT_PIC16call : SDTypeProfile<0, -1, [SDTCisInt<0>]>;
47
48 // PIC16ISD::BRCOND
49 def SDT_PIC16Brcond: SDTypeProfile<0, 2, 
50                                    [SDTCisVT<0, OtherVT>, SDTCisI8<1>]>;
51
52 // PIC16ISD::BRCOND
53 def SDT_PIC16Selecticc: SDTypeProfile<1, 3, 
54                                    [SDTCisI8<0>, SDTCisI8<1>, SDTCisI8<2>,
55                                     SDTCisI8<3>]>;
56
57 //===----------------------------------------------------------------------===//
58 // PIC16 addressing modes matching via DAG.
59 //===----------------------------------------------------------------------===//
60 def diraddr : ComplexPattern<i8, 1, "SelectDirectAddr", [], []>;
61
62 //===----------------------------------------------------------------------===//
63 // PIC16 Specific Node Definitions.
64 //===----------------------------------------------------------------------===//
65 def PIC16callseq_start : SDNode<"ISD::CALLSEQ_START", SDTI8VoidOp,
66                                 [SDNPHasChain, SDNPOutFlag]>;
67 def PIC16callseq_end   : SDNode<"ISD::CALLSEQ_END", SDTI8VoidOp, 
68                                 [SDNPHasChain, SDNPOptInFlag, SDNPOutFlag]>;
69
70 // Low 8-bits of GlobalAddress.
71 def PIC16Lo : SDNode<"PIC16ISD::Lo", SDTI8UnaryOp>;  
72
73 // High 8-bits of GlobalAddress.
74 def PIC16Hi : SDNode<"PIC16ISD::Hi", SDTI8UnaryOp>;
75
76 // The MTHI and MTLO nodes are used only to match them in the incoming 
77 // DAG for replacement by corresponding set_fsrhi, set_fsrlo insntructions.
78 // These nodes are not used for defining any instructions.
79 def MTLO : SDNode<"PIC16ISD::MTLO", SDTI8UnaryOp>;
80 def MTHI : SDNode<"PIC16ISD::MTHI", SDTI8UnaryOp>;
81
82 // Node to generate Bank Select for a GlobalAddress.
83 def Banksel : SDNode<"PIC16ISD::Banksel", SDTI8UnaryOp>;
84
85 // Node to match a direct store operation.
86 def PIC16Store : SDNode<"PIC16ISD::PIC16Store", SDT_PIC16Store, [SDNPHasChain]>;
87 def PIC16StWF : SDNode<"PIC16ISD::PIC16StWF", SDT_PIC16Store, 
88                        [SDNPHasChain, SDNPInFlag, SDNPOutFlag]>;
89
90 // Node to match a direct load operation.
91 def PIC16Load : SDNode<"PIC16ISD::PIC16Load", SDT_PIC16Load, [SDNPHasChain]>;
92 def PIC16LdWF : SDNode<"PIC16ISD::PIC16LdWF", SDT_PIC16Load, 
93                        [SDNPHasChain, SDNPInFlag, SDNPOutFlag]>;
94
95 // Node to match PIC16 call
96 def PIC16call : SDNode<"PIC16ISD::CALL", SDT_PIC16call,
97                               [SDNPHasChain , SDNPOptInFlag, SDNPOutFlag]>;
98
99 // Node to match a comparison instruction.
100 def PIC16Subcc : SDNode<"PIC16ISD::SUBCC", SDTI8BinOp, [SDNPOutFlag]>;
101
102 // Node to match a conditional branch.
103 def PIC16Brcond : SDNode<"PIC16ISD::BRCOND", SDT_PIC16Brcond, 
104                          [SDNPHasChain, SDNPInFlag]>;
105
106 def PIC16Selecticc : SDNode<"PIC16ISD::SELECT_ICC", SDT_PIC16Selecticc, 
107                          [SDNPInFlag]>;
108
109 //===----------------------------------------------------------------------===//
110 // PIC16 Operand Definitions.
111 //===----------------------------------------------------------------------===//
112 def i8mem : Operand<i8>;
113 def brtarget: Operand<OtherVT>;
114
115 // Operand for printing out a condition code.
116 let PrintMethod = "printCCOperand" in
117   def CCOp : Operand<i8>;
118
119 include "PIC16InstrFormats.td"
120
121 //===----------------------------------------------------------------------===//
122 // PIC16 Common Classes.
123 //===----------------------------------------------------------------------===//
124
125 // W = W Op F : Load the value from F and do Op to W.
126 class BinOpFW<bits<6> OpCode, string OpcStr, SDNode OpNode>:
127   ByteFormat<OpCode, (outs GPR:$dst),
128              (ins GPR:$src, i8imm:$offset, i8mem:$ptrlo, i8imm:$ptrhi),
129               !strconcat(OpcStr, " $ptrlo + $offset, W"),
130              [(set GPR:$dst, (OpNode GPR:$src, (PIC16Load diraddr:$ptrlo,
131                                              (i8 imm:$ptrhi),
132                                              (i8 imm:$offset))))]>;
133
134 // F = F Op W : Load the value from F, do op with W and store in F.
135 class BinOpWF<bits<6> OpCode, string OpcStr, SDNode OpNode>:
136   ByteFormat<OpCode, (outs),
137              (ins GPR:$src, i8imm:$offset, i8mem:$ptrlo, i8imm:$ptrhi),
138               !strconcat(OpcStr, " $ptrlo + $offset"),
139              [(PIC16Store (OpNode GPR:$src, (PIC16Load diraddr:$ptrlo,
140                                              (i8 imm:$ptrhi),
141                                              (i8 imm:$offset))),
142                                              diraddr:$ptrlo,
143                                              (i8 imm:$ptrhi), (i8 imm:$offset)
144                                              )]>;
145
146 // W = W Op L : Do Op of L with W and place result in W.
147 class BinOpLW<bits<6> opcode, string OpcStr, SDNode OpNode> :
148   LiteralFormat<opcode, (outs GPR:$dst),
149                 (ins GPR:$src, i8imm:$literal),
150                 !strconcat(OpcStr, " $literal"),
151                 [(set GPR:$dst, (OpNode GPR:$src, (i8 imm:$literal)))]>;
152
153 //===----------------------------------------------------------------------===//
154 // PIC16 Instructions.
155 //===----------------------------------------------------------------------===//
156
157 // Pseudo-instructions.
158 def ADJCALLSTACKDOWN : Pseudo<(outs), (ins i8imm:$amt),
159                        "!ADJCALLSTACKDOWN $amt",
160                        [(PIC16callseq_start imm:$amt)]>;
161
162 def ADJCALLSTACKUP : Pseudo<(outs), (ins i8imm:$amt),
163                        "!ADJCALLSTACKUP $amt", 
164                        [(PIC16callseq_end imm:$amt)]>;
165
166 //-----------------------------------
167 // Vaious movlw insn patterns.
168 //-----------------------------------
169 let isReMaterializable = 1 in {
170 // Move 8-bit literal to W.
171 def movlw : BitFormat<12, (outs GPR:$dst), (ins i8imm:$src),
172                       "movlw $src",
173                       [(set GPR:$dst, (i8 imm:$src))]>;
174
175 // Move a Lo(TGA) to W.
176 def movlw_lo : BitFormat<12, (outs GPR:$dst), (ins i8imm:$src),
177                       "movlw LOW(${src})",
178                       [(set GPR:$dst, (PIC16Lo tglobaladdr:$src))]>;
179
180 // Move a Hi(TGA) to W.
181 def movlw_hi : BitFormat<12, (outs GPR:$dst), (ins i8imm:$src),
182                       "movlw HIGH(${src})",
183                       [(set GPR:$dst, (PIC16Hi tglobaladdr:$src))]>;
184 }
185
186 //-------------------
187 // FSR setting insns. 
188 //-------------------
189 // These insns are matched via a DAG replacement pattern.
190 def set_fsrlo:
191   ByteFormat<0, (outs FSR16:$fsr), 
192              (ins GPR:$val),
193              "movwf ${fsr}L",
194              []>;
195
196 let isTwoAddress = 1 in
197 def set_fsrhi:
198   ByteFormat<0, (outs FSR16:$dst), 
199              (ins FSR16:$src, GPR:$val),
200              "movwf ${dst}H",
201              []>;
202
203 def copy_fsr:
204   Pseudo<(outs FSR16:$dst), (ins FSR16:$src), "copy_fsr $dst, $src", []>;
205
206 def copy_w:
207   Pseudo<(outs GPR:$dst), (ins GPR:$src), "copy_w $dst, $src", []>;
208
209 //--------------------------
210 // Store to memory
211 //-------------------------
212 // Direct store.
213 def movwf : 
214   ByteFormat<0, (outs), 
215              (ins GPR:$val, i8imm:$offset, i8mem:$ptrlo, i8imm:$ptrhi),
216              "movwf ${ptrlo} + ${offset}",
217              [(PIC16Store GPR:$val, tglobaladdr:$ptrlo, (i8 imm:$ptrhi), 
218                (i8 imm:$offset))]>;
219
220 def movwf_1 : 
221   ByteFormat<0, (outs), 
222              (ins GPR:$val, i8mem:$ptrlo, i8imm:$ptrhi, i8imm:$offset),
223              "movwf ${ptrlo} + ${offset}",
224              [(PIC16Store GPR:$val, texternalsym:$ptrlo, (i8 imm:$ptrhi), 
225                (i8 imm:$offset))]>;
226
227 // Store with InFlag and OutFlag
228 def movwf_2 : 
229   ByteFormat<0, (outs), 
230              (ins GPR:$val, i8mem:$ptrlo, i8imm:$ptrhi, i8imm:$offset),
231              "movwf ${ptrlo} + ${offset}",
232              [(PIC16StWF GPR:$val, texternalsym:$ptrlo, (i8 imm:$ptrhi), 
233                (i8 imm:$offset))]>;
234
235 // Indirect store. Matched via a DAG replacement pattern.
236 def store_indirect : 
237   ByteFormat<0, (outs), 
238              (ins GPR:$val, FSR16:$fsr, i8imm:$offset),
239              "movwi $offset[$fsr]",
240              []>;
241
242 //----------------------------
243 // Load from memory
244 //----------------------------
245 // Direct load.
246 def movf : 
247   ByteFormat<0, (outs GPR:$dst), 
248              (ins i8imm:$offset, i8mem:$ptrlo, i8imm:$ptrhi),
249              "movf ${ptrlo} + ${offset}, W",
250              [(set GPR:$dst, 
251                (PIC16Load tglobaladdr:$ptrlo, (i8 imm:$ptrhi),
252                (i8 imm:$offset)))]>;
253
254 def movf_1 : 
255   ByteFormat<0, (outs GPR:$dst), 
256              (ins i8mem:$ptrlo, i8imm:$ptrhi, i8imm:$offset),
257              "movf ${ptrlo} + ${offset}, W",
258              [(set GPR:$dst, 
259                (PIC16Load texternalsym:$ptrlo, (i8 imm:$ptrhi),
260                (i8 imm:$offset)))]>;
261
262 // Load with InFlag and OutFlag
263 def movf_2 : 
264   ByteFormat<0, (outs GPR:$dst), 
265              (ins i8mem:$ptrlo, i8imm:$ptrhi, i8imm:$offset),
266              "movf ${ptrlo} + ${offset}, W",
267              [(set GPR:$dst, 
268                (PIC16LdWF texternalsym:$ptrlo, (i8 imm:$ptrhi),
269                (i8 imm:$offset)))]>;
270
271
272 // Indirect load. Matched via a DAG replacement pattern.
273 def load_indirect : 
274   ByteFormat<0, (outs GPR:$dst), 
275              (ins FSR16:$fsr, i8imm:$offset),
276              "moviw $offset[$fsr]",
277              []>;
278
279 //-------------------------
280 // Bitwise operations patterns
281 //--------------------------
282 let isTwoAddress = 1 in {
283 def OrFW :  BinOpFW<0, "iorwf", or>;
284 def XOrFW : BinOpFW<0, "xorwf", xor>;
285 def AndFW : BinOpFW<0, "andwf", and>;
286 }
287
288 def OrWF :  BinOpWF<0, "iorwf", or>;
289 def XOrWF : BinOpWF<0, "xorwf", xor>;
290 def AndWF : BinOpWF<0, "andwf", and>;
291
292 //-------------------------
293 // Various add/sub patterns.
294 //-------------------------
295
296 let isTwoAddress = 1 in {
297 def addfw_1: BinOpFW<0, "addwf", add>;
298 def addfw_2: BinOpFW<0, "addwf", addc>;
299 def addfwc: BinOpFW<0, "addwfc", adde>;  // With Carry.
300 }
301
302 def addwf_1: BinOpWF<0, "addwf", add>;
303 def addwf_2: BinOpWF<0, "addwf", addc>;
304 def addwfc: BinOpWF<0, "addwfc", adde>;  // With Carry.
305
306 // W -= [F] ; load from F and sub the value from W.
307 class SUBFW<bits<6> OpCode, string OpcStr, SDNode OpNode>:
308   ByteFormat<OpCode, (outs GPR:$dst),
309              (ins GPR:$src, i8imm:$offset, i8mem:$ptrlo, i8imm:$ptrhi),
310               !strconcat(OpcStr, " $ptrlo + $offset, W"),
311              [(set GPR:$dst, (OpNode (PIC16Load diraddr:$ptrlo,
312                                       (i8 imm:$ptrhi), (i8 imm:$offset)),
313                                       GPR:$src))]>;
314 let isTwoAddress = 1 in {
315 def subfw_1: SUBFW<0, "subwf", sub>;
316 def subfw_2: SUBFW<0, "subwf", subc>;
317 def subfwb: SUBFW<0, "subwfb", sube>;  // With Borrow.
318 def subfw_cc: SUBFW<0, "subwf", PIC16Subcc>;
319 }
320
321 // [F] -= W ; 
322 class SUBWF<bits<6> OpCode, string OpcStr, SDNode OpNode>:
323   ByteFormat<OpCode, (outs),
324              (ins GPR:$src, i8imm:$offset, i8mem:$ptrlo, i8imm:$ptrhi),
325               !strconcat(OpcStr, " $ptrlo + $offset"),
326              [(PIC16Store (OpNode (PIC16Load diraddr:$ptrlo,
327                                       (i8 imm:$ptrhi), (i8 imm:$offset)),
328                                       GPR:$src), diraddr:$ptrlo,
329                                       (i8 imm:$ptrhi), (i8 imm:$offset))]>;
330
331 def subwf_1: SUBWF<0, "subwf", sub>;
332 def subwf_2: SUBWF<0, "subwf", subc>;
333 def subwfb: SUBWF<0, "subwfb", sube>;  // With Borrow.
334 def subwf_cc: SUBWF<0, "subwf", PIC16Subcc>;
335
336 // addlw 
337 let isTwoAddress = 1 in {
338 def addlw_1 : BinOpLW<0, "addlw", add>;
339 def addlw_2 : BinOpLW<0, "addlw", addc>;
340 def addlwc : BinOpLW<0, "addlwc", adde>; // With Carry. (Assembler macro).
341 }
342
343 // bitwise operations involving a literal and w.
344 let isTwoAddress = 1 in {
345 def andlw : BinOpLW<0, "andlw", and>;
346 def xorlw : BinOpLW<0, "xorlw", xor>;
347 def orlw  : BinOpLW<0, "iorlw", or>;
348 }
349
350 // sublw 
351 // W = C - W ; sub W from literal. (Without borrow).
352 class SUBLW<bits<6> opcode, SDNode OpNode> :
353   LiteralFormat<opcode, (outs GPR:$dst),
354                 (ins GPR:$src, i8imm:$literal),
355                 "sublw $literal",
356                 [(set GPR:$dst, (OpNode (i8 imm:$literal), GPR:$src))]>;
357
358 let isTwoAddress = 1 in {
359 def sublw_1 : SUBLW<0, sub>;
360 def sublw_2 : SUBLW<0, subc>;
361 def sublw_cc : SUBLW<0, PIC16Subcc>;
362 }
363
364 // Call instruction.
365 let isCall = 1 in {
366     def CALL: LiteralFormat<0x1, (outs), (ins i8imm:$func),
367             "call ${func}",
368             [(PIC16call diraddr:$func)]>;
369 }
370
371 def pic16brcond: ControlFormat<0x0, (outs), (ins brtarget:$dst, CCOp:$cc),
372                           "b$cc $dst",
373                           [(PIC16Brcond bb:$dst, imm:$cc)]>;
374
375 // Unconditional branch.
376 def br_uncond: ControlFormat<0x0, (outs), (ins brtarget:$dst),
377                           "goto $dst",
378                           [(br bb:$dst)]>;
379
380 // SELECT_CC_* - Used to implement the SELECT_CC DAG operation.  Expanded by the
381 // scheduler into a branch sequence.
382 let usesCustomDAGSchedInserter = 1 in {   // Expanded by the scheduler.
383   def SELECT_CC_Int_ICC
384    : Pseudo<(outs GPR:$dst), (ins GPR:$T, GPR:$F, i8imm:$Cond),
385             "; SELECT_CC_Int_ICC PSEUDO!",
386             [(set GPR:$dst, (PIC16Selecticc GPR:$T, GPR:$F,
387                                              imm:$Cond))]>;
388 }
389
390
391 // Banksel.
392 let isReMaterializable = 1 in {
393 def banksel : 
394   Pseudo<(outs BSR:$dst),
395          (ins i8mem:$ptr),
396          "banksel $ptr",
397          [(set BSR:$dst, (Banksel tglobaladdr:$ptr))]>;
398 }
399
400 // Return insn.
401 def Return : 
402   ControlFormat<0, (outs), (ins), "return", [(ret)]>;
403                       
404 //===----------------------------------------------------------------------===//
405 // PIC16 Replacment Patterns.
406 //===----------------------------------------------------------------------===//
407
408 // Identify an indirect store and select insns for it.
409 def : Pat<(PIC16Store GPR:$val, (MTLO GPR:$loaddr), (MTHI GPR:$hiaddr), 
410            imm:$offset),
411           (store_indirect GPR:$val, 
412            (set_fsrhi (set_fsrlo GPR:$loaddr), GPR:$hiaddr),
413            imm:$offset)>;
414
415 // Identify an indirect load and select insns for it.
416 def : Pat<(PIC16Load (MTLO GPR:$loaddr), (MTHI GPR:$hiaddr), 
417            imm:$offset),
418           (load_indirect  (set_fsrhi (set_fsrlo GPR:$loaddr), GPR:$hiaddr),
419            imm:$offset)>;
420