1(* Auto-generate Nios II R2 CDX ldwm/stwm/push.n/pop.n patterns
2   Copyright (C) 2014-2018 Free Software Foundation, Inc.
3   Contributed by Mentor Graphics.
4
5   This file is part of GCC.
6
7   GCC is free software; you can redistribute it and/or modify it under
8   the terms of the GNU General Public License as published by the Free
9   Software Foundation; either version 3, or (at your option) any later
10   version.
11
12   GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13   WARRANTY; without even the implied warranty of MERCHANTABILITY or
14   FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15   for more details.
16
17   You should have received a copy of the GNU General Public License
18   along with GCC; see the file COPYING3.  If not see
19   <http://www.gnu.org/licenses/>.
20
21   This is a Standard ML program.  There are multiple Standard ML
22   implementations widely available.  We recommend the MLton optimizing
23   SML compiler, due to its ease of creating a standalone executable.
24
25     http://www.mlton.org/
26
27   Or from your favourite OS's friendly packaging system. Tested with
28   MLton Release 20130715, though other versions will probably work too.
29
30   Run with:
31     mlton -output a.out /path/to/gcc/config/nios2/nios2-ldstwm.sml
32     ./a.out >/path/to/gcc/config/nios2/ldstwm.md
33*)
34
35datatype ld_st = ld | st;
36datatype push_pop = push | pop;
37datatype inc_dec = inc | dec;
38
39fun for ls f = map f ls;
40fun conds cond str = if cond then str else "";
41fun ints n = if n>=0 then (Int.toString n) else ("-" ^ (Int.toString (~n)));
42
43fun pushpop_pattern pptype n fp =
44    let
45	val sp_reg = "(reg:SI SP_REGNO)";
46	val ra_reg = "(reg:SI RA_REGNO)";
47	val fp_reg = "(reg:SI FP_REGNO)";
48
49	fun sets lhs rhs = "(set " ^ lhs ^
50			   (if pptype=push then " "
51			    else " ") ^ rhs ^ ")";
52	val sp_adj =
53	    "(set " ^ sp_reg ^ "\n          " ^
54	    "(plus:SI " ^ sp_reg ^
55	    " (match_operand 1 \"const_int_operand\" \"\")))";
56
57	fun reg i regi = "(reg:SI " ^ (ints regi) ^ ")";
58	fun mem i opndi =
59	    if pptype=push then
60		"(mem:SI (plus:SI (reg:SI SP_REGNO) (const_int " ^ (ints (~4*i)) ^ ")))"
61	    else
62		"(match_operand:SI " ^
63		(ints opndi) ^ " \"stack_memory_operand\" \"\")";
64
65	val start = 1 + (if fp then 2 else 1);
66	val lim = n + (if fp then 2 else 1);
67	fun set_elt i regi opndi =
68	    if pptype=push then (sets (mem i opndi) (reg i regi))
69	    else (sets (reg i regi) (mem i opndi));
70	fun get_elt_list (i, regi, opndi) =
71	    if i > lim then []
72	    else (set_elt i regi opndi) :: get_elt_list (i+1, regi-1, opndi+1);
73
74	val set_elements = get_elt_list (start, 16+n-1, start+1);
75
76	val ra_set = if pptype=push then sets (mem 1 2) ra_reg
77		     else sets ra_reg (mem 1 2);
78	val fp_set = (conds fp (if pptype=push then sets (mem 2 3) fp_reg
79				else sets fp_reg (mem 2 3)));
80	val ret = (conds (pptype=pop) "(return)");
81	val element_list =
82	    List.filter (fn x => x<>"")
83			([ret, sp_adj, ra_set, fp_set] @ set_elements);
84
85	fun reg_index i = 16 + n - i;
86	fun pop_opnds 0 spl = (conds fp ("fp" ^ spl)) ^ "ra"
87	  | pop_opnds n spl = "r" ^ (ints (reg_index n)) ^ spl ^ (pop_opnds (n-1) spl);
88	fun push_opnds 0 spl = "ra" ^ (conds fp (spl ^ "fp"))
89	  | push_opnds n spl = (push_opnds (n-1) spl) ^ spl ^ "r" ^ (ints (reg_index n));
90
91	val spadj_opnd = if pptype=push then 2 else (start+n);
92	val spadj = ints spadj_opnd;
93	val regsave_num = n + (if fp then 2 else 1);
94
95	val ppname = if pptype=push then "push" else "pop";
96	val name = if pptype=push then "push" ^ "_" ^ (push_opnds n "_")
97		   else "pop" ^ "_" ^ (pop_opnds n "_");
98    in
99	"(define_insn \"*cdx_" ^ name ^ "\"\n" ^
100	"  [(match_parallel 0 \"" ^
101	(conds (pptype=pop) "pop_operation") ^ "\"\n" ^
102	"    [" ^ (String.concatWith ("\n     ") element_list) ^ "])]\n" ^
103	"   \"TARGET_HAS_CDX && XVECLEN (operands[0], 0) == " ^
104	(ints (length element_list)) ^
105	(conds (pptype=push)
106	       ("\n    && (-INTVAL (operands[1]) & 3) == 0\n" ^
107		"    && (-INTVAL (operands[1]) - " ^
108		(ints (4*regsave_num)) ^ ") <= 60")) ^
109	"\"\n" ^
110	(if pptype=pop then
111	     "{\n" ^
112	     "  rtx x = XEXP (operands[" ^ spadj ^ "], 0);\n" ^
113	     "  operands[" ^ spadj ^ "] = REG_P (x) ? const0_rtx : XEXP (x, 1);\n" ^
114	     "  return \"pop.n\\\\t{" ^ (pop_opnds n ", ") ^ "}, %" ^ spadj ^ "\";\n" ^
115	     "}\n"
116	 else
117	     "{\n" ^
118	     "  operands[" ^ spadj ^ "] = " ^
119	     "GEN_INT (-INTVAL (operands[1]) - " ^ (ints (4*regsave_num)) ^ ");\n" ^
120	     "  return \"push.n\\\\t{" ^ (push_opnds n ", ") ^ "}, %" ^ spadj ^ "\";\n" ^
121	     "}\n") ^
122	"  [(set_attr \"type\" \"" ^ ppname ^ "\")])\n\n"
123    end;
124
125fun ldstwm_pattern ldst n id wb pc =
126    let
127	val ldstwm = (if ldst=ld then "ldwm" else "stwm");
128	val name = "*cdx_" ^ ldstwm ^ (Int.toString n) ^
129		   (if id=inc then "_inc" else "_dec") ^
130		   (conds wb "_wb") ^ (conds pc "_ret");
131	val base_reg_referenced_p = ref false;
132	val base_regno = ints (n+1);
133	fun plus_addr base offset =
134	    "(plus:SI " ^ base ^ " (const_int " ^ (ints offset) ^ "))";
135	fun base_reg () =
136	    if !base_reg_referenced_p then
137		"(match_dup " ^ base_regno ^ ")"
138	    else (base_reg_referenced_p := true;
139		  "(match_operand:SI " ^ base_regno ^
140		  " \"register_operand\" \"" ^ (conds wb "+&") ^ "r\")");
141	fun reg i = "(match_operand:SI " ^ (ints i) ^
142		    " \"nios2_hard_register_operand\" \"" ^
143		    (conds (ldst=ld) "") ^ "\")";
144
145	fun addr 1 = if id=inc then base_reg ()
146		     else plus_addr (base_reg ()) (~4)
147	  | addr i = let val offset = if id=inc then (i-1)*4 else (~i*4)
148		     in plus_addr (base_reg ()) offset end;
149
150	fun mem i = "(mem:SI " ^ (addr i) ^ ")";
151	fun lhs i = if ldst=ld then reg i else mem i;
152	fun rhs i = if ldst=st then reg i else mem i;
153	fun sets lhs rhs = "(set " ^ lhs ^ "\n          " ^ rhs ^ ")";
154	fun set_elements i =
155	    if i > n then []
156	    else (sets (lhs i) (rhs i)) :: (set_elements (i+1));
157
158	fun opnds 1 = "%1"
159	  | opnds n = opnds(n-1) ^ ", %" ^ (Int.toString n);
160
161	val asm_template = ldstwm ^ "\\\\t{" ^ (opnds n) ^ "}" ^
162			   (if id=inc
163			    then ", (%" ^ base_regno ^ ")++"
164			    else ", --(%" ^ base_regno ^ ")") ^
165			   (conds wb ", writeback") ^
166			   (conds pc ", ret");
167	val wbtmp =
168	    if wb then
169		(sets (base_reg ())
170		      (plus_addr (base_reg ())
171				 ((if id=inc then n else ~n)*4)))
172	    else "";
173	val pctmp = conds pc "(return)";
174	val set_list = List.filter (fn x => x<>"")
175				   ([pctmp, wbtmp] @ (set_elements 1));
176    in
177	if ldst=st andalso pc then ""
178	else
179	    "(define_insn \"" ^ name ^ "\"\n" ^
180	    "  [(match_parallel 0 \"" ^ ldstwm ^  "_operation\"\n" ^
181	    "    [" ^ (String.concatWith ("\n     ") set_list) ^ "])]\n" ^
182	    "   \"TARGET_HAS_CDX && XVECLEN (operands[0], 0) == " ^
183	    (ints (length set_list)) ^ "\"\n" ^
184	    "   \"" ^ asm_template ^ "\"\n" ^
185	    "  [(set_attr \"type\" \"" ^ ldstwm ^ "\")])\n\n"
186    end;
187
188fun peephole_pattern ldst n scratch_p =
189    let
190	fun sets lhs rhs = "(set " ^ lhs ^ "\n        " ^ rhs ^ ")";
191	fun single_set i indent =
192	    let val reg = "(match_operand:SI " ^ (ints i) ^
193			  " \"register_operand\" \"\")";
194		val mem = "(match_operand:SI " ^ (ints (i+n)) ^
195			  " \"memory_operand\" \"\")";
196	    in
197		if ldst=ld then sets reg mem
198		else sets mem reg
199	    end;
200
201	fun single_sets i =
202	    if i=n then []
203	    else (single_set i "   ") :: (single_sets (i+1));
204
205	val scratch = ints (2*n);
206	val peephole_elements =
207	    let val tmp = single_sets 0 in
208		if scratch_p
209		then (["(match_scratch:SI " ^ scratch ^ " \"r\")"] @
210		      tmp @
211		      ["(match_dup " ^ scratch ^ ")"])
212		else tmp
213	    end;
214    in
215	"(define_peephole2\n" ^
216	"  [" ^ (String.concatWith ("\n   ") peephole_elements) ^ "]\n" ^
217	"  \"TARGET_HAS_CDX\"\n" ^
218	"  [(const_int 0)]\n" ^
219	"{\n" ^
220	"  if (gen_ldstwm_peep (" ^
221	(if ldst=st then "false" else "true") ^ ", " ^ (ints n) ^ ", " ^
222	(if scratch_p then ("operands[" ^ scratch ^ "]") else "NULL_RTX") ^
223	", operands))\n" ^
224	"    DONE;\n" ^
225	"  else\n" ^
226	"    FAIL;\n" ^
227	"})\n\n"
228    end;
229
230
231print
232("/* Nios II R2 CDX ldwm/stwm/push.h/pop.n instruction patterns.\n" ^
233 "   This file was automatically generated using nios2-ldstwm.sml.\n" ^
234 "   Please do not edit manually.\n" ^
235 "\n" ^
236 "   Copyright (C) 2014-2018 Free Software Foundation, Inc.\n" ^
237 "   Contributed by Mentor Graphics.\n" ^
238 "\n" ^
239 "   This file is part of GCC.\n" ^
240 "\n" ^
241 "   GCC is free software; you can redistribute it and/or modify it\n" ^
242 "   under the terms of the GNU General Public License as published\n" ^
243 "   by the Free Software Foundation; either version 3, or (at your\n" ^
244 "   option) any later version.\n" ^
245 "\n" ^
246 "   GCC is distributed in the hope that it will be useful, but WITHOUT\n" ^
247 "   ANY WARRANTY; without even the implied warranty of MERCHANTABILITY\n" ^
248 "   or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public\n" ^
249 "   License for more details.\n" ^
250 "\n" ^
251 "   You should have received a copy of the GNU General Public License and\n" ^
252 "   a copy of the GCC Runtime Library Exception along with this program;\n" ^
253 "   see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see\n" ^
254 "   <http://www.gnu.org/licenses/>.  */\n\n");
255
256fun seq a b = if a=b then [b]
257	      else a :: (seq (if a<b then a+1 else a-1) b);
258
259(* push/pop patterns *)
260for (seq 0 8) (fn n =>
261  for [push, pop] (fn p =>
262    for [true, false] (fn fp =>
263       print (pushpop_pattern p n fp))));
264
265(* ldwm/stwm patterns *)
266for [ld, st] (fn l =>
267  for (seq 1 12) (fn n =>
268    for [inc, dec] (fn id =>
269      for [true, false] (fn wb =>
270        for [true, false] (fn pc =>
271          print (ldstwm_pattern l n id wb pc))))));
272
273(* peephole patterns *)
274for [ld, st] (fn l =>
275  for (seq 12 2) (fn n =>
276    print (peephole_pattern l n true)));
277
278