cleanup: Remove pointless assert(is_${NODE}(x)) just before get_${NODE}_${FOO}(x...
[libfirm] / ir / opt / proc_cloning.c
1 /*
2  * Copyright (C) 1995-2011 University of Karlsruhe.  All right reserved.
3  *
4  * This file is part of libFirm.
5  *
6  * This file may be distributed and/or modified under the terms of the
7  * GNU General Public License version 2 as published by the Free Software
8  * Foundation and appearing in the file LICENSE.GPL included in the
9  * packaging of this file.
10  *
11  * Licensees holding valid libFirm Professional Edition licenses may use
12  * this file in accordance with the libFirm Commercial License.
13  * Agreement provided with the Software.
14  *
15  * This file is provided AS IS with NO WARRANTY OF ANY KIND, INCLUDING THE
16  * WARRANTY OF DESIGN, MERCHANTABILITY AND FITNESS FOR A PARTICULAR
17  * PURPOSE.
18  */
19
20 /**
21  * @file
22  * @brief   Procedure cloning.
23  * @author  Beyhan Veliev, Michael Beck
24  * @brief
25  *
26  * The purpose is first to find and analyze functions, that are called
27  * with constant parameter(s).
28  * The second step is to optimize the function that are found from our
29  * analyze. Optimize mean to make a new function with parameters, that
30  * aren't be constant. The constant parameters of the function are placed
31  * in the function graph. They aren't be passed as parameters.
32  */
33 #include "config.h"
34
35 #include <string.h>
36
37 #include "iroptimize.h"
38 #include "tv.h"
39 #include "set.h"
40 #include "irprog_t.h"
41 #include "hashptr.h"
42 #include "irgwalk.h"
43 #include "analyze_irg_args.h"
44 #include "irprintf.h"
45 #include "ircons.h"
46 #include "irouts.h"
47 #include "irnode_t.h"
48 #include "irtools.h"
49 #include "irgmod.h"
50 #include "array_t.h"
51 #include "irpass_t.h"
52
53 /**
54  * This struct contains the information quadruple for a Call, which we need to
55  * decide if this function must be cloned.
56  */
57 typedef struct quadruple {
58         ir_entity *ent;     /**< The entity of our Call. */
59         size_t    pos;      /**< Position of a constant argument of our Call. */
60         ir_tarval *tv;      /**< The tarval of this argument if Const node. */
61         ir_node   **calls;  /**< The list of all calls with the same characteristics */
62 } quadruple_t;
63
64 /**
65  * The quadruplets are hold in a sorted list
66  */
67 typedef struct entry {
68         quadruple_t  q;      /**< the quadruple */
69         float        weight; /**< its weight */
70         struct entry *next;  /**< link to the next one */
71 } entry_t;
72
73 typedef struct q_set {
74         struct obstack obst;        /**< an obstack containing all entries */
75         pset           *map;        /**< a hash map containing the quadruples */
76         entry_t        *heavy_uses; /**< the ordered list of heavy uses */
77 } q_set;
78
79 /**
80  * Compare two quadruplets.
81  *
82  * @return zero if they are identically, non-zero else
83  */
84 static int entry_cmp(const void *elt, const void *key)
85 {
86         const entry_t *e1 = (const entry_t*)elt;
87         const entry_t *e2 = (const entry_t*)key;
88
89         return (e1->q.ent != e2->q.ent) || (e1->q.pos != e2->q.pos) || (e1->q.tv != e2->q.tv);
90 }
91
92 /**
93  * Hash an element of type entry_t.
94  *
95  * @param entry  The element to be hashed.
96  */
97 static unsigned hash_entry(const entry_t *entry)
98 {
99         return hash_ptr(entry->q.ent) ^ hash_ptr(entry->q.tv) ^ (unsigned)(entry->q.pos * 9);
100 }
101
102 /**
103  * Free memory associated with a quadruplet.
104  */
105 static void kill_entry(entry_t *entry)
106 {
107         if (entry->q.calls) {
108                 DEL_ARR_F(entry->q.calls);
109                 entry->q.calls = NULL;
110         }
111 }
112
113 /**
114  * Process a call node.
115  *
116  * @param call    A ir_node to be checked.
117  * @param callee  The entity of the callee
118  * @param hmap    The quadruple-set containing the calls with constant parameters
119  */
120 static void process_call(ir_node *call, ir_entity *callee, q_set *hmap)
121 {
122         entry_t *key, *entry;
123         ir_node *call_param;
124         size_t i, n_params;
125
126         n_params = get_Call_n_params(call);
127
128         /* TODO
129          * Beware: we cannot clone variadic parameters as well as the
130          * last non-variadic one, which might be needed for the va_start()
131          * magic
132          */
133
134         /* In this for loop we collect the calls, that have
135            an constant parameter. */
136         for (i = n_params; i > 0;) {
137                 call_param = get_Call_param(call, --i);
138                 if (is_Const(call_param)) {
139                         /* we have found a Call to collect and we save the informations,
140                            which we need.*/
141                         if (! hmap->map)
142                                 hmap->map = new_pset(entry_cmp, 8);
143
144                         key = OALLOC(&hmap->obst, entry_t);
145
146                         key->q.ent   = callee;
147                         key->q.pos   = i;
148                         key->q.tv    = get_Const_tarval(call_param);
149                         key->q.calls = NULL;
150                         key->weight  = 0.0F;
151                         key->next    = NULL;
152
153                         /* We insert our information in the set, where we collect the calls.*/
154                         entry = (entry_t*)pset_insert(hmap->map, key, hash_entry(key));
155
156                         if (entry != key)
157                                 obstack_free(&hmap->obst, key);
158
159                         /* add the call to the list */
160                         if (! entry->q.calls) {
161                                 entry->q.calls = NEW_ARR_F(ir_node *, 1);
162                                 entry->q.calls[0] = call;
163                         } else
164                                 ARR_APP1(ir_node *, entry->q.calls, call);
165                 }
166         }
167 }
168
169 /**
170  * Collect all calls in a ir_graph to a set.
171  *
172  * @param call   A ir_node to be checked.
173  * @param env   The quadruple-set containing the calls with constant parameters
174  */
175 static void collect_irg_calls(ir_node *call, void *env)
176 {
177         q_set *hmap = (q_set*)env;
178         ir_node *call_ptr;
179         ir_entity *callee;
180
181         /* We collect just "Call" nodes */
182         if (is_Call(call)) {
183                 call_ptr = get_Call_ptr(call);
184
185                 if (! is_SymConst_addr_ent(call_ptr))
186                         return;
187
188                 callee = get_SymConst_entity(call_ptr);
189
190                 /* we don't know which function gets finally bound to a weak symbol */
191                 if (get_entity_linkage(callee) & IR_LINKAGE_WEAK)
192                         return;
193
194                 /* we can only clone calls to existing entities */
195                 if (get_entity_irg(callee) == NULL)
196                         return;
197
198                 process_call(call, callee, hmap);
199         }
200 }
201
202 /**
203  * Make a name for a clone. The clone name is
204  * the name of the original method suffixed with "_cl_pos_nr".
205  * pos is the pos from our quadruplet and nr is a counter.
206  *
207  * @param id  The ident of the cloned function.
208  * @param pos The "pos" from our quadruplet.
209  * @param nr  A counter for the clones.
210  */
211 static ident *get_clone_ident(ident *id, size_t pos, size_t nr)
212 {
213         char clone_postfix[32];
214
215         ir_snprintf(clone_postfix, sizeof(clone_postfix), "_cl_%zu_%zu", pos, nr);
216
217         return id_mangle(id, new_id_from_str(clone_postfix));
218 }
219
220 /**
221  * Pre-Walker: Copies blocks and nodes from the original method graph
222  * to the cloned graph. Fixes the argument projection numbers for
223  * all arguments behind the removed one.
224  *
225  * @param irn  A node from the original method graph.
226  * @param env  The clone graph.
227  */
228 static void copy_nodes(ir_node *irn, void *env)
229 {
230         ir_graph *clone_irg = (ir_graph*)env;
231         ir_node  *arg       = (ir_node*)get_irg_link(clone_irg);
232         ir_node  *irg_args  = get_Proj_pred(arg);
233         ir_node  *irn_copy;
234         long      proj_nr;
235
236         /* Copy all nodes except the arg. */
237         if (irn != arg)
238                 copy_irn_to_irg(irn, clone_irg);
239
240         irn_copy = (ir_node*)get_irn_link(irn);
241
242         /* Fix argument numbers */
243         if (is_Proj(irn) && get_Proj_pred(irn) == irg_args) {
244                 proj_nr = get_Proj_proj(irn);
245                 if (get_Proj_proj(arg) < proj_nr)
246                         set_Proj_proj(irn_copy, proj_nr - 1);
247         }
248 }
249
250 /**
251  * Post-walker: Set the predecessors of the copied nodes.
252  * The copied nodes are set as link of their original nodes. The links of
253  * "irn" predecessors are the predecessors of copied node.
254  */
255 static void set_preds(ir_node *irn, void *env)
256 {
257         ir_graph *clone_irg = (ir_graph*)env;
258         ir_node  *arg       = (ir_node*)get_irg_link(clone_irg);
259         int       i;
260         ir_node  *irn_copy;
261         ir_node  *pred;
262
263         /* Arg is the method argument, that we have replaced by a constant.*/
264         if (arg == irn)
265                 return;
266
267         irn_copy = (ir_node*)get_irn_link(irn);
268
269         if (is_Block(irn)) {
270                 ir_graph *const irg = get_Block_irg(irn);
271                 for (i = get_Block_n_cfgpreds(irn) - 1; i >= 0; --i) {
272                         pred = get_Block_cfgpred(irn, i);
273                         /* "End" block must be handled extra, because it is not matured.*/
274                         if (get_irg_end_block(irg) == irn)
275                                 add_immBlock_pred(get_irg_end_block(clone_irg), (ir_node*)get_irn_link(pred));
276                         else
277                                 set_Block_cfgpred(irn_copy, i, (ir_node*)get_irn_link(pred));
278                 }
279         } else {
280                 /* First we set the block our copy if it is not a block.*/
281                 set_nodes_block(irn_copy, (ir_node*)get_irn_link(get_nodes_block(irn)));
282                 if (is_End(irn)) {
283                         /* Handle the keep-alives. This must be done separately, because
284                            the End node was NOT copied */
285                         for (i = 0; i < get_End_n_keepalives(irn); ++i)
286                                 add_End_keepalive(irn_copy, (ir_node*)get_irn_link(get_End_keepalive(irn, i)));
287                 } else {
288                         for (i = get_irn_arity(irn) - 1; i >= 0; i--) {
289                                 pred = get_irn_n(irn, i);
290                                 set_irn_n(irn_copy, i, (ir_node*)get_irn_link(pred));
291                         }
292                 }
293         }
294 }
295
296 /**
297  * Get the method argument at the position "pos".
298  *
299  * @param irg  irg that must be cloned.
300  * @param pos  The position of the argument.
301  */
302 static ir_node *get_irg_arg(ir_graph *irg, size_t pos)
303 {
304         ir_node *irg_args = get_irg_args(irg), *arg = NULL;
305
306         /* Call algorithm that computes the out edges */
307         assure_irg_outs(irg);
308
309         /* Search the argument with the number pos.*/
310         for (unsigned i = get_irn_n_outs(irg_args); i-- > 0; ) {
311                 ir_node *proj = get_irn_out(irg_args, i);
312                 if ((int)pos == get_Proj_proj(proj)) {
313                         if (arg) {
314                                 /*
315                                  * More than one arg node found:
316                                  * We rely on the fact that only one arg exists, so do
317                                  * a cheap CSE in this case.
318                                  */
319                                 set_irn_out(irg_args, i, arg, 0);
320                                 exchange(proj, arg);
321                         } else
322                                 arg = proj;
323                 }
324         }
325         assert(arg && "Argument not found");
326         return arg;
327 }
328
329 /**
330  * Create a new graph for the clone of the method,
331  * that we want to clone.
332  *
333  * @param ent The entity of the method that must be cloned.
334  * @param q   Our quadruplet.
335  */
336 static void create_clone_proc_irg(ir_entity *ent, const quadruple_t *q)
337 {
338         ir_graph *method_irg, *clone_irg;
339         ir_node *arg, *const_arg;
340
341         method_irg = get_entity_irg(ent);
342
343         /* We create the skeleton of the clone irg.*/
344         clone_irg  = new_ir_graph(ent, 0);
345
346         arg        = get_irg_arg(get_entity_irg(q->ent), q->pos);
347         /* we will replace the argument in position "q->pos" by this constant. */
348         const_arg  = new_r_Const(clone_irg, q->tv);
349
350         /* args copy in the cloned graph will be the const. */
351         set_irn_link(arg, const_arg);
352
353         /* Store the arg that will be replaced here, so we can easily detect it. */
354         set_irg_link(clone_irg, arg);
355
356         /* We copy the blocks and nodes, that must be in
357         the clone graph and set their predecessors. */
358         irg_walk_graph(method_irg, copy_nodes, set_preds, clone_irg);
359
360         /* The "cloned" graph must be matured. */
361         mature_immBlock(get_irg_end_block(clone_irg));
362         irg_finalize_cons(clone_irg);
363 }
364
365 /**
366  * The function create a new entity type
367  * for our clone and set it to clone entity.
368  *
369  * @param q   Contains information for the method to clone.
370  * @param ent The entity of the clone.
371  * @param nr  A pointer to the counter of clones.
372  **/
373 static void change_entity_type(const quadruple_t *q, ir_entity *ent)
374 {
375         ir_type *mtp, *new_mtp, *tp;
376         size_t  i, j, n_params, n_ress;
377
378         mtp      = get_entity_type(q->ent);
379         n_params = get_method_n_params(mtp);
380         n_ress   = get_method_n_ress(mtp);
381
382         /* Create the new type for our clone. It must have one parameter
383            less then the original.*/
384         new_mtp  = new_type_method(n_params - 1, n_ress);
385
386         /* We must set the type of the methods parameters.*/
387         for (i = j = 0; i < n_params; ++i) {
388                 if (i == q->pos) {
389                         /* This is the position of the argument, that we have
390                            replaced. */
391                         continue;
392                 }
393                 tp = get_method_param_type(mtp, i);
394                 set_method_param_type(new_mtp, j++, tp);
395         }
396         /* Copy the methods result types. */
397         for (i = 0; i < n_ress; ++i) {
398                 tp = get_method_res_type(mtp, i);
399                 set_method_res_type(new_mtp, i, tp);
400         }
401         set_entity_type(ent, new_mtp);
402 }
403
404 /**
405  * Make a clone of a method.
406  *
407  * @param q   Contains information for the method to clone.
408  */
409 static ir_entity *clone_method(const quadruple_t *q)
410 {
411         ir_entity *new_entity;
412         ident *clone_ident;
413         /* A counter for the clones.*/
414         static size_t nr = 0;
415
416         /* We get a new ident for our clone method.*/
417         clone_ident = get_clone_ident(get_entity_ident(q->ent), q->pos, nr);
418         /* We get our entity for the clone method. */
419         new_entity  = copy_entity_name(q->ent, clone_ident);
420
421         /* a cloned entity is always local */
422         set_entity_visibility(new_entity, ir_visibility_local);
423
424         /* set a ld name here: Should we mangle this ? */
425         set_entity_ld_ident(new_entity, get_entity_ident(new_entity));
426
427         /* set a new type here. */
428         change_entity_type(q, new_entity);
429
430         /* We need now a new ir_graph for our clone method. */
431         create_clone_proc_irg(new_entity, q);
432
433         /* The "new_entity" don't have this information. */
434         new_entity->attr.mtd_attr.param_access = NULL;
435         new_entity->attr.mtd_attr.param_weight = NULL;
436
437         return new_entity;
438 }
439
440 /**
441  * Creates a new "cloned" Call node and return it.
442  *
443  * @param call        The call that must be cloned.
444  * @param new_entity  The entity of the cloned function.
445  * @param pos         The position of the replaced parameter of this call.
446  **/
447 static ir_node *new_cl_Call(ir_node *call, ir_entity *new_entity, size_t pos)
448 {
449         ir_node **in;
450         size_t i, n_params, new_params = 0;
451         ir_node *callee;
452         symconst_symbol sym;
453         ir_graph *irg = get_irn_irg(call);
454         ir_node *bl = get_nodes_block(call);
455
456         sym.entity_p = new_entity;
457         callee = new_r_SymConst(irg, mode_P_code, sym, symconst_addr_ent);
458
459         n_params = get_Call_n_params(call);
460         NEW_ARR_A(ir_node *, in, n_params - 1);
461
462         /* we save the parameters of the new call in the array "in" without the
463          * parameter in position "pos", that is replaced with a constant.*/
464         for (i = 0; i < n_params; ++i) {
465                 if (pos != i)
466                         in[new_params++] = get_Call_param(call, i);
467         }
468         /* Create and return the new Call. */
469         return new_r_Call(bl, get_Call_mem(call),
470                 callee, n_params - 1, in, get_entity_type(new_entity));
471 }
472
473 /**
474  * Exchange all Calls stored in the quadruplet to Calls of the cloned entity.
475  *
476  * @param q             The quadruple
477  * @param cloned_ent    The entity of the new function that must be called
478  *                      from the new Call.
479  */
480 static void exchange_calls(quadruple_t *q, ir_entity *cloned_ent)
481 {
482         size_t pos = q->pos;
483         ir_node *new_call, *call;
484         size_t i;
485
486         /* We iterate the list of the "call".*/
487         for (i = 0; i < ARR_LEN(q->calls); ++i) {
488                 call = q->calls[i];
489
490                 /* A clone exist and the copy of "call" in this
491                  * clone graph must be exchanged with new one.*/
492                 new_call = new_cl_Call(call, cloned_ent, pos);
493                 exchange(call, new_call);
494         }
495 }
496
497 /**
498  * The weight formula:
499  * We save one instruction in every caller and param_weight instructions
500  * in the callee.
501  */
502 static float calculate_weight(const entry_t *entry)
503 {
504         return ARR_LEN(entry->q.calls) *
505                 (float)(get_method_param_weight(entry->q.ent, entry->q.pos) + 1);
506 }
507
508 /**
509  * After we exchanged all calls, some entries on the list for
510  * the next cloned entity may get invalid, so we have to check
511  * them and may even update the list of heavy uses.
512  */
513 static void reorder_weights(q_set *hmap, float threshold)
514 {
515         entry_t **adr, *p, *entry;
516         size_t i, len;
517
518 restart:
519         entry = hmap->heavy_uses;
520         if (! entry)
521                 return;
522
523         len = ARR_LEN(entry->q.calls);
524         for (i = 0; i < len; ++i) {
525                 ir_node *ptr, *call = entry->q.calls[i];
526
527                 /* might be exchanged, so skip Id nodes here. */
528                 call = skip_Id(call);
529
530                 /* we know, that a SymConst is here */
531                 ptr = get_Call_ptr(call);
532
533                 ir_entity *const callee = get_SymConst_entity(ptr);
534                 if (callee != entry->q.ent) {
535                         /*
536                          * This call is already changed because of a previous
537                          * optimization. Remove it from the list.
538                          */
539                         --len;
540                         entry->q.calls[i] = entry->q.calls[len];
541                         entry->q.calls[len] = NULL;
542
543                         /* the new call should be processed */
544                         process_call(call, callee, hmap);
545                         --i;
546                 }
547         }
548
549         /* the length might be changed */
550         ARR_SHRINKLEN(entry->q.calls, len);
551
552         /* recalculate the weight and resort the heavy uses map */
553         entry->weight = calculate_weight(entry);
554
555         if (len <= 0 || entry->weight < threshold) {
556                 hmap->heavy_uses = entry->next;
557                 kill_entry(entry);
558
559                 /* we have changed the list, check the next one */
560                 goto restart;
561         }
562
563         adr = NULL;
564         for (p = entry->next; p && entry->weight < p->weight; p = p->next) {
565                 adr = &p->next;
566         }
567
568         if (adr) {
569                 hmap->heavy_uses = entry->next;
570                 entry->next      = *adr;
571                 *adr             = entry;
572
573                 /* we have changed the list, check the next one */
574                 goto restart;
575         }
576 }
577
578 /*
579  * Do the procedure cloning. Evaluate a heuristic weight for every
580  * call(..., Const, ...). If the weight is bigger than threshold,
581  * clone the entity and fix the calls.
582  */
583 void proc_cloning(float threshold)
584 {
585         entry_t *p;
586         size_t i, n;
587         q_set hmap;
588
589         DEBUG_ONLY(firm_dbg_module_t *dbg;)
590
591         /* register a debug mask */
592         FIRM_DBG_REGISTER(dbg, "firm.opt.proc_cloning");
593
594         obstack_init(&hmap.obst);
595         hmap.map        = NULL;
596         hmap.heavy_uses = NULL;
597
598         /* initially fill our map by visiting all irgs */
599         for (i = 0, n = get_irp_n_irgs(); i < n; ++i) {
600                 ir_graph *irg = get_irp_irg(i);
601                 irg_walk_graph(irg, collect_irg_calls, NULL, &hmap);
602         }
603
604         /* We have the "Call" nodes to optimize in set "set_entries". Our algorithm
605            replace one constant parameter and make a new "Call" node for all found "Calls". It exchange the
606            old one with the new one and the algorithm is called with the new "Call".
607          */
608         while (hmap.map || hmap.heavy_uses) {
609                 /* We iterate the set and arrange the element of the set in a list.
610                    The elements are arranged dependent of their value descending.*/
611                 if (hmap.map) {
612                         foreach_pset(hmap.map, entry_t, entry) {
613                                 entry->weight = calculate_weight(entry);
614
615                                 /*
616                                  * Do not put entry with a weight < threshold in the list
617                                  */
618                                 if (entry->weight < threshold) {
619                                         kill_entry(entry);
620                                         continue;
621                                 }
622
623                                 /* put entry in the heavy uses list */
624                                 entry->next = NULL;
625                                 if (! hmap.heavy_uses)
626                                         hmap.heavy_uses = entry;
627                                 else {
628                                         if (entry->weight >= hmap.heavy_uses->weight) {
629                                                 entry->next     = hmap.heavy_uses;
630                                                 hmap.heavy_uses = entry;
631                                         } else {
632                                                 for (p = hmap.heavy_uses; p->next; p = p->next) {
633                                                         if (entry->weight >= p->next->weight) {
634                                                                 entry->next = p->next;
635                                                                 p->next     = entry;
636                                                                 break;
637                                                         }
638                                                 }
639                                                 if (! p->next)
640                                                         p->next = entry;
641                                         }
642                                 }
643                         }
644                         del_pset(hmap.map);
645                         hmap.map = NULL;
646                 }
647
648 #ifdef DEBUG_libfirm
649                 /* Print some information about the list. */
650                 DB((dbg, LEVEL_2, "-----------------\n"));
651                 for (entry_t *entry = hmap.heavy_uses; entry; entry = entry->next) {
652                         DB((dbg, LEVEL_2, "\nweight: is %f\n", entry->weight));
653                         DB((dbg, LEVEL_2, "Call for Method %E\n", entry->q.ent));
654                         DB((dbg, LEVEL_2, "Position %zu\n", entry->q.pos));
655                         DB((dbg, LEVEL_2, "Value %T\n", entry->q.tv));
656                 }
657 #endif
658                 entry_t *const entry = hmap.heavy_uses;
659                 if (entry) {
660                         quadruple_t *qp = &entry->q;
661
662                         ir_entity *ent = clone_method(qp);
663                         DB((dbg, LEVEL_1, "Cloned <%+F, %zu, %T> info %+F\n", qp->ent, qp->pos, qp->tv, ent));
664
665                         hmap.heavy_uses = entry->next;
666
667                         /* We must exchange the copies of this call in all clones too.*/
668                         exchange_calls(&entry->q, ent);
669                         kill_entry(entry);
670
671                         /*
672                          * after we exchanged all calls, some entries on the list for
673                          * the next cloned entity may get invalid, so we have to check
674                          * them and may even update the list of heavy uses.
675                          */
676                         reorder_weights(&hmap, threshold);
677                 }
678         }
679         obstack_free(&hmap.obst, NULL);
680 }
681
682 typedef struct pass_t {
683         ir_prog_pass_t pass;
684         float          threshold;
685 } pass_t;
686
687 /**
688  * Wrapper to run proc_cloning() as an ir_prog pass.
689  */
690 static int proc_cloning_wrapper(ir_prog *irp, void *context)
691 {
692         pass_t *pass = (pass_t*)context;
693
694         (void)irp;
695         proc_cloning(pass->threshold);
696         return 0;
697 }
698
699 /* create a ir_prog pass */
700 ir_prog_pass_t *proc_cloning_pass(const char *name, float threshold)
701 {
702         pass_t *pass = XMALLOCZ(pass_t);
703
704         pass->threshold = threshold;
705         return def_prog_pass_constructor(
706                 &pass->pass, name ? name : "cloning", proc_cloning_wrapper);
707 }