OSDN Git Service

2011-12-11 Paul Thomas <pault@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / trans-intrinsic.c
1 /* Intrinsic translation
2    Copyright (C) 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011
3    Free Software Foundation, Inc.
4    Contributed by Paul Brook <paul@nowt.org>
5    and Steven Bosscher <s.bosscher@student.tudelft.nl>
6
7 This file is part of GCC.
8
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
13
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17 for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3.  If not see
21 <http://www.gnu.org/licenses/>.  */
22
23 /* trans-intrinsic.c-- generate GENERIC trees for calls to intrinsics.  */
24
25 #include "config.h"
26 #include "system.h"
27 #include "coretypes.h"
28 #include "tm.h"         /* For UNITS_PER_WORD.  */
29 #include "tree.h"
30 #include "ggc.h"
31 #include "diagnostic-core.h"    /* For internal_error.  */
32 #include "toplev.h"     /* For rest_of_decl_compilation.  */
33 #include "flags.h"
34 #include "gfortran.h"
35 #include "arith.h"
36 #include "intrinsic.h"
37 #include "trans.h"
38 #include "trans-const.h"
39 #include "trans-types.h"
40 #include "trans-array.h"
41 #include "defaults.h"
42 /* Only for gfc_trans_assign and gfc_trans_pointer_assign.  */
43 #include "trans-stmt.h"
44
45 /* This maps fortran intrinsic math functions to external library or GCC
46    builtin functions.  */
47 typedef struct GTY(()) gfc_intrinsic_map_t {
48   /* The explicit enum is required to work around inadequacies in the
49      garbage collection/gengtype parsing mechanism.  */
50   enum gfc_isym_id id;
51
52   /* Enum value from the "language-independent", aka C-centric, part
53      of gcc, or END_BUILTINS of no such value set.  */
54   enum built_in_function float_built_in;
55   enum built_in_function double_built_in;
56   enum built_in_function long_double_built_in;
57   enum built_in_function complex_float_built_in;
58   enum built_in_function complex_double_built_in;
59   enum built_in_function complex_long_double_built_in;
60
61   /* True if the naming pattern is to prepend "c" for complex and
62      append "f" for kind=4.  False if the naming pattern is to
63      prepend "_gfortran_" and append "[rc](4|8|10|16)".  */
64   bool libm_name;
65
66   /* True if a complex version of the function exists.  */
67   bool complex_available;
68
69   /* True if the function should be marked const.  */
70   bool is_constant;
71
72   /* The base library name of this function.  */
73   const char *name;
74
75   /* Cache decls created for the various operand types.  */
76   tree real4_decl;
77   tree real8_decl;
78   tree real10_decl;
79   tree real16_decl;
80   tree complex4_decl;
81   tree complex8_decl;
82   tree complex10_decl;
83   tree complex16_decl;
84 }
85 gfc_intrinsic_map_t;
86
87 /* ??? The NARGS==1 hack here is based on the fact that (c99 at least)
88    defines complex variants of all of the entries in mathbuiltins.def
89    except for atan2.  */
90 #define DEFINE_MATH_BUILTIN(ID, NAME, ARGTYPE) \
91   { GFC_ISYM_ ## ID, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
92     BUILT_IN_ ## ID ## L, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
93     true, false, true, NAME, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, \
94     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
95
96 #define DEFINE_MATH_BUILTIN_C(ID, NAME, ARGTYPE) \
97   { GFC_ISYM_ ## ID, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
98     BUILT_IN_ ## ID ## L, BUILT_IN_C ## ID ## F, BUILT_IN_C ## ID, \
99     BUILT_IN_C ## ID ## L, true, true, true, NAME, NULL_TREE, NULL_TREE, \
100     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
101
102 #define LIB_FUNCTION(ID, NAME, HAVE_COMPLEX) \
103   { GFC_ISYM_ ## ID, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
104     END_BUILTINS, END_BUILTINS, END_BUILTINS, \
105     false, HAVE_COMPLEX, true, NAME, NULL_TREE, NULL_TREE, NULL_TREE, \
106     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE }
107
108 #define OTHER_BUILTIN(ID, NAME, TYPE, CONST) \
109   { GFC_ISYM_NONE, BUILT_IN_ ## ID ## F, BUILT_IN_ ## ID, \
110     BUILT_IN_ ## ID ## L, END_BUILTINS, END_BUILTINS, END_BUILTINS, \
111     true, false, CONST, NAME, NULL_TREE, NULL_TREE, \
112     NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE},
113
114 static GTY(()) gfc_intrinsic_map_t gfc_intrinsic_map[] =
115 {
116   /* Functions built into gcc itself (DEFINE_MATH_BUILTIN and
117      DEFINE_MATH_BUILTIN_C), then the built-ins that don't correspond
118      to any GFC_ISYM id directly, which use the OTHER_BUILTIN macro.  */
119 #include "mathbuiltins.def"
120
121   /* Functions in libgfortran.  */
122   LIB_FUNCTION (ERFC_SCALED, "erfc_scaled", false),
123
124   /* End the list.  */
125   LIB_FUNCTION (NONE, NULL, false)
126
127 };
128 #undef OTHER_BUILTIN
129 #undef LIB_FUNCTION
130 #undef DEFINE_MATH_BUILTIN
131 #undef DEFINE_MATH_BUILTIN_C
132
133
134 enum rounding_mode { RND_ROUND, RND_TRUNC, RND_CEIL, RND_FLOOR };
135
136
137 /* Find the correct variant of a given builtin from its argument.  */
138 static tree
139 builtin_decl_for_precision (enum built_in_function base_built_in,
140                             int precision)
141 {
142   enum built_in_function i = END_BUILTINS;
143
144   gfc_intrinsic_map_t *m;
145   for (m = gfc_intrinsic_map; m->double_built_in != base_built_in ; m++)
146     ;
147
148   if (precision == TYPE_PRECISION (float_type_node))
149     i = m->float_built_in;
150   else if (precision == TYPE_PRECISION (double_type_node))
151     i = m->double_built_in;
152   else if (precision == TYPE_PRECISION (long_double_type_node))
153     i = m->long_double_built_in;
154   else if (precision == TYPE_PRECISION (float128_type_node))
155     {
156       /* Special treatment, because it is not exactly a built-in, but
157          a library function.  */
158       return m->real16_decl;
159     }
160
161   return (i == END_BUILTINS ? NULL_TREE : builtin_decl_explicit (i));
162 }
163
164
165 tree
166 gfc_builtin_decl_for_float_kind (enum built_in_function double_built_in,
167                                  int kind)
168 {
169   int i = gfc_validate_kind (BT_REAL, kind, false);
170
171   if (gfc_real_kinds[i].c_float128)
172     {
173       /* For __float128, the story is a bit different, because we return
174          a decl to a library function rather than a built-in.  */
175       gfc_intrinsic_map_t *m; 
176       for (m = gfc_intrinsic_map; m->double_built_in != double_built_in ; m++)
177         ;
178
179       return m->real16_decl;
180     }
181
182   return builtin_decl_for_precision (double_built_in,
183                                      gfc_real_kinds[i].mode_precision);
184 }
185
186
187 /* Evaluate the arguments to an intrinsic function.  The value
188    of NARGS may be less than the actual number of arguments in EXPR
189    to allow optional "KIND" arguments that are not included in the
190    generated code to be ignored.  */
191
192 static void
193 gfc_conv_intrinsic_function_args (gfc_se *se, gfc_expr *expr,
194                                   tree *argarray, int nargs)
195 {
196   gfc_actual_arglist *actual;
197   gfc_expr *e;
198   gfc_intrinsic_arg  *formal;
199   gfc_se argse;
200   int curr_arg;
201
202   formal = expr->value.function.isym->formal;
203   actual = expr->value.function.actual;
204
205    for (curr_arg = 0; curr_arg < nargs; curr_arg++,
206         actual = actual->next,
207         formal = formal ? formal->next : NULL)
208     {
209       gcc_assert (actual);
210       e = actual->expr;
211       /* Skip omitted optional arguments.  */
212       if (!e)
213         {
214           --curr_arg;
215           continue;
216         }
217
218       /* Evaluate the parameter.  This will substitute scalarized
219          references automatically.  */
220       gfc_init_se (&argse, se);
221
222       if (e->ts.type == BT_CHARACTER)
223         {
224           gfc_conv_expr (&argse, e);
225           gfc_conv_string_parameter (&argse);
226           argarray[curr_arg++] = argse.string_length;
227           gcc_assert (curr_arg < nargs);
228         }
229       else
230         gfc_conv_expr_val (&argse, e);
231
232       /* If an optional argument is itself an optional dummy argument,
233          check its presence and substitute a null if absent.  */
234       if (e->expr_type == EXPR_VARIABLE
235             && e->symtree->n.sym->attr.optional
236             && formal
237             && formal->optional)
238         gfc_conv_missing_dummy (&argse, e, formal->ts, 0);
239
240       gfc_add_block_to_block (&se->pre, &argse.pre);
241       gfc_add_block_to_block (&se->post, &argse.post);
242       argarray[curr_arg] = argse.expr;
243     }
244 }
245
246 /* Count the number of actual arguments to the intrinsic function EXPR
247    including any "hidden" string length arguments.  */
248
249 static unsigned int
250 gfc_intrinsic_argument_list_length (gfc_expr *expr)
251 {
252   int n = 0;
253   gfc_actual_arglist *actual;
254
255   for (actual = expr->value.function.actual; actual; actual = actual->next)
256     {
257       if (!actual->expr)
258         continue;
259
260       if (actual->expr->ts.type == BT_CHARACTER)
261         n += 2;
262       else
263         n++;
264     }
265
266   return n;
267 }
268
269
270 /* Conversions between different types are output by the frontend as
271    intrinsic functions.  We implement these directly with inline code.  */
272
273 static void
274 gfc_conv_intrinsic_conversion (gfc_se * se, gfc_expr * expr)
275 {
276   tree type;
277   tree *args;
278   int nargs;
279
280   nargs = gfc_intrinsic_argument_list_length (expr);
281   args = XALLOCAVEC (tree, nargs);
282
283   /* Evaluate all the arguments passed. Whilst we're only interested in the 
284      first one here, there are other parts of the front-end that assume this 
285      and will trigger an ICE if it's not the case.  */
286   type = gfc_typenode_for_spec (&expr->ts);
287   gcc_assert (expr->value.function.actual->expr);
288   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
289
290   /* Conversion between character kinds involves a call to a library
291      function.  */
292   if (expr->ts.type == BT_CHARACTER)
293     {
294       tree fndecl, var, addr, tmp;
295
296       if (expr->ts.kind == 1
297           && expr->value.function.actual->expr->ts.kind == 4)
298         fndecl = gfor_fndecl_convert_char4_to_char1;
299       else if (expr->ts.kind == 4
300                && expr->value.function.actual->expr->ts.kind == 1)
301         fndecl = gfor_fndecl_convert_char1_to_char4;
302       else
303         gcc_unreachable ();
304
305       /* Create the variable storing the converted value.  */
306       type = gfc_get_pchar_type (expr->ts.kind);
307       var = gfc_create_var (type, "str");
308       addr = gfc_build_addr_expr (build_pointer_type (type), var);
309
310       /* Call the library function that will perform the conversion.  */
311       gcc_assert (nargs >= 2);
312       tmp = build_call_expr_loc (input_location,
313                              fndecl, 3, addr, args[0], args[1]);
314       gfc_add_expr_to_block (&se->pre, tmp);
315
316       /* Free the temporary afterwards.  */
317       tmp = gfc_call_free (var);
318       gfc_add_expr_to_block (&se->post, tmp);
319
320       se->expr = var;
321       se->string_length = args[0];
322
323       return;
324     }
325
326   /* Conversion from complex to non-complex involves taking the real
327      component of the value.  */
328   if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE
329       && expr->ts.type != BT_COMPLEX)
330     {
331       tree artype;
332
333       artype = TREE_TYPE (TREE_TYPE (args[0]));
334       args[0] = fold_build1_loc (input_location, REALPART_EXPR, artype,
335                                  args[0]);
336     }
337
338   se->expr = convert (type, args[0]);
339 }
340
341 /* This is needed because the gcc backend only implements
342    FIX_TRUNC_EXPR, which is the same as INT() in Fortran.
343    FLOOR(x) = INT(x) <= x ? INT(x) : INT(x) - 1
344    Similarly for CEILING.  */
345
346 static tree
347 build_fixbound_expr (stmtblock_t * pblock, tree arg, tree type, int up)
348 {
349   tree tmp;
350   tree cond;
351   tree argtype;
352   tree intval;
353
354   argtype = TREE_TYPE (arg);
355   arg = gfc_evaluate_now (arg, pblock);
356
357   intval = convert (type, arg);
358   intval = gfc_evaluate_now (intval, pblock);
359
360   tmp = convert (argtype, intval);
361   cond = fold_build2_loc (input_location, up ? GE_EXPR : LE_EXPR,
362                           boolean_type_node, tmp, arg);
363
364   tmp = fold_build2_loc (input_location, up ? PLUS_EXPR : MINUS_EXPR, type,
365                          intval, build_int_cst (type, 1));
366   tmp = fold_build3_loc (input_location, COND_EXPR, type, cond, intval, tmp);
367   return tmp;
368 }
369
370
371 /* Round to nearest integer, away from zero.  */
372
373 static tree
374 build_round_expr (tree arg, tree restype)
375 {
376   tree argtype;
377   tree fn;
378   bool longlong;
379   int argprec, resprec;
380
381   argtype = TREE_TYPE (arg);
382   argprec = TYPE_PRECISION (argtype);
383   resprec = TYPE_PRECISION (restype);
384
385   /* Depending on the type of the result, choose the long int intrinsic
386      (lround family) or long long intrinsic (llround).  We might also
387      need to convert the result afterwards.  */
388   if (resprec <= LONG_TYPE_SIZE)
389     longlong = false;
390   else if (resprec <= LONG_LONG_TYPE_SIZE)
391     longlong = true;
392   else
393     gcc_unreachable ();
394
395   /* Now, depending on the argument type, we choose between intrinsics.  */
396   if (longlong)
397     fn = builtin_decl_for_precision (BUILT_IN_LLROUND, argprec);
398   else
399     fn = builtin_decl_for_precision (BUILT_IN_LROUND, argprec);
400
401   return fold_convert (restype, build_call_expr_loc (input_location,
402                                                  fn, 1, arg));
403 }
404
405
406 /* Convert a real to an integer using a specific rounding mode.
407    Ideally we would just build the corresponding GENERIC node,
408    however the RTL expander only actually supports FIX_TRUNC_EXPR.  */
409
410 static tree
411 build_fix_expr (stmtblock_t * pblock, tree arg, tree type,
412                enum rounding_mode op)
413 {
414   switch (op)
415     {
416     case RND_FLOOR:
417       return build_fixbound_expr (pblock, arg, type, 0);
418       break;
419
420     case RND_CEIL:
421       return build_fixbound_expr (pblock, arg, type, 1);
422       break;
423
424     case RND_ROUND:
425       return build_round_expr (arg, type);
426       break;
427
428     case RND_TRUNC:
429       return fold_build1_loc (input_location, FIX_TRUNC_EXPR, type, arg);
430       break;
431
432     default:
433       gcc_unreachable ();
434     }
435 }
436
437
438 /* Round a real value using the specified rounding mode.
439    We use a temporary integer of that same kind size as the result.
440    Values larger than those that can be represented by this kind are
441    unchanged, as they will not be accurate enough to represent the
442    rounding.
443     huge = HUGE (KIND (a))
444     aint (a) = ((a > huge) || (a < -huge)) ? a : (real)(int)a
445    */
446
447 static void
448 gfc_conv_intrinsic_aint (gfc_se * se, gfc_expr * expr, enum rounding_mode op)
449 {
450   tree type;
451   tree itype;
452   tree arg[2];
453   tree tmp;
454   tree cond;
455   tree decl;
456   mpfr_t huge;
457   int n, nargs;
458   int kind;
459
460   kind = expr->ts.kind;
461   nargs = gfc_intrinsic_argument_list_length (expr);
462
463   decl = NULL_TREE;
464   /* We have builtin functions for some cases.  */
465   switch (op)
466     {
467     case RND_ROUND:
468       decl = gfc_builtin_decl_for_float_kind (BUILT_IN_ROUND, kind);
469       break;
470
471     case RND_TRUNC:
472       decl = gfc_builtin_decl_for_float_kind (BUILT_IN_TRUNC, kind);
473       break;
474
475     default:
476       gcc_unreachable ();
477     }
478
479   /* Evaluate the argument.  */
480   gcc_assert (expr->value.function.actual->expr);
481   gfc_conv_intrinsic_function_args (se, expr, arg, nargs);
482
483   /* Use a builtin function if one exists.  */
484   if (decl != NULL_TREE)
485     {
486       se->expr = build_call_expr_loc (input_location, decl, 1, arg[0]);
487       return;
488     }
489
490   /* This code is probably redundant, but we'll keep it lying around just
491      in case.  */
492   type = gfc_typenode_for_spec (&expr->ts);
493   arg[0] = gfc_evaluate_now (arg[0], &se->pre);
494
495   /* Test if the value is too large to handle sensibly.  */
496   gfc_set_model_kind (kind);
497   mpfr_init (huge);
498   n = gfc_validate_kind (BT_INTEGER, kind, false);
499   mpfr_set_z (huge, gfc_integer_kinds[n].huge, GFC_RND_MODE);
500   tmp = gfc_conv_mpfr_to_tree (huge, kind, 0);
501   cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node, arg[0],
502                           tmp);
503
504   mpfr_neg (huge, huge, GFC_RND_MODE);
505   tmp = gfc_conv_mpfr_to_tree (huge, kind, 0);
506   tmp = fold_build2_loc (input_location, GT_EXPR, boolean_type_node, arg[0],
507                          tmp);
508   cond = fold_build2_loc (input_location, TRUTH_AND_EXPR, boolean_type_node,
509                           cond, tmp);
510   itype = gfc_get_int_type (kind);
511
512   tmp = build_fix_expr (&se->pre, arg[0], itype, op);
513   tmp = convert (type, tmp);
514   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond, tmp,
515                               arg[0]);
516   mpfr_clear (huge);
517 }
518
519
520 /* Convert to an integer using the specified rounding mode.  */
521
522 static void
523 gfc_conv_intrinsic_int (gfc_se * se, gfc_expr * expr, enum rounding_mode op)
524 {
525   tree type;
526   tree *args;
527   int nargs;
528
529   nargs = gfc_intrinsic_argument_list_length (expr);
530   args = XALLOCAVEC (tree, nargs);
531
532   /* Evaluate the argument, we process all arguments even though we only 
533      use the first one for code generation purposes.  */
534   type = gfc_typenode_for_spec (&expr->ts);
535   gcc_assert (expr->value.function.actual->expr);
536   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
537
538   if (TREE_CODE (TREE_TYPE (args[0])) == INTEGER_TYPE)
539     {
540       /* Conversion to a different integer kind.  */
541       se->expr = convert (type, args[0]);
542     }
543   else
544     {
545       /* Conversion from complex to non-complex involves taking the real
546          component of the value.  */
547       if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE
548           && expr->ts.type != BT_COMPLEX)
549         {
550           tree artype;
551
552           artype = TREE_TYPE (TREE_TYPE (args[0]));
553           args[0] = fold_build1_loc (input_location, REALPART_EXPR, artype,
554                                      args[0]);
555         }
556
557       se->expr = build_fix_expr (&se->pre, args[0], type, op);
558     }
559 }
560
561
562 /* Get the imaginary component of a value.  */
563
564 static void
565 gfc_conv_intrinsic_imagpart (gfc_se * se, gfc_expr * expr)
566 {
567   tree arg;
568
569   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
570   se->expr = fold_build1_loc (input_location, IMAGPART_EXPR,
571                               TREE_TYPE (TREE_TYPE (arg)), arg);
572 }
573
574
575 /* Get the complex conjugate of a value.  */
576
577 static void
578 gfc_conv_intrinsic_conjg (gfc_se * se, gfc_expr * expr)
579 {
580   tree arg;
581
582   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
583   se->expr = fold_build1_loc (input_location, CONJ_EXPR, TREE_TYPE (arg), arg);
584 }
585
586
587
588 static tree
589 define_quad_builtin (const char *name, tree type, bool is_const)
590 {
591   tree fndecl;
592   fndecl = build_decl (input_location, FUNCTION_DECL, get_identifier (name),
593                        type);
594
595   /* Mark the decl as external.  */
596   DECL_EXTERNAL (fndecl) = 1;
597   TREE_PUBLIC (fndecl) = 1;
598
599   /* Mark it __attribute__((const)).  */
600   TREE_READONLY (fndecl) = is_const;
601
602   rest_of_decl_compilation (fndecl, 1, 0);
603
604   return fndecl;
605 }
606
607
608
609 /* Initialize function decls for library functions.  The external functions
610    are created as required.  Builtin functions are added here.  */
611
612 void
613 gfc_build_intrinsic_lib_fndecls (void)
614 {
615   gfc_intrinsic_map_t *m;
616   tree quad_decls[END_BUILTINS + 1];
617
618   if (gfc_real16_is_float128)
619   {
620     /* If we have soft-float types, we create the decls for their
621        C99-like library functions.  For now, we only handle __float128
622        q-suffixed functions.  */
623
624     tree type, complex_type, func_1, func_2, func_cabs, func_frexp;
625     tree func_lround, func_llround, func_scalbn, func_cpow;
626
627     memset (quad_decls, 0, sizeof(tree) * (END_BUILTINS + 1));
628
629     type = float128_type_node;
630     complex_type = complex_float128_type_node;
631     /* type (*) (type) */
632     func_1 = build_function_type_list (type, type, NULL_TREE);
633     /* long (*) (type) */
634     func_lround = build_function_type_list (long_integer_type_node,
635                                             type, NULL_TREE);
636     /* long long (*) (type) */
637     func_llround = build_function_type_list (long_long_integer_type_node,
638                                              type, NULL_TREE);
639     /* type (*) (type, type) */
640     func_2 = build_function_type_list (type, type, type, NULL_TREE);
641     /* type (*) (type, &int) */
642     func_frexp
643       = build_function_type_list (type,
644                                   type,
645                                   build_pointer_type (integer_type_node),
646                                   NULL_TREE);
647     /* type (*) (type, int) */
648     func_scalbn = build_function_type_list (type,
649                                             type, integer_type_node, NULL_TREE);
650     /* type (*) (complex type) */
651     func_cabs = build_function_type_list (type, complex_type, NULL_TREE);
652     /* complex type (*) (complex type, complex type) */
653     func_cpow
654       = build_function_type_list (complex_type,
655                                   complex_type, complex_type, NULL_TREE);
656
657 #define DEFINE_MATH_BUILTIN(ID, NAME, ARGTYPE)
658 #define DEFINE_MATH_BUILTIN_C(ID, NAME, ARGTYPE)
659 #define LIB_FUNCTION(ID, NAME, HAVE_COMPLEX)
660
661     /* Only these built-ins are actually needed here. These are used directly
662        from the code, when calling builtin_decl_for_precision() or
663        builtin_decl_for_float_type(). The others are all constructed by
664        gfc_get_intrinsic_lib_fndecl().  */
665 #define OTHER_BUILTIN(ID, NAME, TYPE, CONST) \
666   quad_decls[BUILT_IN_ ## ID] = define_quad_builtin (NAME "q", func_ ## TYPE, CONST);
667
668 #include "mathbuiltins.def"
669
670 #undef OTHER_BUILTIN
671 #undef LIB_FUNCTION
672 #undef DEFINE_MATH_BUILTIN
673 #undef DEFINE_MATH_BUILTIN_C
674
675   }
676
677   /* Add GCC builtin functions.  */
678   for (m = gfc_intrinsic_map;
679        m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
680     {
681       if (m->float_built_in != END_BUILTINS)
682         m->real4_decl = builtin_decl_explicit (m->float_built_in);
683       if (m->complex_float_built_in != END_BUILTINS)
684         m->complex4_decl = builtin_decl_explicit (m->complex_float_built_in);
685       if (m->double_built_in != END_BUILTINS)
686         m->real8_decl = builtin_decl_explicit (m->double_built_in);
687       if (m->complex_double_built_in != END_BUILTINS)
688         m->complex8_decl = builtin_decl_explicit (m->complex_double_built_in);
689
690       /* If real(kind=10) exists, it is always long double.  */
691       if (m->long_double_built_in != END_BUILTINS)
692         m->real10_decl = builtin_decl_explicit (m->long_double_built_in);
693       if (m->complex_long_double_built_in != END_BUILTINS)
694         m->complex10_decl
695           = builtin_decl_explicit (m->complex_long_double_built_in);
696
697       if (!gfc_real16_is_float128)
698         {
699           if (m->long_double_built_in != END_BUILTINS)
700             m->real16_decl = builtin_decl_explicit (m->long_double_built_in);
701           if (m->complex_long_double_built_in != END_BUILTINS)
702             m->complex16_decl
703               = builtin_decl_explicit (m->complex_long_double_built_in);
704         }
705       else if (quad_decls[m->double_built_in] != NULL_TREE)
706         {
707           /* Quad-precision function calls are constructed when first
708              needed by builtin_decl_for_precision(), except for those
709              that will be used directly (define by OTHER_BUILTIN).  */
710           m->real16_decl = quad_decls[m->double_built_in];
711         }
712       else if (quad_decls[m->complex_double_built_in] != NULL_TREE)
713         {
714           /* Same thing for the complex ones.  */
715           m->complex16_decl = quad_decls[m->double_built_in];
716         }
717     }
718 }
719
720
721 /* Create a fndecl for a simple intrinsic library function.  */
722
723 static tree
724 gfc_get_intrinsic_lib_fndecl (gfc_intrinsic_map_t * m, gfc_expr * expr)
725 {
726   tree type;
727   VEC(tree,gc) *argtypes;
728   tree fndecl;
729   gfc_actual_arglist *actual;
730   tree *pdecl;
731   gfc_typespec *ts;
732   char name[GFC_MAX_SYMBOL_LEN + 3];
733
734   ts = &expr->ts;
735   if (ts->type == BT_REAL)
736     {
737       switch (ts->kind)
738         {
739         case 4:
740           pdecl = &m->real4_decl;
741           break;
742         case 8:
743           pdecl = &m->real8_decl;
744           break;
745         case 10:
746           pdecl = &m->real10_decl;
747           break;
748         case 16:
749           pdecl = &m->real16_decl;
750           break;
751         default:
752           gcc_unreachable ();
753         }
754     }
755   else if (ts->type == BT_COMPLEX)
756     {
757       gcc_assert (m->complex_available);
758
759       switch (ts->kind)
760         {
761         case 4:
762           pdecl = &m->complex4_decl;
763           break;
764         case 8:
765           pdecl = &m->complex8_decl;
766           break;
767         case 10:
768           pdecl = &m->complex10_decl;
769           break;
770         case 16:
771           pdecl = &m->complex16_decl;
772           break;
773         default:
774           gcc_unreachable ();
775         }
776     }
777   else
778     gcc_unreachable ();
779
780   if (*pdecl)
781     return *pdecl;
782
783   if (m->libm_name)
784     {
785       int n = gfc_validate_kind (BT_REAL, ts->kind, false);
786       if (gfc_real_kinds[n].c_float)
787         snprintf (name, sizeof (name), "%s%s%s",
788                   ts->type == BT_COMPLEX ? "c" : "", m->name, "f");
789       else if (gfc_real_kinds[n].c_double)
790         snprintf (name, sizeof (name), "%s%s",
791                   ts->type == BT_COMPLEX ? "c" : "", m->name);
792       else if (gfc_real_kinds[n].c_long_double)
793         snprintf (name, sizeof (name), "%s%s%s",
794                   ts->type == BT_COMPLEX ? "c" : "", m->name, "l");
795       else if (gfc_real_kinds[n].c_float128)
796         snprintf (name, sizeof (name), "%s%s%s",
797                   ts->type == BT_COMPLEX ? "c" : "", m->name, "q");
798       else
799         gcc_unreachable ();
800     }
801   else
802     {
803       snprintf (name, sizeof (name), PREFIX ("%s_%c%d"), m->name,
804                 ts->type == BT_COMPLEX ? 'c' : 'r',
805                 ts->kind);
806     }
807
808   argtypes = NULL;
809   for (actual = expr->value.function.actual; actual; actual = actual->next)
810     {
811       type = gfc_typenode_for_spec (&actual->expr->ts);
812       VEC_safe_push (tree, gc, argtypes, type);
813     }
814   type = build_function_type_vec (gfc_typenode_for_spec (ts), argtypes);
815   fndecl = build_decl (input_location,
816                        FUNCTION_DECL, get_identifier (name), type);
817
818   /* Mark the decl as external.  */
819   DECL_EXTERNAL (fndecl) = 1;
820   TREE_PUBLIC (fndecl) = 1;
821
822   /* Mark it __attribute__((const)), if possible.  */
823   TREE_READONLY (fndecl) = m->is_constant;
824
825   rest_of_decl_compilation (fndecl, 1, 0);
826
827   (*pdecl) = fndecl;
828   return fndecl;
829 }
830
831
832 /* Convert an intrinsic function into an external or builtin call.  */
833
834 static void
835 gfc_conv_intrinsic_lib_function (gfc_se * se, gfc_expr * expr)
836 {
837   gfc_intrinsic_map_t *m;
838   tree fndecl;
839   tree rettype;
840   tree *args;
841   unsigned int num_args;
842   gfc_isym_id id;
843
844   id = expr->value.function.isym->id;
845   /* Find the entry for this function.  */
846   for (m = gfc_intrinsic_map;
847        m->id != GFC_ISYM_NONE || m->double_built_in != END_BUILTINS; m++)
848     {
849       if (id == m->id)
850         break;
851     }
852
853   if (m->id == GFC_ISYM_NONE)
854     {
855       internal_error ("Intrinsic function %s(%d) not recognized",
856                       expr->value.function.name, id);
857     }
858
859   /* Get the decl and generate the call.  */
860   num_args = gfc_intrinsic_argument_list_length (expr);
861   args = XALLOCAVEC (tree, num_args);
862
863   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
864   fndecl = gfc_get_intrinsic_lib_fndecl (m, expr);
865   rettype = TREE_TYPE (TREE_TYPE (fndecl));
866
867   fndecl = build_addr (fndecl, current_function_decl);
868   se->expr = build_call_array_loc (input_location, rettype, fndecl, num_args, args);
869 }
870
871
872 /* If bounds-checking is enabled, create code to verify at runtime that the
873    string lengths for both expressions are the same (needed for e.g. MERGE).
874    If bounds-checking is not enabled, does nothing.  */
875
876 void
877 gfc_trans_same_strlen_check (const char* intr_name, locus* where,
878                              tree a, tree b, stmtblock_t* target)
879 {
880   tree cond;
881   tree name;
882
883   /* If bounds-checking is disabled, do nothing.  */
884   if (!(gfc_option.rtcheck & GFC_RTCHECK_BOUNDS))
885     return;
886
887   /* Compare the two string lengths.  */
888   cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, a, b);
889
890   /* Output the runtime-check.  */
891   name = gfc_build_cstring_const (intr_name);
892   name = gfc_build_addr_expr (pchar_type_node, name);
893   gfc_trans_runtime_check (true, false, cond, target, where,
894                            "Unequal character lengths (%ld/%ld) in %s",
895                            fold_convert (long_integer_type_node, a),
896                            fold_convert (long_integer_type_node, b), name);
897 }
898
899
900 /* The EXPONENT(s) intrinsic function is translated into
901        int ret;
902        frexp (s, &ret);
903        return ret;
904  */
905
906 static void
907 gfc_conv_intrinsic_exponent (gfc_se *se, gfc_expr *expr)
908 {
909   tree arg, type, res, tmp, frexp;
910
911   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP,
912                                        expr->value.function.actual->expr->ts.kind);
913
914   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
915
916   res = gfc_create_var (integer_type_node, NULL);
917   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
918                              gfc_build_addr_expr (NULL_TREE, res));
919   gfc_add_expr_to_block (&se->pre, tmp);
920
921   type = gfc_typenode_for_spec (&expr->ts);
922   se->expr = fold_convert (type, res);
923 }
924
925
926 /* Convert the last ref of a scalar coarray from an AR_ELEMENT to an
927    AR_FULL, suitable for the scalarizer.  */
928
929 static gfc_ss *
930 walk_coarray (gfc_expr *e)
931 {
932   gfc_ss *ss;
933
934   gcc_assert (gfc_get_corank (e) > 0);
935
936   ss = gfc_walk_expr (e);
937
938   /* Fix scalar coarray.  */
939   if (ss == gfc_ss_terminator)
940     {
941       gfc_ref *ref;
942
943       ref = e->ref;
944       while (ref)
945         {
946           if (ref->type == REF_ARRAY
947               && ref->u.ar.codimen > 0)
948             break;
949
950           ref = ref->next;
951         }
952
953       gcc_assert (ref != NULL);
954       if (ref->u.ar.type == AR_ELEMENT)
955         ref->u.ar.type = AR_SECTION;
956       ss = gfc_reverse_ss (gfc_walk_array_ref (ss, e, ref));
957     }
958
959   return ss;
960 }
961
962
963 static void
964 trans_this_image (gfc_se * se, gfc_expr *expr)
965 {
966   stmtblock_t loop;
967   tree type, desc, dim_arg, cond, tmp, m, loop_var, exit_label, min_var,
968        lbound, ubound, extent, ml;
969   gfc_se argse;
970   gfc_ss *ss;
971   int rank, corank;
972
973   /* The case -fcoarray=single is handled elsewhere.  */
974   gcc_assert (gfc_option.coarray != GFC_FCOARRAY_SINGLE);
975
976   gfc_init_coarray_decl (false);
977
978   /* Argument-free version: THIS_IMAGE().  */
979   if (expr->value.function.actual->expr == NULL)
980     {
981       se->expr = gfort_gvar_caf_this_image;
982       return;
983     }
984
985   /* Coarray-argument version: THIS_IMAGE(coarray [, dim]).  */
986
987   type = gfc_get_int_type (gfc_default_integer_kind);
988   corank = gfc_get_corank (expr->value.function.actual->expr);
989   rank = expr->value.function.actual->expr->rank;
990
991   /* Obtain the descriptor of the COARRAY.  */
992   gfc_init_se (&argse, NULL);
993   ss = walk_coarray (expr->value.function.actual->expr);
994   gcc_assert (ss != gfc_ss_terminator);
995   argse.want_coarray = 1;
996   gfc_conv_expr_descriptor (&argse, expr->value.function.actual->expr, ss);
997   gfc_add_block_to_block (&se->pre, &argse.pre);
998   gfc_add_block_to_block (&se->post, &argse.post);
999   desc = argse.expr;
1000
1001   if (se->ss)
1002     {
1003       /* Create an implicit second parameter from the loop variable.  */
1004       gcc_assert (!expr->value.function.actual->next->expr);
1005       gcc_assert (corank > 0);
1006       gcc_assert (se->loop->dimen == 1);
1007       gcc_assert (se->ss->info->expr == expr);
1008
1009       dim_arg = se->loop->loopvar[0];
1010       dim_arg = fold_build2_loc (input_location, PLUS_EXPR,
1011                                  gfc_array_index_type, dim_arg,
1012                                  build_int_cst (TREE_TYPE (dim_arg), 1));
1013       gfc_advance_se_ss_chain (se);
1014     }
1015   else
1016     {
1017       /* Use the passed DIM= argument.  */
1018       gcc_assert (expr->value.function.actual->next->expr);
1019       gfc_init_se (&argse, NULL);
1020       gfc_conv_expr_type (&argse, expr->value.function.actual->next->expr,
1021                           gfc_array_index_type);
1022       gfc_add_block_to_block (&se->pre, &argse.pre);
1023       dim_arg = argse.expr;
1024
1025       if (INTEGER_CST_P (dim_arg))
1026         {
1027           int hi, co_dim;
1028
1029           hi = TREE_INT_CST_HIGH (dim_arg);
1030           co_dim = TREE_INT_CST_LOW (dim_arg);
1031           if (hi || co_dim < 1
1032               || co_dim > GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc)))
1033             gfc_error ("'dim' argument of %s intrinsic at %L is not a valid "
1034                        "dimension index", expr->value.function.isym->name,
1035                        &expr->where);
1036         }
1037      else if (gfc_option.rtcheck & GFC_RTCHECK_BOUNDS)
1038         {
1039           dim_arg = gfc_evaluate_now (dim_arg, &se->pre);
1040           cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1041                                   dim_arg,
1042                                   build_int_cst (TREE_TYPE (dim_arg), 1));
1043           tmp = gfc_rank_cst[GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc))];
1044           tmp = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
1045                                  dim_arg, tmp);
1046           cond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
1047                                   boolean_type_node, cond, tmp);
1048           gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
1049                                    gfc_msg_fault);
1050         }
1051     }
1052
1053   /* Used algorithm; cf. Fortran 2008, C.10. Note, due to the scalarizer,
1054      one always has a dim_arg argument.
1055
1056      m = this_images() - 1
1057      i = rank
1058      min_var = min (rank + corank - 2, rank + dim_arg - 1)
1059      for (;;)
1060        {
1061          extent = gfc_extent(i)
1062          ml = m
1063          m  = m/extent
1064          if (i >= min_var) 
1065            goto exit_label
1066          i++
1067        }
1068      exit_label:
1069      sub(dim_arg) = (dim_arg < corank) ? ml - m*extent + lcobound(dim_arg)
1070                                        : m + lcobound(corank)
1071   */
1072
1073   m = gfc_create_var (type, NULL); 
1074   ml = gfc_create_var (type, NULL); 
1075   loop_var = gfc_create_var (integer_type_node, NULL); 
1076   min_var = gfc_create_var (integer_type_node, NULL); 
1077
1078   /* m = this_image () - 1.  */
1079   tmp = fold_convert (type, gfort_gvar_caf_this_image);
1080   tmp = fold_build2_loc (input_location, MINUS_EXPR, type, tmp,
1081                        build_int_cst (type, 1));
1082   gfc_add_modify (&se->pre, m, tmp);
1083
1084   /* min_var = min (rank + corank-2, rank + dim_arg - 1).  */
1085   tmp = fold_build2_loc (input_location, PLUS_EXPR, integer_type_node,
1086                          fold_convert (integer_type_node, dim_arg),
1087                          build_int_cst (integer_type_node, rank - 1));
1088   tmp = fold_build2_loc (input_location, MIN_EXPR, integer_type_node,
1089                          build_int_cst (integer_type_node, rank + corank - 2),
1090                          tmp);
1091   gfc_add_modify (&se->pre, min_var, tmp);
1092
1093   /* i = rank.  */
1094   tmp = build_int_cst (integer_type_node, rank);
1095   gfc_add_modify (&se->pre, loop_var, tmp);
1096
1097   exit_label = gfc_build_label_decl (NULL_TREE);
1098   TREE_USED (exit_label) = 1;
1099
1100   /* Loop body.  */
1101   gfc_init_block (&loop);
1102
1103   /* ml = m.  */
1104   gfc_add_modify (&loop, ml, m);
1105
1106   /* extent = ...  */
1107   lbound = gfc_conv_descriptor_lbound_get (desc, loop_var);
1108   ubound = gfc_conv_descriptor_ubound_get (desc, loop_var);
1109   extent = gfc_conv_array_extent_dim (lbound, ubound, NULL);
1110   extent = fold_convert (type, extent);
1111
1112   /* m = m/extent.  */
1113   gfc_add_modify (&loop, m, 
1114                   fold_build2_loc (input_location, TRUNC_DIV_EXPR, type,
1115                           m, extent));
1116
1117   /* Exit condition:  if (i >= min_var) goto exit_label.  */
1118   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, loop_var,
1119                   min_var);
1120   tmp = build1_v (GOTO_EXPR, exit_label);
1121   tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond, tmp,
1122                          build_empty_stmt (input_location));
1123   gfc_add_expr_to_block (&loop, tmp);
1124
1125   /* Increment loop variable: i++.  */
1126   gfc_add_modify (&loop, loop_var,
1127                   fold_build2_loc (input_location, PLUS_EXPR, integer_type_node,
1128                                    loop_var,
1129                                    build_int_cst (integer_type_node, 1)));
1130
1131   /* Making the loop... actually loop!  */
1132   tmp = gfc_finish_block (&loop);
1133   tmp = build1_v (LOOP_EXPR, tmp);
1134   gfc_add_expr_to_block (&se->pre, tmp);
1135
1136   /* The exit label.  */
1137   tmp = build1_v (LABEL_EXPR, exit_label);
1138   gfc_add_expr_to_block (&se->pre, tmp);
1139
1140   /*  sub(co_dim) = (co_dim < corank) ? ml - m*extent + lcobound(dim_arg)
1141                                       : m + lcobound(corank) */
1142
1143   cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node, dim_arg,
1144                           build_int_cst (TREE_TYPE (dim_arg), corank));
1145
1146   lbound = gfc_conv_descriptor_lbound_get (desc,
1147                 fold_build2_loc (input_location, PLUS_EXPR,
1148                                  gfc_array_index_type, dim_arg,
1149                                  build_int_cst (TREE_TYPE (dim_arg), rank-1)));
1150   lbound = fold_convert (type, lbound);
1151
1152   tmp = fold_build2_loc (input_location, MINUS_EXPR, type, ml,
1153                          fold_build2_loc (input_location, MULT_EXPR, type,
1154                                           m, extent));
1155   tmp = fold_build2_loc (input_location, PLUS_EXPR, type, tmp, lbound);
1156
1157   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond, tmp,
1158                               fold_build2_loc (input_location, PLUS_EXPR, type,
1159                                                m, lbound));
1160 }
1161
1162
1163 static void
1164 trans_image_index (gfc_se * se, gfc_expr *expr)
1165 {
1166   tree num_images, cond, coindex, type, lbound, ubound, desc, subdesc,
1167        tmp, invalid_bound;
1168   gfc_se argse, subse;
1169   gfc_ss *ss, *subss;
1170   int rank, corank, codim;
1171
1172   type = gfc_get_int_type (gfc_default_integer_kind);
1173   corank = gfc_get_corank (expr->value.function.actual->expr);
1174   rank = expr->value.function.actual->expr->rank;
1175
1176   /* Obtain the descriptor of the COARRAY.  */
1177   gfc_init_se (&argse, NULL);
1178   ss = walk_coarray (expr->value.function.actual->expr);
1179   gcc_assert (ss != gfc_ss_terminator);
1180   argse.want_coarray = 1;
1181   gfc_conv_expr_descriptor (&argse, expr->value.function.actual->expr, ss);
1182   gfc_add_block_to_block (&se->pre, &argse.pre);
1183   gfc_add_block_to_block (&se->post, &argse.post);
1184   desc = argse.expr;
1185
1186   /* Obtain a handle to the SUB argument.  */
1187   gfc_init_se (&subse, NULL);
1188   subss = gfc_walk_expr (expr->value.function.actual->next->expr);
1189   gcc_assert (subss != gfc_ss_terminator);
1190   gfc_conv_expr_descriptor (&subse, expr->value.function.actual->next->expr,
1191                             subss);
1192   gfc_add_block_to_block (&se->pre, &subse.pre);
1193   gfc_add_block_to_block (&se->post, &subse.post);
1194   subdesc = build_fold_indirect_ref_loc (input_location,
1195                         gfc_conv_descriptor_data_get (subse.expr));
1196
1197   /* Fortran 2008 does not require that the values remain in the cobounds,
1198      thus we need explicitly check this - and return 0 if they are exceeded.  */
1199
1200   lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[rank+corank-1]);
1201   tmp = gfc_build_array_ref (subdesc, gfc_rank_cst[corank-1], NULL);
1202   invalid_bound = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1203                                  fold_convert (gfc_array_index_type, tmp),
1204                                  lbound);
1205
1206   for (codim = corank + rank - 2; codim >= rank; codim--)
1207     {
1208       lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[codim]);
1209       ubound = gfc_conv_descriptor_ubound_get (desc, gfc_rank_cst[codim]);
1210       tmp = gfc_build_array_ref (subdesc, gfc_rank_cst[codim-rank], NULL);
1211       cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1212                               fold_convert (gfc_array_index_type, tmp),
1213                               lbound);
1214       invalid_bound = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1215                                        boolean_type_node, invalid_bound, cond);
1216       cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
1217                               fold_convert (gfc_array_index_type, tmp),
1218                               ubound);
1219       invalid_bound = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1220                                        boolean_type_node, invalid_bound, cond);
1221     }
1222
1223   invalid_bound = gfc_unlikely (invalid_bound);
1224
1225
1226   /* See Fortran 2008, C.10 for the following algorithm.  */
1227
1228   /* coindex = sub(corank) - lcobound(n).  */
1229   coindex = fold_convert (gfc_array_index_type,
1230                           gfc_build_array_ref (subdesc, gfc_rank_cst[corank-1],
1231                                                NULL));
1232   lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[rank+corank-1]);
1233   coindex = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
1234                              fold_convert (gfc_array_index_type, coindex),
1235                              lbound);
1236
1237   for (codim = corank + rank - 2; codim >= rank; codim--)
1238     {
1239       tree extent, ubound;
1240
1241       /* coindex = coindex*extent(codim) + sub(codim) - lcobound(codim).  */
1242       lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[codim]);
1243       ubound = gfc_conv_descriptor_ubound_get (desc, gfc_rank_cst[codim]);
1244       extent = gfc_conv_array_extent_dim (lbound, ubound, NULL);
1245
1246       /* coindex *= extent.  */
1247       coindex = fold_build2_loc (input_location, MULT_EXPR,
1248                                  gfc_array_index_type, coindex, extent);
1249
1250       /* coindex += sub(codim).  */
1251       tmp = gfc_build_array_ref (subdesc, gfc_rank_cst[codim-rank], NULL);
1252       coindex = fold_build2_loc (input_location, PLUS_EXPR,
1253                                  gfc_array_index_type, coindex,
1254                                  fold_convert (gfc_array_index_type, tmp));
1255
1256       /* coindex -= lbound(codim).  */
1257       lbound = gfc_conv_descriptor_lbound_get (desc, gfc_rank_cst[codim]);
1258       coindex = fold_build2_loc (input_location, MINUS_EXPR,
1259                                  gfc_array_index_type, coindex, lbound);
1260     }
1261
1262   coindex = fold_build2_loc (input_location, PLUS_EXPR, type,
1263                              fold_convert(type, coindex),
1264                              build_int_cst (type, 1));
1265
1266   /* Return 0 if "coindex" exceeds num_images().  */
1267
1268   if (gfc_option.coarray == GFC_FCOARRAY_SINGLE)
1269     num_images = build_int_cst (type, 1);
1270   else
1271     {
1272       gfc_init_coarray_decl (false);
1273       num_images = gfort_gvar_caf_num_images;
1274     }
1275
1276   tmp = gfc_create_var (type, NULL);
1277   gfc_add_modify (&se->pre, tmp, coindex);
1278
1279   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node, tmp,
1280                           num_images);
1281   cond = fold_build2_loc (input_location, TRUTH_OR_EXPR, boolean_type_node,
1282                           cond,
1283                           fold_convert (boolean_type_node, invalid_bound));
1284   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
1285                               build_int_cst (type, 0), tmp);
1286 }
1287
1288
1289 static void
1290 trans_num_images (gfc_se * se)
1291 {
1292   gfc_init_coarray_decl (false);
1293   se->expr = gfort_gvar_caf_num_images;
1294 }
1295
1296
1297 /* Evaluate a single upper or lower bound.  */
1298 /* TODO: bound intrinsic generates way too much unnecessary code.  */
1299
1300 static void
1301 gfc_conv_intrinsic_bound (gfc_se * se, gfc_expr * expr, int upper)
1302 {
1303   gfc_actual_arglist *arg;
1304   gfc_actual_arglist *arg2;
1305   tree desc;
1306   tree type;
1307   tree bound;
1308   tree tmp;
1309   tree cond, cond1, cond3, cond4, size;
1310   tree ubound;
1311   tree lbound;
1312   gfc_se argse;
1313   gfc_ss *ss;
1314   gfc_array_spec * as;
1315
1316   arg = expr->value.function.actual;
1317   arg2 = arg->next;
1318
1319   if (se->ss)
1320     {
1321       /* Create an implicit second parameter from the loop variable.  */
1322       gcc_assert (!arg2->expr);
1323       gcc_assert (se->loop->dimen == 1);
1324       gcc_assert (se->ss->info->expr == expr);
1325       gfc_advance_se_ss_chain (se);
1326       bound = se->loop->loopvar[0];
1327       bound = fold_build2_loc (input_location, MINUS_EXPR,
1328                                gfc_array_index_type, bound,
1329                                se->loop->from[0]);
1330     }
1331   else
1332     {
1333       /* use the passed argument.  */
1334       gcc_assert (arg2->expr);
1335       gfc_init_se (&argse, NULL);
1336       gfc_conv_expr_type (&argse, arg2->expr, gfc_array_index_type);
1337       gfc_add_block_to_block (&se->pre, &argse.pre);
1338       bound = argse.expr;
1339       /* Convert from one based to zero based.  */
1340       bound = fold_build2_loc (input_location, MINUS_EXPR,
1341                                gfc_array_index_type, bound,
1342                                gfc_index_one_node);
1343     }
1344
1345   /* TODO: don't re-evaluate the descriptor on each iteration.  */
1346   /* Get a descriptor for the first parameter.  */
1347   ss = gfc_walk_expr (arg->expr);
1348   gcc_assert (ss != gfc_ss_terminator);
1349   gfc_init_se (&argse, NULL);
1350   gfc_conv_expr_descriptor (&argse, arg->expr, ss);
1351   gfc_add_block_to_block (&se->pre, &argse.pre);
1352   gfc_add_block_to_block (&se->post, &argse.post);
1353
1354   desc = argse.expr;
1355
1356   if (INTEGER_CST_P (bound))
1357     {
1358       int hi, low;
1359
1360       hi = TREE_INT_CST_HIGH (bound);
1361       low = TREE_INT_CST_LOW (bound);
1362       if (hi || low < 0 || low >= GFC_TYPE_ARRAY_RANK (TREE_TYPE (desc)))
1363         gfc_error ("'dim' argument of %s intrinsic at %L is not a valid "
1364                    "dimension index", upper ? "UBOUND" : "LBOUND",
1365                    &expr->where);
1366     }
1367   else
1368     {
1369       if (gfc_option.rtcheck & GFC_RTCHECK_BOUNDS)
1370         {
1371           bound = gfc_evaluate_now (bound, &se->pre);
1372           cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1373                                   bound, build_int_cst (TREE_TYPE (bound), 0));
1374           tmp = gfc_rank_cst[GFC_TYPE_ARRAY_RANK (TREE_TYPE (desc))];
1375           tmp = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
1376                                  bound, tmp);
1377           cond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
1378                                   boolean_type_node, cond, tmp);
1379           gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
1380                                    gfc_msg_fault);
1381         }
1382     }
1383
1384   ubound = gfc_conv_descriptor_ubound_get (desc, bound);
1385   lbound = gfc_conv_descriptor_lbound_get (desc, bound);
1386   
1387   as = gfc_get_full_arrayspec_from_expr (arg->expr);
1388
1389   /* 13.14.53: Result value for LBOUND
1390
1391      Case (i): For an array section or for an array expression other than a
1392                whole array or array structure component, LBOUND(ARRAY, DIM)
1393                has the value 1.  For a whole array or array structure
1394                component, LBOUND(ARRAY, DIM) has the value:
1395                  (a) equal to the lower bound for subscript DIM of ARRAY if
1396                      dimension DIM of ARRAY does not have extent zero
1397                      or if ARRAY is an assumed-size array of rank DIM,
1398               or (b) 1 otherwise.
1399
1400      13.14.113: Result value for UBOUND
1401
1402      Case (i): For an array section or for an array expression other than a
1403                whole array or array structure component, UBOUND(ARRAY, DIM)
1404                has the value equal to the number of elements in the given
1405                dimension; otherwise, it has a value equal to the upper bound
1406                for subscript DIM of ARRAY if dimension DIM of ARRAY does
1407                not have size zero and has value zero if dimension DIM has
1408                size zero.  */
1409
1410   if (as)
1411     {
1412       tree stride = gfc_conv_descriptor_stride_get (desc, bound);
1413
1414       cond1 = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
1415                                ubound, lbound);
1416       cond3 = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
1417                                stride, gfc_index_zero_node);
1418       cond3 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
1419                                boolean_type_node, cond3, cond1);
1420       cond4 = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1421                                stride, gfc_index_zero_node);
1422
1423       if (upper)
1424         {
1425           tree cond5;
1426           cond = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1427                                   boolean_type_node, cond3, cond4);
1428           cond5 = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
1429                                    gfc_index_one_node, lbound);
1430           cond5 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
1431                                    boolean_type_node, cond4, cond5);
1432
1433           cond = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1434                                   boolean_type_node, cond, cond5);
1435
1436           se->expr = fold_build3_loc (input_location, COND_EXPR,
1437                                       gfc_array_index_type, cond,
1438                                       ubound, gfc_index_zero_node);
1439         }
1440       else
1441         {
1442           if (as->type == AS_ASSUMED_SIZE)
1443             cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
1444                                     bound, build_int_cst (TREE_TYPE (bound),
1445                                                           arg->expr->rank - 1));
1446           else
1447             cond = boolean_false_node;
1448
1449           cond1 = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1450                                    boolean_type_node, cond3, cond4);
1451           cond = fold_build2_loc (input_location, TRUTH_OR_EXPR,
1452                                   boolean_type_node, cond, cond1);
1453
1454           se->expr = fold_build3_loc (input_location, COND_EXPR,
1455                                       gfc_array_index_type, cond,
1456                                       lbound, gfc_index_one_node);
1457         }
1458     }
1459   else
1460     {
1461       if (upper)
1462         {
1463           size = fold_build2_loc (input_location, MINUS_EXPR,
1464                                   gfc_array_index_type, ubound, lbound);
1465           se->expr = fold_build2_loc (input_location, PLUS_EXPR,
1466                                       gfc_array_index_type, size,
1467                                   gfc_index_one_node);
1468           se->expr = fold_build2_loc (input_location, MAX_EXPR,
1469                                       gfc_array_index_type, se->expr,
1470                                       gfc_index_zero_node);
1471         }
1472       else
1473         se->expr = gfc_index_one_node;
1474     }
1475
1476   type = gfc_typenode_for_spec (&expr->ts);
1477   se->expr = convert (type, se->expr);
1478 }
1479
1480
1481 static void
1482 conv_intrinsic_cobound (gfc_se * se, gfc_expr * expr)
1483 {
1484   gfc_actual_arglist *arg;
1485   gfc_actual_arglist *arg2;
1486   gfc_se argse;
1487   gfc_ss *ss;
1488   tree bound, resbound, resbound2, desc, cond, tmp;
1489   tree type;
1490   int corank;
1491
1492   gcc_assert (expr->value.function.isym->id == GFC_ISYM_LCOBOUND
1493               || expr->value.function.isym->id == GFC_ISYM_UCOBOUND
1494               || expr->value.function.isym->id == GFC_ISYM_THIS_IMAGE);
1495
1496   arg = expr->value.function.actual;
1497   arg2 = arg->next;
1498
1499   gcc_assert (arg->expr->expr_type == EXPR_VARIABLE);
1500   corank = gfc_get_corank (arg->expr);
1501
1502   ss = walk_coarray (arg->expr);
1503   gcc_assert (ss != gfc_ss_terminator);
1504   gfc_init_se (&argse, NULL);
1505   argse.want_coarray = 1;
1506
1507   gfc_conv_expr_descriptor (&argse, arg->expr, ss);
1508   gfc_add_block_to_block (&se->pre, &argse.pre);
1509   gfc_add_block_to_block (&se->post, &argse.post);
1510   desc = argse.expr;
1511
1512   if (se->ss)
1513     {
1514       /* Create an implicit second parameter from the loop variable.  */
1515       gcc_assert (!arg2->expr);
1516       gcc_assert (corank > 0);
1517       gcc_assert (se->loop->dimen == 1);
1518       gcc_assert (se->ss->info->expr == expr);
1519
1520       bound = se->loop->loopvar[0];
1521       bound = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
1522                                bound, gfc_rank_cst[arg->expr->rank]);
1523       gfc_advance_se_ss_chain (se);
1524     }
1525   else
1526     {
1527       /* use the passed argument.  */
1528       gcc_assert (arg2->expr);
1529       gfc_init_se (&argse, NULL);
1530       gfc_conv_expr_type (&argse, arg2->expr, gfc_array_index_type);
1531       gfc_add_block_to_block (&se->pre, &argse.pre);
1532       bound = argse.expr;
1533
1534       if (INTEGER_CST_P (bound))
1535         {
1536           int hi, low;
1537
1538           hi = TREE_INT_CST_HIGH (bound);
1539           low = TREE_INT_CST_LOW (bound);
1540           if (hi || low < 1 || low > GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc)))
1541             gfc_error ("'dim' argument of %s intrinsic at %L is not a valid "
1542                        "dimension index", expr->value.function.isym->name,
1543                        &expr->where);
1544         }
1545       else if (gfc_option.rtcheck & GFC_RTCHECK_BOUNDS)
1546         {
1547           bound = gfc_evaluate_now (bound, &se->pre);
1548           cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1549                                   bound, build_int_cst (TREE_TYPE (bound), 1));
1550           tmp = gfc_rank_cst[GFC_TYPE_ARRAY_CORANK (TREE_TYPE (desc))];
1551           tmp = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
1552                                  bound, tmp);
1553           cond = fold_build2_loc (input_location, TRUTH_ORIF_EXPR,
1554                                   boolean_type_node, cond, tmp);
1555           gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
1556                                    gfc_msg_fault);
1557         }
1558
1559
1560       /* Substract 1 to get to zero based and add dimensions.  */
1561       switch (arg->expr->rank)
1562         {
1563         case 0:
1564           bound = fold_build2_loc (input_location, MINUS_EXPR,
1565                                    gfc_array_index_type, bound,
1566                                    gfc_index_one_node);
1567         case 1:
1568           break;
1569         default:
1570           bound = fold_build2_loc (input_location, PLUS_EXPR,
1571                                    gfc_array_index_type, bound,
1572                                    gfc_rank_cst[arg->expr->rank - 1]);
1573         }
1574     }
1575
1576   resbound = gfc_conv_descriptor_lbound_get (desc, bound);
1577
1578   /* Handle UCOBOUND with special handling of the last codimension.  */
1579   if (expr->value.function.isym->id == GFC_ISYM_UCOBOUND)
1580     {
1581       /* Last codimension: For -fcoarray=single just return
1582          the lcobound - otherwise add
1583            ceiling (real (num_images ()) / real (size)) - 1
1584          = (num_images () + size - 1) / size - 1
1585          = (num_images - 1) / size(),
1586          where size is the product of the extent of all but the last
1587          codimension.  */
1588
1589       if (gfc_option.coarray != GFC_FCOARRAY_SINGLE && corank > 1)
1590         {
1591           tree cosize;
1592
1593           gfc_init_coarray_decl (false);
1594           cosize = gfc_conv_descriptor_cosize (desc, arg->expr->rank, corank);
1595
1596           tmp = fold_build2_loc (input_location, MINUS_EXPR,
1597                                  gfc_array_index_type,
1598                                  gfort_gvar_caf_num_images,
1599                                  build_int_cst (gfc_array_index_type, 1));
1600           tmp = fold_build2_loc (input_location, TRUNC_DIV_EXPR,
1601                                  gfc_array_index_type, tmp,
1602                                  fold_convert (gfc_array_index_type, cosize));
1603           resbound = fold_build2_loc (input_location, PLUS_EXPR,
1604                                       gfc_array_index_type, resbound, tmp);
1605         }
1606       else if (gfc_option.coarray != GFC_FCOARRAY_SINGLE)
1607         {
1608           /* ubound = lbound + num_images() - 1.  */
1609           gfc_init_coarray_decl (false);
1610           tmp = fold_build2_loc (input_location, MINUS_EXPR,
1611                                  gfc_array_index_type,
1612                                  gfort_gvar_caf_num_images,
1613                                  build_int_cst (gfc_array_index_type, 1));
1614           resbound = fold_build2_loc (input_location, PLUS_EXPR,
1615                                       gfc_array_index_type, resbound, tmp);
1616         }
1617
1618       if (corank > 1)
1619         {
1620           cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
1621                                   bound,
1622                                   build_int_cst (TREE_TYPE (bound),
1623                                                  arg->expr->rank + corank - 1));
1624
1625           resbound2 = gfc_conv_descriptor_ubound_get (desc, bound);
1626           se->expr = fold_build3_loc (input_location, COND_EXPR,
1627                                       gfc_array_index_type, cond,
1628                                       resbound, resbound2);
1629         }
1630       else
1631         se->expr = resbound;
1632     }
1633   else
1634     se->expr = resbound;
1635
1636   type = gfc_typenode_for_spec (&expr->ts);
1637   se->expr = convert (type, se->expr);
1638 }
1639
1640
1641 static void
1642 gfc_conv_intrinsic_abs (gfc_se * se, gfc_expr * expr)
1643 {
1644   tree arg, cabs;
1645
1646   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
1647
1648   switch (expr->value.function.actual->expr->ts.type)
1649     {
1650     case BT_INTEGER:
1651     case BT_REAL:
1652       se->expr = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (arg),
1653                                   arg);
1654       break;
1655
1656     case BT_COMPLEX:
1657       cabs = gfc_builtin_decl_for_float_kind (BUILT_IN_CABS, expr->ts.kind);
1658       se->expr = build_call_expr_loc (input_location, cabs, 1, arg);
1659       break;
1660
1661     default:
1662       gcc_unreachable ();
1663     }
1664 }
1665
1666
1667 /* Create a complex value from one or two real components.  */
1668
1669 static void
1670 gfc_conv_intrinsic_cmplx (gfc_se * se, gfc_expr * expr, int both)
1671 {
1672   tree real;
1673   tree imag;
1674   tree type;
1675   tree *args;
1676   unsigned int num_args;
1677
1678   num_args = gfc_intrinsic_argument_list_length (expr);
1679   args = XALLOCAVEC (tree, num_args);
1680
1681   type = gfc_typenode_for_spec (&expr->ts);
1682   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
1683   real = convert (TREE_TYPE (type), args[0]);
1684   if (both)
1685     imag = convert (TREE_TYPE (type), args[1]);
1686   else if (TREE_CODE (TREE_TYPE (args[0])) == COMPLEX_TYPE)
1687     {
1688       imag = fold_build1_loc (input_location, IMAGPART_EXPR,
1689                               TREE_TYPE (TREE_TYPE (args[0])), args[0]);
1690       imag = convert (TREE_TYPE (type), imag);
1691     }
1692   else
1693     imag = build_real_from_int_cst (TREE_TYPE (type), integer_zero_node);
1694
1695   se->expr = fold_build2_loc (input_location, COMPLEX_EXPR, type, real, imag);
1696 }
1697
1698 /* Remainder function MOD(A, P) = A - INT(A / P) * P
1699                       MODULO(A, P) = A - FLOOR (A / P) * P  */
1700 /* TODO: MOD(x, 0)  */
1701
1702 static void
1703 gfc_conv_intrinsic_mod (gfc_se * se, gfc_expr * expr, int modulo)
1704 {
1705   tree type;
1706   tree itype;
1707   tree tmp;
1708   tree test;
1709   tree test2;
1710   tree fmod;
1711   mpfr_t huge;
1712   int n, ikind;
1713   tree args[2];
1714
1715   gfc_conv_intrinsic_function_args (se, expr, args, 2);
1716
1717   switch (expr->ts.type)
1718     {
1719     case BT_INTEGER:
1720       /* Integer case is easy, we've got a builtin op.  */
1721       type = TREE_TYPE (args[0]);
1722
1723       if (modulo)
1724        se->expr = fold_build2_loc (input_location, FLOOR_MOD_EXPR, type,
1725                                    args[0], args[1]);
1726       else
1727        se->expr = fold_build2_loc (input_location, TRUNC_MOD_EXPR, type,
1728                                    args[0], args[1]);
1729       break;
1730
1731     case BT_REAL:
1732       fmod = NULL_TREE;
1733       /* Check if we have a builtin fmod.  */
1734       fmod = gfc_builtin_decl_for_float_kind (BUILT_IN_FMOD, expr->ts.kind);
1735
1736       /* Use it if it exists.  */
1737       if (fmod != NULL_TREE)
1738         {
1739           tmp = build_addr (fmod, current_function_decl);
1740           se->expr = build_call_array_loc (input_location,
1741                                        TREE_TYPE (TREE_TYPE (fmod)),
1742                                        tmp, 2, args);
1743           if (modulo == 0)
1744             return;
1745         }
1746
1747       type = TREE_TYPE (args[0]);
1748
1749       args[0] = gfc_evaluate_now (args[0], &se->pre);
1750       args[1] = gfc_evaluate_now (args[1], &se->pre);
1751
1752       /* Definition:
1753          modulo = arg - floor (arg/arg2) * arg2, so
1754                 = test ? fmod (arg, arg2) : fmod (arg, arg2) + arg2, 
1755          where
1756           test  = (fmod (arg, arg2) != 0) && ((arg < 0) xor (arg2 < 0))
1757          thereby avoiding another division and retaining the accuracy
1758          of the builtin function.  */
1759       if (fmod != NULL_TREE && modulo)
1760         {
1761           tree zero = gfc_build_const (type, integer_zero_node);
1762           tmp = gfc_evaluate_now (se->expr, &se->pre);
1763           test = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1764                                   args[0], zero);
1765           test2 = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1766                                    args[1], zero);
1767           test2 = fold_build2_loc (input_location, TRUTH_XOR_EXPR,
1768                                    boolean_type_node, test, test2);
1769           test = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
1770                                   tmp, zero);
1771           test = fold_build2_loc (input_location, TRUTH_AND_EXPR,
1772                                   boolean_type_node, test, test2);
1773           test = gfc_evaluate_now (test, &se->pre);
1774           se->expr = fold_build3_loc (input_location, COND_EXPR, type, test,
1775                                   fold_build2_loc (input_location, PLUS_EXPR,
1776                                                    type, tmp, args[1]), tmp);
1777           return;
1778         }
1779
1780       /* If we do not have a built_in fmod, the calculation is going to
1781          have to be done longhand.  */
1782       tmp = fold_build2_loc (input_location, RDIV_EXPR, type, args[0], args[1]);
1783
1784       /* Test if the value is too large to handle sensibly.  */
1785       gfc_set_model_kind (expr->ts.kind);
1786       mpfr_init (huge);
1787       n = gfc_validate_kind (BT_INTEGER, expr->ts.kind, true);
1788       ikind = expr->ts.kind;
1789       if (n < 0)
1790         {
1791           n = gfc_validate_kind (BT_INTEGER, gfc_max_integer_kind, false);
1792           ikind = gfc_max_integer_kind;
1793         }
1794       mpfr_set_z (huge, gfc_integer_kinds[n].huge, GFC_RND_MODE);
1795       test = gfc_conv_mpfr_to_tree (huge, expr->ts.kind, 0);
1796       test2 = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
1797                                tmp, test);
1798
1799       mpfr_neg (huge, huge, GFC_RND_MODE);
1800       test = gfc_conv_mpfr_to_tree (huge, expr->ts.kind, 0);
1801       test = fold_build2_loc (input_location, GT_EXPR, boolean_type_node, tmp,
1802                               test);
1803       test2 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
1804                                boolean_type_node, test, test2);
1805
1806       itype = gfc_get_int_type (ikind);
1807       if (modulo)
1808        tmp = build_fix_expr (&se->pre, tmp, itype, RND_FLOOR);
1809       else
1810        tmp = build_fix_expr (&se->pre, tmp, itype, RND_TRUNC);
1811       tmp = convert (type, tmp);
1812       tmp = fold_build3_loc (input_location, COND_EXPR, type, test2, tmp,
1813                              args[0]);
1814       tmp = fold_build2_loc (input_location, MULT_EXPR, type, tmp, args[1]);
1815       se->expr = fold_build2_loc (input_location, MINUS_EXPR, type, args[0],
1816                                   tmp);
1817       mpfr_clear (huge);
1818       break;
1819
1820     default:
1821       gcc_unreachable ();
1822     }
1823 }
1824
1825 /* DSHIFTL(I,J,S) = (I << S) | (J >> (BITSIZE(J) - S))
1826    DSHIFTR(I,J,S) = (I << (BITSIZE(I) - S)) | (J >> S)
1827    where the right shifts are logical (i.e. 0's are shifted in).
1828    Because SHIFT_EXPR's want shifts strictly smaller than the integral
1829    type width, we have to special-case both S == 0 and S == BITSIZE(J):
1830      DSHIFTL(I,J,0) = I
1831      DSHIFTL(I,J,BITSIZE) = J
1832      DSHIFTR(I,J,0) = J
1833      DSHIFTR(I,J,BITSIZE) = I.  */
1834
1835 static void
1836 gfc_conv_intrinsic_dshift (gfc_se * se, gfc_expr * expr, bool dshiftl)
1837 {
1838   tree type, utype, stype, arg1, arg2, shift, res, left, right;
1839   tree args[3], cond, tmp;
1840   int bitsize;
1841
1842   gfc_conv_intrinsic_function_args (se, expr, args, 3);
1843
1844   gcc_assert (TREE_TYPE (args[0]) == TREE_TYPE (args[1]));
1845   type = TREE_TYPE (args[0]);
1846   bitsize = TYPE_PRECISION (type);
1847   utype = unsigned_type_for (type);
1848   stype = TREE_TYPE (args[2]);
1849
1850   arg1 = gfc_evaluate_now (args[0], &se->pre);
1851   arg2 = gfc_evaluate_now (args[1], &se->pre);
1852   shift = gfc_evaluate_now (args[2], &se->pre);
1853
1854   /* The generic case.  */
1855   tmp = fold_build2_loc (input_location, MINUS_EXPR, stype,
1856                          build_int_cst (stype, bitsize), shift);
1857   left = fold_build2_loc (input_location, LSHIFT_EXPR, type,
1858                           arg1, dshiftl ? shift : tmp);
1859
1860   right = fold_build2_loc (input_location, RSHIFT_EXPR, utype,
1861                            fold_convert (utype, arg2), dshiftl ? tmp : shift);
1862   right = fold_convert (type, right);
1863
1864   res = fold_build2_loc (input_location, BIT_IOR_EXPR, type, left, right);
1865
1866   /* Special cases.  */
1867   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, shift,
1868                           build_int_cst (stype, 0));
1869   res = fold_build3_loc (input_location, COND_EXPR, type, cond,
1870                          dshiftl ? arg1 : arg2, res);
1871
1872   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, shift,
1873                           build_int_cst (stype, bitsize));
1874   res = fold_build3_loc (input_location, COND_EXPR, type, cond,
1875                          dshiftl ? arg2 : arg1, res);
1876
1877   se->expr = res;
1878 }
1879
1880
1881 /* Positive difference DIM (x, y) = ((x - y) < 0) ? 0 : x - y.  */
1882
1883 static void
1884 gfc_conv_intrinsic_dim (gfc_se * se, gfc_expr * expr)
1885 {
1886   tree val;
1887   tree tmp;
1888   tree type;
1889   tree zero;
1890   tree args[2];
1891
1892   gfc_conv_intrinsic_function_args (se, expr, args, 2);
1893   type = TREE_TYPE (args[0]);
1894
1895   val = fold_build2_loc (input_location, MINUS_EXPR, type, args[0], args[1]);
1896   val = gfc_evaluate_now (val, &se->pre);
1897
1898   zero = gfc_build_const (type, integer_zero_node);
1899   tmp = fold_build2_loc (input_location, LE_EXPR, boolean_type_node, val, zero);
1900   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, zero, val);
1901 }
1902
1903
1904 /* SIGN(A, B) is absolute value of A times sign of B.
1905    The real value versions use library functions to ensure the correct
1906    handling of negative zero.  Integer case implemented as:
1907    SIGN(A, B) = { tmp = (A ^ B) >> C; (A + tmp) ^ tmp }
1908   */
1909
1910 static void
1911 gfc_conv_intrinsic_sign (gfc_se * se, gfc_expr * expr)
1912 {
1913   tree tmp;
1914   tree type;
1915   tree args[2];
1916
1917   gfc_conv_intrinsic_function_args (se, expr, args, 2);
1918   if (expr->ts.type == BT_REAL)
1919     {
1920       tree abs;
1921
1922       tmp = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
1923       abs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
1924
1925       /* We explicitly have to ignore the minus sign. We do so by using
1926          result = (arg1 == 0) ? abs(arg0) : copysign(arg0, arg1).  */
1927       if (!gfc_option.flag_sign_zero
1928           && MODE_HAS_SIGNED_ZEROS (TYPE_MODE (TREE_TYPE (args[1]))))
1929         {
1930           tree cond, zero;
1931           zero = build_real_from_int_cst (TREE_TYPE (args[1]), integer_zero_node);
1932           cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
1933                                   args[1], zero);
1934           se->expr = fold_build3_loc (input_location, COND_EXPR,
1935                                   TREE_TYPE (args[0]), cond,
1936                                   build_call_expr_loc (input_location, abs, 1,
1937                                                        args[0]),
1938                                   build_call_expr_loc (input_location, tmp, 2,
1939                                                        args[0], args[1]));
1940         }
1941       else
1942         se->expr = build_call_expr_loc (input_location, tmp, 2,
1943                                         args[0], args[1]);
1944       return;
1945     }
1946
1947   /* Having excluded floating point types, we know we are now dealing
1948      with signed integer types.  */
1949   type = TREE_TYPE (args[0]);
1950
1951   /* Args[0] is used multiple times below.  */
1952   args[0] = gfc_evaluate_now (args[0], &se->pre);
1953
1954   /* Construct (A ^ B) >> 31, which generates a bit mask of all zeros if
1955      the signs of A and B are the same, and of all ones if they differ.  */
1956   tmp = fold_build2_loc (input_location, BIT_XOR_EXPR, type, args[0], args[1]);
1957   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, tmp,
1958                          build_int_cst (type, TYPE_PRECISION (type) - 1));
1959   tmp = gfc_evaluate_now (tmp, &se->pre);
1960
1961   /* Construct (A + tmp) ^ tmp, which is A if tmp is zero, and -A if tmp]
1962      is all ones (i.e. -1).  */
1963   se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR, type,
1964                               fold_build2_loc (input_location, PLUS_EXPR,
1965                                                type, args[0], tmp), tmp);
1966 }
1967
1968
1969 /* Test for the presence of an optional argument.  */
1970
1971 static void
1972 gfc_conv_intrinsic_present (gfc_se * se, gfc_expr * expr)
1973 {
1974   gfc_expr *arg;
1975
1976   arg = expr->value.function.actual->expr;
1977   gcc_assert (arg->expr_type == EXPR_VARIABLE);
1978   se->expr = gfc_conv_expr_present (arg->symtree->n.sym);
1979   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
1980 }
1981
1982
1983 /* Calculate the double precision product of two single precision values.  */
1984
1985 static void
1986 gfc_conv_intrinsic_dprod (gfc_se * se, gfc_expr * expr)
1987 {
1988   tree type;
1989   tree args[2];
1990
1991   gfc_conv_intrinsic_function_args (se, expr, args, 2);
1992
1993   /* Convert the args to double precision before multiplying.  */
1994   type = gfc_typenode_for_spec (&expr->ts);
1995   args[0] = convert (type, args[0]);
1996   args[1] = convert (type, args[1]);
1997   se->expr = fold_build2_loc (input_location, MULT_EXPR, type, args[0],
1998                               args[1]);
1999 }
2000
2001
2002 /* Return a length one character string containing an ascii character.  */
2003
2004 static void
2005 gfc_conv_intrinsic_char (gfc_se * se, gfc_expr * expr)
2006 {
2007   tree arg[2];
2008   tree var;
2009   tree type;
2010   unsigned int num_args;
2011
2012   num_args = gfc_intrinsic_argument_list_length (expr);
2013   gfc_conv_intrinsic_function_args (se, expr, arg, num_args);
2014
2015   type = gfc_get_char_type (expr->ts.kind);
2016   var = gfc_create_var (type, "char");
2017
2018   arg[0] = fold_build1_loc (input_location, NOP_EXPR, type, arg[0]);
2019   gfc_add_modify (&se->pre, var, arg[0]);
2020   se->expr = gfc_build_addr_expr (build_pointer_type (type), var);
2021   se->string_length = build_int_cst (gfc_charlen_type_node, 1);
2022 }
2023
2024
2025 static void
2026 gfc_conv_intrinsic_ctime (gfc_se * se, gfc_expr * expr)
2027 {
2028   tree var;
2029   tree len;
2030   tree tmp;
2031   tree cond;
2032   tree fndecl;
2033   tree *args;
2034   unsigned int num_args;
2035
2036   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
2037   args = XALLOCAVEC (tree, num_args);
2038
2039   var = gfc_create_var (pchar_type_node, "pstr");
2040   len = gfc_create_var (gfc_charlen_type_node, "len");
2041
2042   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
2043   args[0] = gfc_build_addr_expr (NULL_TREE, var);
2044   args[1] = gfc_build_addr_expr (NULL_TREE, len);
2045
2046   fndecl = build_addr (gfor_fndecl_ctime, current_function_decl);
2047   tmp = build_call_array_loc (input_location,
2048                           TREE_TYPE (TREE_TYPE (gfor_fndecl_ctime)),
2049                           fndecl, num_args, args);
2050   gfc_add_expr_to_block (&se->pre, tmp);
2051
2052   /* Free the temporary afterwards, if necessary.  */
2053   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
2054                           len, build_int_cst (TREE_TYPE (len), 0));
2055   tmp = gfc_call_free (var);
2056   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
2057   gfc_add_expr_to_block (&se->post, tmp);
2058
2059   se->expr = var;
2060   se->string_length = len;
2061 }
2062
2063
2064 static void
2065 gfc_conv_intrinsic_fdate (gfc_se * se, gfc_expr * expr)
2066 {
2067   tree var;
2068   tree len;
2069   tree tmp;
2070   tree cond;
2071   tree fndecl;
2072   tree *args;
2073   unsigned int num_args;
2074
2075   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
2076   args = XALLOCAVEC (tree, num_args);
2077
2078   var = gfc_create_var (pchar_type_node, "pstr");
2079   len = gfc_create_var (gfc_charlen_type_node, "len");
2080
2081   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
2082   args[0] = gfc_build_addr_expr (NULL_TREE, var);
2083   args[1] = gfc_build_addr_expr (NULL_TREE, len);
2084
2085   fndecl = build_addr (gfor_fndecl_fdate, current_function_decl);
2086   tmp = build_call_array_loc (input_location,
2087                           TREE_TYPE (TREE_TYPE (gfor_fndecl_fdate)),
2088                           fndecl, num_args, args);
2089   gfc_add_expr_to_block (&se->pre, tmp);
2090
2091   /* Free the temporary afterwards, if necessary.  */
2092   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
2093                           len, build_int_cst (TREE_TYPE (len), 0));
2094   tmp = gfc_call_free (var);
2095   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
2096   gfc_add_expr_to_block (&se->post, tmp);
2097
2098   se->expr = var;
2099   se->string_length = len;
2100 }
2101
2102
2103 /* Return a character string containing the tty name.  */
2104
2105 static void
2106 gfc_conv_intrinsic_ttynam (gfc_se * se, gfc_expr * expr)
2107 {
2108   tree var;
2109   tree len;
2110   tree tmp;
2111   tree cond;
2112   tree fndecl;
2113   tree *args;
2114   unsigned int num_args;
2115
2116   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
2117   args = XALLOCAVEC (tree, num_args);
2118
2119   var = gfc_create_var (pchar_type_node, "pstr");
2120   len = gfc_create_var (gfc_charlen_type_node, "len");
2121
2122   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
2123   args[0] = gfc_build_addr_expr (NULL_TREE, var);
2124   args[1] = gfc_build_addr_expr (NULL_TREE, len);
2125
2126   fndecl = build_addr (gfor_fndecl_ttynam, current_function_decl);
2127   tmp = build_call_array_loc (input_location,
2128                           TREE_TYPE (TREE_TYPE (gfor_fndecl_ttynam)),
2129                           fndecl, num_args, args);
2130   gfc_add_expr_to_block (&se->pre, tmp);
2131
2132   /* Free the temporary afterwards, if necessary.  */
2133   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
2134                           len, build_int_cst (TREE_TYPE (len), 0));
2135   tmp = gfc_call_free (var);
2136   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
2137   gfc_add_expr_to_block (&se->post, tmp);
2138
2139   se->expr = var;
2140   se->string_length = len;
2141 }
2142
2143
2144 /* Get the minimum/maximum value of all the parameters.
2145     minmax (a1, a2, a3, ...)
2146     {
2147       mvar = a1;
2148       if (a2 .op. mvar || isnan(mvar))
2149         mvar = a2;
2150       if (a3 .op. mvar || isnan(mvar))
2151         mvar = a3;
2152       ...
2153       return mvar
2154     }
2155  */
2156
2157 /* TODO: Mismatching types can occur when specific names are used.
2158    These should be handled during resolution.  */
2159 static void
2160 gfc_conv_intrinsic_minmax (gfc_se * se, gfc_expr * expr, enum tree_code op)
2161 {
2162   tree tmp;
2163   tree mvar;
2164   tree val;
2165   tree thencase;
2166   tree *args;
2167   tree type;
2168   gfc_actual_arglist *argexpr;
2169   unsigned int i, nargs;
2170
2171   nargs = gfc_intrinsic_argument_list_length (expr);
2172   args = XALLOCAVEC (tree, nargs);
2173
2174   gfc_conv_intrinsic_function_args (se, expr, args, nargs);
2175   type = gfc_typenode_for_spec (&expr->ts);
2176
2177   argexpr = expr->value.function.actual;
2178   if (TREE_TYPE (args[0]) != type)
2179     args[0] = convert (type, args[0]);
2180   /* Only evaluate the argument once.  */
2181   if (TREE_CODE (args[0]) != VAR_DECL && !TREE_CONSTANT (args[0]))
2182     args[0] = gfc_evaluate_now (args[0], &se->pre);
2183
2184   mvar = gfc_create_var (type, "M");
2185   gfc_add_modify (&se->pre, mvar, args[0]);
2186   for (i = 1, argexpr = argexpr->next; i < nargs; i++)
2187     {
2188       tree cond, isnan;
2189
2190       val = args[i]; 
2191
2192       /* Handle absent optional arguments by ignoring the comparison.  */
2193       if (argexpr->expr->expr_type == EXPR_VARIABLE
2194           && argexpr->expr->symtree->n.sym->attr.optional
2195           && TREE_CODE (val) == INDIRECT_REF)
2196         cond = fold_build2_loc (input_location,
2197                                 NE_EXPR, boolean_type_node,
2198                                 TREE_OPERAND (val, 0), 
2199                         build_int_cst (TREE_TYPE (TREE_OPERAND (val, 0)), 0));
2200       else
2201       {
2202         cond = NULL_TREE;
2203
2204         /* Only evaluate the argument once.  */
2205         if (TREE_CODE (val) != VAR_DECL && !TREE_CONSTANT (val))
2206           val = gfc_evaluate_now (val, &se->pre);
2207       }
2208
2209       thencase = build2_v (MODIFY_EXPR, mvar, convert (type, val));
2210
2211       tmp = fold_build2_loc (input_location, op, boolean_type_node,
2212                              convert (type, val), mvar);
2213
2214       /* FIXME: When the IEEE_ARITHMETIC module is implemented, the call to
2215          __builtin_isnan might be made dependent on that module being loaded,
2216          to help performance of programs that don't rely on IEEE semantics.  */
2217       if (FLOAT_TYPE_P (TREE_TYPE (mvar)))
2218         {
2219           isnan = build_call_expr_loc (input_location,
2220                                        builtin_decl_explicit (BUILT_IN_ISNAN),
2221                                        1, mvar);
2222           tmp = fold_build2_loc (input_location, TRUTH_OR_EXPR,
2223                                  boolean_type_node, tmp,
2224                                  fold_convert (boolean_type_node, isnan));
2225         }
2226       tmp = build3_v (COND_EXPR, tmp, thencase,
2227                       build_empty_stmt (input_location));
2228
2229       if (cond != NULL_TREE)
2230         tmp = build3_v (COND_EXPR, cond, tmp,
2231                         build_empty_stmt (input_location));
2232
2233       gfc_add_expr_to_block (&se->pre, tmp);
2234       argexpr = argexpr->next;
2235     }
2236   se->expr = mvar;
2237 }
2238
2239
2240 /* Generate library calls for MIN and MAX intrinsics for character
2241    variables.  */
2242 static void
2243 gfc_conv_intrinsic_minmax_char (gfc_se * se, gfc_expr * expr, int op)
2244 {
2245   tree *args;
2246   tree var, len, fndecl, tmp, cond, function;
2247   unsigned int nargs;
2248
2249   nargs = gfc_intrinsic_argument_list_length (expr);
2250   args = XALLOCAVEC (tree, nargs + 4);
2251   gfc_conv_intrinsic_function_args (se, expr, &args[4], nargs);
2252
2253   /* Create the result variables.  */
2254   len = gfc_create_var (gfc_charlen_type_node, "len");
2255   args[0] = gfc_build_addr_expr (NULL_TREE, len);
2256   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
2257   args[1] = gfc_build_addr_expr (ppvoid_type_node, var);
2258   args[2] = build_int_cst (integer_type_node, op);
2259   args[3] = build_int_cst (integer_type_node, nargs / 2);
2260
2261   if (expr->ts.kind == 1)
2262     function = gfor_fndecl_string_minmax;
2263   else if (expr->ts.kind == 4)
2264     function = gfor_fndecl_string_minmax_char4;
2265   else
2266     gcc_unreachable ();
2267
2268   /* Make the function call.  */
2269   fndecl = build_addr (function, current_function_decl);
2270   tmp = build_call_array_loc (input_location,
2271                           TREE_TYPE (TREE_TYPE (function)), fndecl,
2272                           nargs + 4, args);
2273   gfc_add_expr_to_block (&se->pre, tmp);
2274
2275   /* Free the temporary afterwards, if necessary.  */
2276   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
2277                           len, build_int_cst (TREE_TYPE (len), 0));
2278   tmp = gfc_call_free (var);
2279   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
2280   gfc_add_expr_to_block (&se->post, tmp);
2281
2282   se->expr = var;
2283   se->string_length = len;
2284 }
2285
2286
2287 /* Create a symbol node for this intrinsic.  The symbol from the frontend
2288    has the generic name.  */
2289
2290 static gfc_symbol *
2291 gfc_get_symbol_for_expr (gfc_expr * expr)
2292 {
2293   gfc_symbol *sym;
2294
2295   /* TODO: Add symbols for intrinsic function to the global namespace.  */
2296   gcc_assert (strlen (expr->value.function.name) <= GFC_MAX_SYMBOL_LEN - 5);
2297   sym = gfc_new_symbol (expr->value.function.name, NULL);
2298
2299   sym->ts = expr->ts;
2300   sym->attr.external = 1;
2301   sym->attr.function = 1;
2302   sym->attr.always_explicit = 1;
2303   sym->attr.proc = PROC_INTRINSIC;
2304   sym->attr.flavor = FL_PROCEDURE;
2305   sym->result = sym;
2306   if (expr->rank > 0)
2307     {
2308       sym->attr.dimension = 1;
2309       sym->as = gfc_get_array_spec ();
2310       sym->as->type = AS_ASSUMED_SHAPE;
2311       sym->as->rank = expr->rank;
2312     }
2313
2314   gfc_copy_formal_args_intr (sym, expr->value.function.isym);
2315
2316   return sym;
2317 }
2318
2319 /* Generate a call to an external intrinsic function.  */
2320 static void
2321 gfc_conv_intrinsic_funcall (gfc_se * se, gfc_expr * expr)
2322 {
2323   gfc_symbol *sym;
2324   VEC(tree,gc) *append_args;
2325
2326   gcc_assert (!se->ss || se->ss->info->expr == expr);
2327
2328   if (se->ss)
2329     gcc_assert (expr->rank > 0);
2330   else
2331     gcc_assert (expr->rank == 0);
2332
2333   sym = gfc_get_symbol_for_expr (expr);
2334
2335   /* Calls to libgfortran_matmul need to be appended special arguments,
2336      to be able to call the BLAS ?gemm functions if required and possible.  */
2337   append_args = NULL;
2338   if (expr->value.function.isym->id == GFC_ISYM_MATMUL
2339       && sym->ts.type != BT_LOGICAL)
2340     {
2341       tree cint = gfc_get_int_type (gfc_c_int_kind);
2342
2343       if (gfc_option.flag_external_blas
2344           && (sym->ts.type == BT_REAL || sym->ts.type == BT_COMPLEX)
2345           && (sym->ts.kind == gfc_default_real_kind
2346               || sym->ts.kind == gfc_default_double_kind))
2347         {
2348           tree gemm_fndecl;
2349
2350           if (sym->ts.type == BT_REAL)
2351             {
2352               if (sym->ts.kind == gfc_default_real_kind)
2353                 gemm_fndecl = gfor_fndecl_sgemm;
2354               else
2355                 gemm_fndecl = gfor_fndecl_dgemm;
2356             }
2357           else
2358             {
2359               if (sym->ts.kind == gfc_default_real_kind)
2360                 gemm_fndecl = gfor_fndecl_cgemm;
2361               else
2362                 gemm_fndecl = gfor_fndecl_zgemm;
2363             }
2364
2365           append_args = VEC_alloc (tree, gc, 3);
2366           VEC_quick_push (tree, append_args, build_int_cst (cint, 1));
2367           VEC_quick_push (tree, append_args,
2368                           build_int_cst (cint, gfc_option.blas_matmul_limit));
2369           VEC_quick_push (tree, append_args,
2370                           gfc_build_addr_expr (NULL_TREE, gemm_fndecl));
2371         }
2372       else
2373         {
2374           append_args = VEC_alloc (tree, gc, 3);
2375           VEC_quick_push (tree, append_args, build_int_cst (cint, 0));
2376           VEC_quick_push (tree, append_args, build_int_cst (cint, 0));
2377           VEC_quick_push (tree, append_args, null_pointer_node);
2378         }
2379     }
2380
2381   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
2382                           append_args);
2383   gfc_free_symbol (sym);
2384 }
2385
2386 /* ANY and ALL intrinsics. ANY->op == NE_EXPR, ALL->op == EQ_EXPR.
2387    Implemented as
2388     any(a)
2389     {
2390       forall (i=...)
2391         if (a[i] != 0)
2392           return 1
2393       end forall
2394       return 0
2395     }
2396     all(a)
2397     {
2398       forall (i=...)
2399         if (a[i] == 0)
2400           return 0
2401       end forall
2402       return 1
2403     }
2404  */
2405 static void
2406 gfc_conv_intrinsic_anyall (gfc_se * se, gfc_expr * expr, enum tree_code op)
2407 {
2408   tree resvar;
2409   stmtblock_t block;
2410   stmtblock_t body;
2411   tree type;
2412   tree tmp;
2413   tree found;
2414   gfc_loopinfo loop;
2415   gfc_actual_arglist *actual;
2416   gfc_ss *arrayss;
2417   gfc_se arrayse;
2418   tree exit_label;
2419
2420   if (se->ss)
2421     {
2422       gfc_conv_intrinsic_funcall (se, expr);
2423       return;
2424     }
2425
2426   actual = expr->value.function.actual;
2427   type = gfc_typenode_for_spec (&expr->ts);
2428   /* Initialize the result.  */
2429   resvar = gfc_create_var (type, "test");
2430   if (op == EQ_EXPR)
2431     tmp = convert (type, boolean_true_node);
2432   else
2433     tmp = convert (type, boolean_false_node);
2434   gfc_add_modify (&se->pre, resvar, tmp);
2435
2436   /* Walk the arguments.  */
2437   arrayss = gfc_walk_expr (actual->expr);
2438   gcc_assert (arrayss != gfc_ss_terminator);
2439
2440   /* Initialize the scalarizer.  */
2441   gfc_init_loopinfo (&loop);
2442   exit_label = gfc_build_label_decl (NULL_TREE);
2443   TREE_USED (exit_label) = 1;
2444   gfc_add_ss_to_loop (&loop, arrayss);
2445
2446   /* Initialize the loop.  */
2447   gfc_conv_ss_startstride (&loop);
2448   gfc_conv_loop_setup (&loop, &expr->where);
2449
2450   gfc_mark_ss_chain_used (arrayss, 1);
2451   /* Generate the loop body.  */
2452   gfc_start_scalarized_body (&loop, &body);
2453
2454   /* If the condition matches then set the return value.  */
2455   gfc_start_block (&block);
2456   if (op == EQ_EXPR)
2457     tmp = convert (type, boolean_false_node);
2458   else
2459     tmp = convert (type, boolean_true_node);
2460   gfc_add_modify (&block, resvar, tmp);
2461
2462   /* And break out of the loop.  */
2463   tmp = build1_v (GOTO_EXPR, exit_label);
2464   gfc_add_expr_to_block (&block, tmp);
2465
2466   found = gfc_finish_block (&block);
2467
2468   /* Check this element.  */
2469   gfc_init_se (&arrayse, NULL);
2470   gfc_copy_loopinfo_to_se (&arrayse, &loop);
2471   arrayse.ss = arrayss;
2472   gfc_conv_expr_val (&arrayse, actual->expr);
2473
2474   gfc_add_block_to_block (&body, &arrayse.pre);
2475   tmp = fold_build2_loc (input_location, op, boolean_type_node, arrayse.expr,
2476                          build_int_cst (TREE_TYPE (arrayse.expr), 0));
2477   tmp = build3_v (COND_EXPR, tmp, found, build_empty_stmt (input_location));
2478   gfc_add_expr_to_block (&body, tmp);
2479   gfc_add_block_to_block (&body, &arrayse.post);
2480
2481   gfc_trans_scalarizing_loops (&loop, &body);
2482
2483   /* Add the exit label.  */
2484   tmp = build1_v (LABEL_EXPR, exit_label);
2485   gfc_add_expr_to_block (&loop.pre, tmp);
2486
2487   gfc_add_block_to_block (&se->pre, &loop.pre);
2488   gfc_add_block_to_block (&se->pre, &loop.post);
2489   gfc_cleanup_loop (&loop);
2490
2491   se->expr = resvar;
2492 }
2493
2494 /* COUNT(A) = Number of true elements in A.  */
2495 static void
2496 gfc_conv_intrinsic_count (gfc_se * se, gfc_expr * expr)
2497 {
2498   tree resvar;
2499   tree type;
2500   stmtblock_t body;
2501   tree tmp;
2502   gfc_loopinfo loop;
2503   gfc_actual_arglist *actual;
2504   gfc_ss *arrayss;
2505   gfc_se arrayse;
2506
2507   if (se->ss)
2508     {
2509       gfc_conv_intrinsic_funcall (se, expr);
2510       return;
2511     }
2512
2513   actual = expr->value.function.actual;
2514
2515   type = gfc_typenode_for_spec (&expr->ts);
2516   /* Initialize the result.  */
2517   resvar = gfc_create_var (type, "count");
2518   gfc_add_modify (&se->pre, resvar, build_int_cst (type, 0));
2519
2520   /* Walk the arguments.  */
2521   arrayss = gfc_walk_expr (actual->expr);
2522   gcc_assert (arrayss != gfc_ss_terminator);
2523
2524   /* Initialize the scalarizer.  */
2525   gfc_init_loopinfo (&loop);
2526   gfc_add_ss_to_loop (&loop, arrayss);
2527
2528   /* Initialize the loop.  */
2529   gfc_conv_ss_startstride (&loop);
2530   gfc_conv_loop_setup (&loop, &expr->where);
2531
2532   gfc_mark_ss_chain_used (arrayss, 1);
2533   /* Generate the loop body.  */
2534   gfc_start_scalarized_body (&loop, &body);
2535
2536   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (resvar),
2537                          resvar, build_int_cst (TREE_TYPE (resvar), 1));
2538   tmp = build2_v (MODIFY_EXPR, resvar, tmp);
2539
2540   gfc_init_se (&arrayse, NULL);
2541   gfc_copy_loopinfo_to_se (&arrayse, &loop);
2542   arrayse.ss = arrayss;
2543   gfc_conv_expr_val (&arrayse, actual->expr);
2544   tmp = build3_v (COND_EXPR, arrayse.expr, tmp,
2545                   build_empty_stmt (input_location));
2546
2547   gfc_add_block_to_block (&body, &arrayse.pre);
2548   gfc_add_expr_to_block (&body, tmp);
2549   gfc_add_block_to_block (&body, &arrayse.post);
2550
2551   gfc_trans_scalarizing_loops (&loop, &body);
2552
2553   gfc_add_block_to_block (&se->pre, &loop.pre);
2554   gfc_add_block_to_block (&se->pre, &loop.post);
2555   gfc_cleanup_loop (&loop);
2556
2557   se->expr = resvar;
2558 }
2559
2560
2561 /* Update given gfc_se to have ss component pointing to the nested gfc_ss
2562    struct and return the corresponding loopinfo.  */
2563
2564 static gfc_loopinfo *
2565 enter_nested_loop (gfc_se *se)
2566 {
2567   se->ss = se->ss->nested_ss;
2568   gcc_assert (se->ss == se->ss->loop->ss);
2569
2570   return se->ss->loop;
2571 }
2572
2573
2574 /* Inline implementation of the sum and product intrinsics.  */
2575 static void
2576 gfc_conv_intrinsic_arith (gfc_se * se, gfc_expr * expr, enum tree_code op,
2577                           bool norm2)
2578 {
2579   tree resvar;
2580   tree scale = NULL_TREE;
2581   tree type;
2582   stmtblock_t body;
2583   stmtblock_t block;
2584   tree tmp;
2585   gfc_loopinfo loop, *ploop;
2586   gfc_actual_arglist *arg_array, *arg_mask;
2587   gfc_ss *arrayss = NULL;
2588   gfc_ss *maskss = NULL;
2589   gfc_se arrayse;
2590   gfc_se maskse;
2591   gfc_se *parent_se;
2592   gfc_expr *arrayexpr;
2593   gfc_expr *maskexpr;
2594
2595   if (expr->rank > 0)
2596     {
2597       gcc_assert (gfc_inline_intrinsic_function_p (expr));
2598       parent_se = se;
2599     }
2600   else
2601     parent_se = NULL;
2602
2603   type = gfc_typenode_for_spec (&expr->ts);
2604   /* Initialize the result.  */
2605   resvar = gfc_create_var (type, "val");
2606   if (norm2)
2607     {
2608       /* result = 0.0;
2609          scale = 1.0.  */
2610       scale = gfc_create_var (type, "scale");
2611       gfc_add_modify (&se->pre, scale,
2612                       gfc_build_const (type, integer_one_node));
2613       tmp = gfc_build_const (type, integer_zero_node);
2614     }
2615   else if (op == PLUS_EXPR || op == BIT_IOR_EXPR || op == BIT_XOR_EXPR)
2616     tmp = gfc_build_const (type, integer_zero_node);
2617   else if (op == NE_EXPR)
2618     /* PARITY.  */
2619     tmp = convert (type, boolean_false_node);
2620   else if (op == BIT_AND_EXPR)
2621     tmp = gfc_build_const (type, fold_build1_loc (input_location, NEGATE_EXPR,
2622                                                   type, integer_one_node));
2623   else
2624     tmp = gfc_build_const (type, integer_one_node);
2625
2626   gfc_add_modify (&se->pre, resvar, tmp);
2627
2628   arg_array = expr->value.function.actual;
2629
2630   arrayexpr = arg_array->expr;
2631
2632   if (op == NE_EXPR || norm2)
2633     /* PARITY and NORM2.  */
2634     maskexpr = NULL;
2635   else
2636     {
2637       arg_mask  = arg_array->next->next;
2638       gcc_assert (arg_mask != NULL);
2639       maskexpr = arg_mask->expr;
2640     }
2641
2642   if (expr->rank == 0)
2643     {
2644       /* Walk the arguments.  */
2645       arrayss = gfc_walk_expr (arrayexpr);
2646       gcc_assert (arrayss != gfc_ss_terminator);
2647
2648       if (maskexpr && maskexpr->rank > 0)
2649         {
2650           maskss = gfc_walk_expr (maskexpr);
2651           gcc_assert (maskss != gfc_ss_terminator);
2652         }
2653       else
2654         maskss = NULL;
2655
2656       /* Initialize the scalarizer.  */
2657       gfc_init_loopinfo (&loop);
2658       gfc_add_ss_to_loop (&loop, arrayss);
2659       if (maskexpr && maskexpr->rank > 0)
2660         gfc_add_ss_to_loop (&loop, maskss);
2661
2662       /* Initialize the loop.  */
2663       gfc_conv_ss_startstride (&loop);
2664       gfc_conv_loop_setup (&loop, &expr->where);
2665
2666       gfc_mark_ss_chain_used (arrayss, 1);
2667       if (maskexpr && maskexpr->rank > 0)
2668         gfc_mark_ss_chain_used (maskss, 1);
2669
2670       ploop = &loop;
2671     }
2672   else
2673     /* All the work has been done in the parent loops.  */
2674     ploop = enter_nested_loop (se);
2675
2676   gcc_assert (ploop);
2677
2678   /* Generate the loop body.  */
2679   gfc_start_scalarized_body (ploop, &body);
2680
2681   /* If we have a mask, only add this element if the mask is set.  */
2682   if (maskexpr && maskexpr->rank > 0)
2683     {
2684       gfc_init_se (&maskse, parent_se);
2685       gfc_copy_loopinfo_to_se (&maskse, ploop);
2686       if (expr->rank == 0)
2687         maskse.ss = maskss;
2688       gfc_conv_expr_val (&maskse, maskexpr);
2689       gfc_add_block_to_block (&body, &maskse.pre);
2690
2691       gfc_start_block (&block);
2692     }
2693   else
2694     gfc_init_block (&block);
2695
2696   /* Do the actual summation/product.  */
2697   gfc_init_se (&arrayse, parent_se);
2698   gfc_copy_loopinfo_to_se (&arrayse, ploop);
2699   if (expr->rank == 0)
2700     arrayse.ss = arrayss;
2701   gfc_conv_expr_val (&arrayse, arrayexpr);
2702   gfc_add_block_to_block (&block, &arrayse.pre);
2703
2704   if (norm2)
2705     {
2706       /* if (x(i) != 0.0)
2707            {
2708              absX = abs(x(i))
2709              if (absX > scale)
2710                {
2711                  val = scale/absX;
2712                  result = 1.0 + result * val * val;
2713                  scale = absX;
2714                }
2715              else
2716                {
2717                  val = absX/scale;
2718                  result += val * val;
2719                }
2720            }  */
2721       tree res1, res2, cond, absX, val;
2722       stmtblock_t ifblock1, ifblock2, ifblock3;
2723
2724       gfc_init_block (&ifblock1);
2725
2726       absX = gfc_create_var (type, "absX");
2727       gfc_add_modify (&ifblock1, absX,
2728                       fold_build1_loc (input_location, ABS_EXPR, type,
2729                                        arrayse.expr));
2730       val = gfc_create_var (type, "val");
2731       gfc_add_expr_to_block (&ifblock1, val);
2732
2733       gfc_init_block (&ifblock2);
2734       gfc_add_modify (&ifblock2, val,
2735                       fold_build2_loc (input_location, RDIV_EXPR, type, scale,
2736                                        absX));
2737       res1 = fold_build2_loc (input_location, MULT_EXPR, type, val, val); 
2738       res1 = fold_build2_loc (input_location, MULT_EXPR, type, resvar, res1);
2739       res1 = fold_build2_loc (input_location, PLUS_EXPR, type, res1,
2740                               gfc_build_const (type, integer_one_node));
2741       gfc_add_modify (&ifblock2, resvar, res1);
2742       gfc_add_modify (&ifblock2, scale, absX);
2743       res1 = gfc_finish_block (&ifblock2); 
2744
2745       gfc_init_block (&ifblock3);
2746       gfc_add_modify (&ifblock3, val,
2747                       fold_build2_loc (input_location, RDIV_EXPR, type, absX,
2748                                        scale));
2749       res2 = fold_build2_loc (input_location, MULT_EXPR, type, val, val); 
2750       res2 = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, res2);
2751       gfc_add_modify (&ifblock3, resvar, res2);
2752       res2 = gfc_finish_block (&ifblock3);
2753
2754       cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
2755                               absX, scale);
2756       tmp = build3_v (COND_EXPR, cond, res1, res2);
2757       gfc_add_expr_to_block (&ifblock1, tmp);  
2758       tmp = gfc_finish_block (&ifblock1);
2759
2760       cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
2761                               arrayse.expr,
2762                               gfc_build_const (type, integer_zero_node));
2763
2764       tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
2765       gfc_add_expr_to_block (&block, tmp);  
2766     }
2767   else
2768     {
2769       tmp = fold_build2_loc (input_location, op, type, resvar, arrayse.expr);
2770       gfc_add_modify (&block, resvar, tmp);
2771     }
2772
2773   gfc_add_block_to_block (&block, &arrayse.post);
2774
2775   if (maskexpr && maskexpr->rank > 0)
2776     {
2777       /* We enclose the above in if (mask) {...} .  */
2778
2779       tmp = gfc_finish_block (&block);
2780       tmp = build3_v (COND_EXPR, maskse.expr, tmp,
2781                       build_empty_stmt (input_location));
2782     }
2783   else
2784     tmp = gfc_finish_block (&block);
2785   gfc_add_expr_to_block (&body, tmp);
2786
2787   gfc_trans_scalarizing_loops (ploop, &body);
2788
2789   /* For a scalar mask, enclose the loop in an if statement.  */
2790   if (maskexpr && maskexpr->rank == 0)
2791     {
2792       gfc_init_block (&block);
2793       gfc_add_block_to_block (&block, &ploop->pre);
2794       gfc_add_block_to_block (&block, &ploop->post);
2795       tmp = gfc_finish_block (&block);
2796
2797       if (expr->rank > 0)
2798         {
2799           tmp = build3_v (COND_EXPR, se->ss->info->data.scalar.value, tmp,
2800                           build_empty_stmt (input_location));
2801           gfc_advance_se_ss_chain (se);
2802         }
2803       else
2804         {
2805           gcc_assert (expr->rank == 0);
2806           gfc_init_se (&maskse, NULL);
2807           gfc_conv_expr_val (&maskse, maskexpr);
2808           tmp = build3_v (COND_EXPR, maskse.expr, tmp,
2809                           build_empty_stmt (input_location));
2810         }
2811
2812       gfc_add_expr_to_block (&block, tmp);
2813       gfc_add_block_to_block (&se->pre, &block);
2814       gcc_assert (se->post.head == NULL);
2815     }
2816   else
2817     {
2818       gfc_add_block_to_block (&se->pre, &ploop->pre);
2819       gfc_add_block_to_block (&se->pre, &ploop->post);
2820     }
2821
2822   if (expr->rank == 0)
2823     gfc_cleanup_loop (ploop);
2824
2825   if (norm2)
2826     {
2827       /* result = scale * sqrt(result).  */
2828       tree sqrt;
2829       sqrt = gfc_builtin_decl_for_float_kind (BUILT_IN_SQRT, expr->ts.kind);
2830       resvar = build_call_expr_loc (input_location,
2831                                     sqrt, 1, resvar);
2832       resvar = fold_build2_loc (input_location, MULT_EXPR, type, scale, resvar);
2833     }
2834
2835   se->expr = resvar;
2836 }
2837
2838
2839 /* Inline implementation of the dot_product intrinsic. This function
2840    is based on gfc_conv_intrinsic_arith (the previous function).  */
2841 static void
2842 gfc_conv_intrinsic_dot_product (gfc_se * se, gfc_expr * expr)
2843 {
2844   tree resvar;
2845   tree type;
2846   stmtblock_t body;
2847   stmtblock_t block;
2848   tree tmp;
2849   gfc_loopinfo loop;
2850   gfc_actual_arglist *actual;
2851   gfc_ss *arrayss1, *arrayss2;
2852   gfc_se arrayse1, arrayse2;
2853   gfc_expr *arrayexpr1, *arrayexpr2;
2854
2855   type = gfc_typenode_for_spec (&expr->ts);
2856
2857   /* Initialize the result.  */
2858   resvar = gfc_create_var (type, "val");
2859   if (expr->ts.type == BT_LOGICAL)
2860     tmp = build_int_cst (type, 0);
2861   else
2862     tmp = gfc_build_const (type, integer_zero_node);
2863
2864   gfc_add_modify (&se->pre, resvar, tmp);
2865
2866   /* Walk argument #1.  */
2867   actual = expr->value.function.actual;
2868   arrayexpr1 = actual->expr;
2869   arrayss1 = gfc_walk_expr (arrayexpr1);
2870   gcc_assert (arrayss1 != gfc_ss_terminator);
2871
2872   /* Walk argument #2.  */
2873   actual = actual->next;
2874   arrayexpr2 = actual->expr;
2875   arrayss2 = gfc_walk_expr (arrayexpr2);
2876   gcc_assert (arrayss2 != gfc_ss_terminator);
2877
2878   /* Initialize the scalarizer.  */
2879   gfc_init_loopinfo (&loop);
2880   gfc_add_ss_to_loop (&loop, arrayss1);
2881   gfc_add_ss_to_loop (&loop, arrayss2);
2882
2883   /* Initialize the loop.  */
2884   gfc_conv_ss_startstride (&loop);
2885   gfc_conv_loop_setup (&loop, &expr->where);
2886
2887   gfc_mark_ss_chain_used (arrayss1, 1);
2888   gfc_mark_ss_chain_used (arrayss2, 1);
2889
2890   /* Generate the loop body.  */
2891   gfc_start_scalarized_body (&loop, &body);
2892   gfc_init_block (&block);
2893
2894   /* Make the tree expression for [conjg(]array1[)].  */
2895   gfc_init_se (&arrayse1, NULL);
2896   gfc_copy_loopinfo_to_se (&arrayse1, &loop);
2897   arrayse1.ss = arrayss1;
2898   gfc_conv_expr_val (&arrayse1, arrayexpr1);
2899   if (expr->ts.type == BT_COMPLEX)
2900     arrayse1.expr = fold_build1_loc (input_location, CONJ_EXPR, type,
2901                                      arrayse1.expr);
2902   gfc_add_block_to_block (&block, &arrayse1.pre);
2903
2904   /* Make the tree expression for array2.  */
2905   gfc_init_se (&arrayse2, NULL);
2906   gfc_copy_loopinfo_to_se (&arrayse2, &loop);
2907   arrayse2.ss = arrayss2;
2908   gfc_conv_expr_val (&arrayse2, arrayexpr2);
2909   gfc_add_block_to_block (&block, &arrayse2.pre);
2910
2911   /* Do the actual product and sum.  */
2912   if (expr->ts.type == BT_LOGICAL)
2913     {
2914       tmp = fold_build2_loc (input_location, TRUTH_AND_EXPR, type,
2915                              arrayse1.expr, arrayse2.expr);
2916       tmp = fold_build2_loc (input_location, TRUTH_OR_EXPR, type, resvar, tmp);
2917     }
2918   else
2919     {
2920       tmp = fold_build2_loc (input_location, MULT_EXPR, type, arrayse1.expr,
2921                              arrayse2.expr);
2922       tmp = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, tmp);
2923     }
2924   gfc_add_modify (&block, resvar, tmp);
2925
2926   /* Finish up the loop block and the loop.  */
2927   tmp = gfc_finish_block (&block);
2928   gfc_add_expr_to_block (&body, tmp);
2929
2930   gfc_trans_scalarizing_loops (&loop, &body);
2931   gfc_add_block_to_block (&se->pre, &loop.pre);
2932   gfc_add_block_to_block (&se->pre, &loop.post);
2933   gfc_cleanup_loop (&loop);
2934
2935   se->expr = resvar;
2936 }
2937
2938
2939 /* Emit code for minloc or maxloc intrinsic.  There are many different cases
2940    we need to handle.  For performance reasons we sometimes create two
2941    loops instead of one, where the second one is much simpler.
2942    Examples for minloc intrinsic:
2943    1) Result is an array, a call is generated
2944    2) Array mask is used and NaNs need to be supported:
2945       limit = Infinity;
2946       pos = 0;
2947       S = from;
2948       while (S <= to) {
2949         if (mask[S]) {
2950           if (pos == 0) pos = S + (1 - from);
2951           if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2952         }
2953         S++;
2954       }
2955       goto lab2;
2956       lab1:;
2957       while (S <= to) {
2958         if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2959         S++;
2960       }
2961       lab2:;
2962    3) NaNs need to be supported, but it is known at compile time or cheaply
2963       at runtime whether array is nonempty or not:
2964       limit = Infinity;
2965       pos = 0;
2966       S = from;
2967       while (S <= to) {
2968         if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2969         S++;
2970       }
2971       if (from <= to) pos = 1;
2972       goto lab2;
2973       lab1:;
2974       while (S <= to) {
2975         if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2976         S++;
2977       }
2978       lab2:;
2979    4) NaNs aren't supported, array mask is used:
2980       limit = infinities_supported ? Infinity : huge (limit);
2981       pos = 0;
2982       S = from;
2983       while (S <= to) {
2984         if (mask[S]) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2985         S++;
2986       }
2987       goto lab2;
2988       lab1:;
2989       while (S <= to) {
2990         if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2991         S++;
2992       }
2993       lab2:;
2994    5) Same without array mask:
2995       limit = infinities_supported ? Infinity : huge (limit);
2996       pos = (from <= to) ? 1 : 0;
2997       S = from;
2998       while (S <= to) {
2999         if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
3000         S++;
3001       }
3002    For 3) and 5), if mask is scalar, this all goes into a conditional,
3003    setting pos = 0; in the else branch.  */
3004
3005 static void
3006 gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * expr, enum tree_code op)
3007 {
3008   stmtblock_t body;
3009   stmtblock_t block;
3010   stmtblock_t ifblock;
3011   stmtblock_t elseblock;
3012   tree limit;
3013   tree type;
3014   tree tmp;
3015   tree cond;
3016   tree elsetmp;
3017   tree ifbody;
3018   tree offset;
3019   tree nonempty;
3020   tree lab1, lab2;
3021   gfc_loopinfo loop;
3022   gfc_actual_arglist *actual;
3023   gfc_ss *arrayss;
3024   gfc_ss *maskss;
3025   gfc_se arrayse;
3026   gfc_se maskse;
3027   gfc_expr *arrayexpr;
3028   gfc_expr *maskexpr;
3029   tree pos;
3030   int n;
3031
3032   if (se->ss)
3033     {
3034       gfc_conv_intrinsic_funcall (se, expr);
3035       return;
3036     }
3037
3038   /* Initialize the result.  */
3039   pos = gfc_create_var (gfc_array_index_type, "pos");
3040   offset = gfc_create_var (gfc_array_index_type, "offset");
3041   type = gfc_typenode_for_spec (&expr->ts);
3042
3043   /* Walk the arguments.  */
3044   actual = expr->value.function.actual;
3045   arrayexpr = actual->expr;
3046   arrayss = gfc_walk_expr (arrayexpr);
3047   gcc_assert (arrayss != gfc_ss_terminator);
3048
3049   actual = actual->next->next;
3050   gcc_assert (actual);
3051   maskexpr = actual->expr;
3052   nonempty = NULL;
3053   if (maskexpr && maskexpr->rank != 0)
3054     {
3055       maskss = gfc_walk_expr (maskexpr);
3056       gcc_assert (maskss != gfc_ss_terminator);
3057     }
3058   else
3059     {
3060       mpz_t asize;
3061       if (gfc_array_size (arrayexpr, &asize) == SUCCESS)
3062         {
3063           nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
3064           mpz_clear (asize);
3065           nonempty = fold_build2_loc (input_location, GT_EXPR,
3066                                       boolean_type_node, nonempty,
3067                                       gfc_index_zero_node);
3068         }
3069       maskss = NULL;
3070     }
3071
3072   limit = gfc_create_var (gfc_typenode_for_spec (&arrayexpr->ts), "limit");
3073   switch (arrayexpr->ts.type)
3074     {
3075     case BT_REAL:
3076       tmp = gfc_build_inf_or_huge (TREE_TYPE (limit), arrayexpr->ts.kind);
3077       break;
3078
3079     case BT_INTEGER:
3080       n = gfc_validate_kind (arrayexpr->ts.type, arrayexpr->ts.kind, false);
3081       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge,
3082                                   arrayexpr->ts.kind);
3083       break;
3084
3085     default:
3086       gcc_unreachable ();
3087     }
3088
3089   /* We start with the most negative possible value for MAXLOC, and the most
3090      positive possible value for MINLOC. The most negative possible value is
3091      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
3092      possible value is HUGE in both cases.  */
3093   if (op == GT_EXPR)
3094     tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
3095   if (op == GT_EXPR && expr->ts.type == BT_INTEGER)
3096     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp), tmp,
3097                            build_int_cst (type, 1));
3098
3099   gfc_add_modify (&se->pre, limit, tmp);
3100
3101   /* Initialize the scalarizer.  */
3102   gfc_init_loopinfo (&loop);
3103   gfc_add_ss_to_loop (&loop, arrayss);
3104   if (maskss)
3105     gfc_add_ss_to_loop (&loop, maskss);
3106
3107   /* Initialize the loop.  */
3108   gfc_conv_ss_startstride (&loop);
3109
3110   /* The code generated can have more than one loop in sequence (see the
3111      comment at the function header).  This doesn't work well with the
3112      scalarizer, which changes arrays' offset when the scalarization loops
3113      are generated (see gfc_trans_preloop_setup).  Fortunately, {min,max}loc
3114      are  currently inlined in the scalar case only (for which loop is of rank
3115      one).  As there is no dependency to care about in that case, there is no
3116      temporary, so that we can use the scalarizer temporary code to handle
3117      multiple loops.  Thus, we set temp_dim here, we call gfc_mark_ss_chain_used
3118      with flag=3 later, and we use gfc_trans_scalarized_loop_boundary even later
3119      to restore offset.
3120      TODO: this prevents inlining of rank > 0 minmaxloc calls, so this
3121      should eventually go away.  We could either create two loops properly,
3122      or find another way to save/restore the array offsets between the two
3123      loops (without conflicting with temporary management), or use a single
3124      loop minmaxloc implementation.  See PR 31067.  */
3125   loop.temp_dim = loop.dimen;
3126   gfc_conv_loop_setup (&loop, &expr->where);
3127
3128   gcc_assert (loop.dimen == 1);
3129   if (nonempty == NULL && maskss == NULL && loop.from[0] && loop.to[0])
3130     nonempty = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
3131                                 loop.from[0], loop.to[0]);
3132
3133   lab1 = NULL;
3134   lab2 = NULL;
3135   /* Initialize the position to zero, following Fortran 2003.  We are free
3136      to do this because Fortran 95 allows the result of an entirely false
3137      mask to be processor dependent.  If we know at compile time the array
3138      is non-empty and no MASK is used, we can initialize to 1 to simplify
3139      the inner loop.  */
3140   if (nonempty != NULL && !HONOR_NANS (DECL_MODE (limit)))
3141     gfc_add_modify (&loop.pre, pos,
3142                     fold_build3_loc (input_location, COND_EXPR,
3143                                      gfc_array_index_type,
3144                                      nonempty, gfc_index_one_node,
3145                                      gfc_index_zero_node));
3146   else
3147     {
3148       gfc_add_modify (&loop.pre, pos, gfc_index_zero_node);
3149       lab1 = gfc_build_label_decl (NULL_TREE);
3150       TREE_USED (lab1) = 1;
3151       lab2 = gfc_build_label_decl (NULL_TREE);
3152       TREE_USED (lab2) = 1;
3153     }
3154
3155   /* An offset must be added to the loop
3156      counter to obtain the required position.  */
3157   gcc_assert (loop.from[0]);
3158
3159   tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
3160                          gfc_index_one_node, loop.from[0]);
3161   gfc_add_modify (&loop.pre, offset, tmp);
3162
3163   gfc_mark_ss_chain_used (arrayss, lab1 ? 3 : 1);
3164   if (maskss)
3165     gfc_mark_ss_chain_used (maskss, lab1 ? 3 : 1);
3166   /* Generate the loop body.  */
3167   gfc_start_scalarized_body (&loop, &body);
3168
3169   /* If we have a mask, only check this element if the mask is set.  */
3170   if (maskss)
3171     {
3172       gfc_init_se (&maskse, NULL);
3173       gfc_copy_loopinfo_to_se (&maskse, &loop);
3174       maskse.ss = maskss;
3175       gfc_conv_expr_val (&maskse, maskexpr);
3176       gfc_add_block_to_block (&body, &maskse.pre);
3177
3178       gfc_start_block (&block);
3179     }
3180   else
3181     gfc_init_block (&block);
3182
3183   /* Compare with the current limit.  */
3184   gfc_init_se (&arrayse, NULL);
3185   gfc_copy_loopinfo_to_se (&arrayse, &loop);
3186   arrayse.ss = arrayss;
3187   gfc_conv_expr_val (&arrayse, arrayexpr);
3188   gfc_add_block_to_block (&block, &arrayse.pre);
3189
3190   /* We do the following if this is a more extreme value.  */
3191   gfc_start_block (&ifblock);
3192
3193   /* Assign the value to the limit...  */
3194   gfc_add_modify (&ifblock, limit, arrayse.expr);
3195
3196   if (nonempty == NULL && HONOR_NANS (DECL_MODE (limit)))
3197     {
3198       stmtblock_t ifblock2;
3199       tree ifbody2;
3200
3201       gfc_start_block (&ifblock2);
3202       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
3203                              loop.loopvar[0], offset);
3204       gfc_add_modify (&ifblock2, pos, tmp);
3205       ifbody2 = gfc_finish_block (&ifblock2);
3206       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, pos,
3207                               gfc_index_zero_node);
3208       tmp = build3_v (COND_EXPR, cond, ifbody2,
3209                       build_empty_stmt (input_location));
3210       gfc_add_expr_to_block (&block, tmp);
3211     }
3212
3213   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
3214                          loop.loopvar[0], offset);
3215   gfc_add_modify (&ifblock, pos, tmp);
3216
3217   if (lab1)
3218     gfc_add_expr_to_block (&ifblock, build1_v (GOTO_EXPR, lab1));
3219
3220   ifbody = gfc_finish_block (&ifblock);
3221
3222   if (!lab1 || HONOR_NANS (DECL_MODE (limit)))
3223     {
3224       if (lab1)
3225         cond = fold_build2_loc (input_location,
3226                                 op == GT_EXPR ? GE_EXPR : LE_EXPR,
3227                                 boolean_type_node, arrayse.expr, limit);
3228       else
3229         cond = fold_build2_loc (input_location, op, boolean_type_node,
3230                                 arrayse.expr, limit);
3231
3232       ifbody = build3_v (COND_EXPR, cond, ifbody,
3233                          build_empty_stmt (input_location));
3234     }
3235   gfc_add_expr_to_block (&block, ifbody);
3236
3237   if (maskss)
3238     {
3239       /* We enclose the above in if (mask) {...}.  */
3240       tmp = gfc_finish_block (&block);
3241
3242       tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3243                       build_empty_stmt (input_location));
3244     }
3245   else
3246     tmp = gfc_finish_block (&block);
3247   gfc_add_expr_to_block (&body, tmp);
3248
3249   if (lab1)
3250     {
3251       gfc_trans_scalarized_loop_boundary (&loop, &body);
3252
3253       if (HONOR_NANS (DECL_MODE (limit)))
3254         {
3255           if (nonempty != NULL)
3256             {
3257               ifbody = build2_v (MODIFY_EXPR, pos, gfc_index_one_node);
3258               tmp = build3_v (COND_EXPR, nonempty, ifbody,
3259                               build_empty_stmt (input_location));
3260               gfc_add_expr_to_block (&loop.code[0], tmp);
3261             }
3262         }
3263
3264       gfc_add_expr_to_block (&loop.code[0], build1_v (GOTO_EXPR, lab2));
3265       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab1));
3266
3267       /* If we have a mask, only check this element if the mask is set.  */
3268       if (maskss)
3269         {
3270           gfc_init_se (&maskse, NULL);
3271           gfc_copy_loopinfo_to_se (&maskse, &loop);
3272           maskse.ss = maskss;
3273           gfc_conv_expr_val (&maskse, maskexpr);
3274           gfc_add_block_to_block (&body, &maskse.pre);
3275
3276           gfc_start_block (&block);
3277         }
3278       else
3279         gfc_init_block (&block);
3280
3281       /* Compare with the current limit.  */
3282       gfc_init_se (&arrayse, NULL);
3283       gfc_copy_loopinfo_to_se (&arrayse, &loop);
3284       arrayse.ss = arrayss;
3285       gfc_conv_expr_val (&arrayse, arrayexpr);
3286       gfc_add_block_to_block (&block, &arrayse.pre);
3287
3288       /* We do the following if this is a more extreme value.  */
3289       gfc_start_block (&ifblock);
3290
3291       /* Assign the value to the limit...  */
3292       gfc_add_modify (&ifblock, limit, arrayse.expr);
3293
3294       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
3295                              loop.loopvar[0], offset);
3296       gfc_add_modify (&ifblock, pos, tmp);
3297
3298       ifbody = gfc_finish_block (&ifblock);
3299
3300       cond = fold_build2_loc (input_location, op, boolean_type_node,
3301                               arrayse.expr, limit);
3302
3303       tmp = build3_v (COND_EXPR, cond, ifbody,
3304                       build_empty_stmt (input_location));
3305       gfc_add_expr_to_block (&block, tmp);
3306
3307       if (maskss)
3308         {
3309           /* We enclose the above in if (mask) {...}.  */
3310           tmp = gfc_finish_block (&block);
3311
3312           tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3313                           build_empty_stmt (input_location));
3314         }
3315       else
3316         tmp = gfc_finish_block (&block);
3317       gfc_add_expr_to_block (&body, tmp);
3318       /* Avoid initializing loopvar[0] again, it should be left where
3319          it finished by the first loop.  */
3320       loop.from[0] = loop.loopvar[0];
3321     }
3322
3323   gfc_trans_scalarizing_loops (&loop, &body);
3324
3325   if (lab2)
3326     gfc_add_expr_to_block (&loop.pre, build1_v (LABEL_EXPR, lab2));
3327
3328   /* For a scalar mask, enclose the loop in an if statement.  */
3329   if (maskexpr && maskss == NULL)
3330     {
3331       gfc_init_se (&maskse, NULL);
3332       gfc_conv_expr_val (&maskse, maskexpr);
3333       gfc_init_block (&block);
3334       gfc_add_block_to_block (&block, &loop.pre);
3335       gfc_add_block_to_block (&block, &loop.post);
3336       tmp = gfc_finish_block (&block);
3337
3338       /* For the else part of the scalar mask, just initialize
3339          the pos variable the same way as above.  */
3340
3341       gfc_init_block (&elseblock);
3342       gfc_add_modify (&elseblock, pos, gfc_index_zero_node);
3343       elsetmp = gfc_finish_block (&elseblock);
3344
3345       tmp = build3_v (COND_EXPR, maskse.expr, tmp, elsetmp);
3346       gfc_add_expr_to_block (&block, tmp);
3347       gfc_add_block_to_block (&se->pre, &block);
3348     }
3349   else
3350     {
3351       gfc_add_block_to_block (&se->pre, &loop.pre);
3352       gfc_add_block_to_block (&se->pre, &loop.post);
3353     }
3354   gfc_cleanup_loop (&loop);
3355
3356   se->expr = convert (type, pos);
3357 }
3358
3359 /* Emit code for minval or maxval intrinsic.  There are many different cases
3360    we need to handle.  For performance reasons we sometimes create two
3361    loops instead of one, where the second one is much simpler.
3362    Examples for minval intrinsic:
3363    1) Result is an array, a call is generated
3364    2) Array mask is used and NaNs need to be supported, rank 1:
3365       limit = Infinity;
3366       nonempty = false;
3367       S = from;
3368       while (S <= to) {
3369         if (mask[S]) { nonempty = true; if (a[S] <= limit) goto lab; }
3370         S++;
3371       }
3372       limit = nonempty ? NaN : huge (limit);
3373       lab:
3374       while (S <= to) { if(mask[S]) limit = min (a[S], limit); S++; }
3375    3) NaNs need to be supported, but it is known at compile time or cheaply
3376       at runtime whether array is nonempty or not, rank 1:
3377       limit = Infinity;
3378       S = from;
3379       while (S <= to) { if (a[S] <= limit) goto lab; S++; }
3380       limit = (from <= to) ? NaN : huge (limit);
3381       lab:
3382       while (S <= to) { limit = min (a[S], limit); S++; }
3383    4) Array mask is used and NaNs need to be supported, rank > 1:
3384       limit = Infinity;
3385       nonempty = false;
3386       fast = false;
3387       S1 = from1;
3388       while (S1 <= to1) {
3389         S2 = from2;
3390         while (S2 <= to2) {
3391           if (mask[S1][S2]) {
3392             if (fast) limit = min (a[S1][S2], limit);
3393             else {
3394               nonempty = true;
3395               if (a[S1][S2] <= limit) {
3396                 limit = a[S1][S2];
3397                 fast = true;
3398               }
3399             }
3400           }
3401           S2++;
3402         }
3403         S1++;
3404       }
3405       if (!fast)
3406         limit = nonempty ? NaN : huge (limit);
3407    5) NaNs need to be supported, but it is known at compile time or cheaply
3408       at runtime whether array is nonempty or not, rank > 1:
3409       limit = Infinity;
3410       fast = false;
3411       S1 = from1;
3412       while (S1 <= to1) {
3413         S2 = from2;
3414         while (S2 <= to2) {
3415           if (fast) limit = min (a[S1][S2], limit);
3416           else {
3417             if (a[S1][S2] <= limit) {
3418               limit = a[S1][S2];
3419               fast = true;
3420             }
3421           }
3422           S2++;
3423         }
3424         S1++;
3425       }
3426       if (!fast)
3427         limit = (nonempty_array) ? NaN : huge (limit);
3428    6) NaNs aren't supported, but infinities are.  Array mask is used:
3429       limit = Infinity;
3430       nonempty = false;
3431       S = from;
3432       while (S <= to) {
3433         if (mask[S]) { nonempty = true; limit = min (a[S], limit); }
3434         S++;
3435       }
3436       limit = nonempty ? limit : huge (limit);
3437    7) Same without array mask:
3438       limit = Infinity;
3439       S = from;
3440       while (S <= to) { limit = min (a[S], limit); S++; }
3441       limit = (from <= to) ? limit : huge (limit);
3442    8) Neither NaNs nor infinities are supported (-ffast-math or BT_INTEGER):
3443       limit = huge (limit);
3444       S = from;
3445       while (S <= to) { limit = min (a[S], limit); S++); }
3446       (or
3447       while (S <= to) { if (mask[S]) limit = min (a[S], limit); S++; }
3448       with array mask instead).
3449    For 3), 5), 7) and 8), if mask is scalar, this all goes into a conditional,
3450    setting limit = huge (limit); in the else branch.  */
3451
3452 static void
3453 gfc_conv_intrinsic_minmaxval (gfc_se * se, gfc_expr * expr, enum tree_code op)
3454 {
3455   tree limit;
3456   tree type;
3457   tree tmp;
3458   tree ifbody;
3459   tree nonempty;
3460   tree nonempty_var;
3461   tree lab;
3462   tree fast;
3463   tree huge_cst = NULL, nan_cst = NULL;
3464   stmtblock_t body;
3465   stmtblock_t block, block2;
3466   gfc_loopinfo loop;
3467   gfc_actual_arglist *actual;
3468   gfc_ss *arrayss;
3469   gfc_ss *maskss;
3470   gfc_se arrayse;
3471   gfc_se maskse;
3472   gfc_expr *arrayexpr;
3473   gfc_expr *maskexpr;
3474   int n;
3475
3476   if (se->ss)
3477     {
3478       gfc_conv_intrinsic_funcall (se, expr);
3479       return;
3480     }
3481
3482   type = gfc_typenode_for_spec (&expr->ts);
3483   /* Initialize the result.  */
3484   limit = gfc_create_var (type, "limit");
3485   n = gfc_validate_kind (expr->ts.type, expr->ts.kind, false);
3486   switch (expr->ts.type)
3487     {
3488     case BT_REAL:
3489       huge_cst = gfc_conv_mpfr_to_tree (gfc_real_kinds[n].huge,
3490                                         expr->ts.kind, 0);
3491       if (HONOR_INFINITIES (DECL_MODE (limit)))
3492         {
3493           REAL_VALUE_TYPE real;
3494           real_inf (&real);
3495           tmp = build_real (type, real);
3496         }
3497       else
3498         tmp = huge_cst;
3499       if (HONOR_NANS (DECL_MODE (limit)))
3500         {
3501           REAL_VALUE_TYPE real;
3502           real_nan (&real, "", 1, DECL_MODE (limit));
3503           nan_cst = build_real (type, real);
3504         }
3505       break;
3506
3507     case BT_INTEGER:
3508       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge, expr->ts.kind);
3509       break;
3510
3511     default:
3512       gcc_unreachable ();
3513     }
3514
3515   /* We start with the most negative possible value for MAXVAL, and the most
3516      positive possible value for MINVAL. The most negative possible value is
3517      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
3518      possible value is HUGE in both cases.  */
3519   if (op == GT_EXPR)
3520     {
3521       tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
3522       if (huge_cst)
3523         huge_cst = fold_build1_loc (input_location, NEGATE_EXPR,
3524                                     TREE_TYPE (huge_cst), huge_cst);
3525     }
3526
3527   if (op == GT_EXPR && expr->ts.type == BT_INTEGER)
3528     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp),
3529                            tmp, build_int_cst (type, 1));
3530
3531   gfc_add_modify (&se->pre, limit, tmp);
3532
3533   /* Walk the arguments.  */
3534   actual = expr->value.function.actual;
3535   arrayexpr = actual->expr;
3536   arrayss = gfc_walk_expr (arrayexpr);
3537   gcc_assert (arrayss != gfc_ss_terminator);
3538
3539   actual = actual->next->next;
3540   gcc_assert (actual);
3541   maskexpr = actual->expr;
3542   nonempty = NULL;
3543   if (maskexpr && maskexpr->rank != 0)
3544     {
3545       maskss = gfc_walk_expr (maskexpr);
3546       gcc_assert (maskss != gfc_ss_terminator);
3547     }
3548   else
3549     {
3550       mpz_t asize;
3551       if (gfc_array_size (arrayexpr, &asize) == SUCCESS)
3552         {
3553           nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
3554           mpz_clear (asize);
3555           nonempty = fold_build2_loc (input_location, GT_EXPR,
3556                                       boolean_type_node, nonempty,
3557                                       gfc_index_zero_node);
3558         }
3559       maskss = NULL;
3560     }
3561
3562   /* Initialize the scalarizer.  */
3563   gfc_init_loopinfo (&loop);
3564   gfc_add_ss_to_loop (&loop, arrayss);
3565   if (maskss)
3566     gfc_add_ss_to_loop (&loop, maskss);
3567
3568   /* Initialize the loop.  */
3569   gfc_conv_ss_startstride (&loop);
3570
3571   /* The code generated can have more than one loop in sequence (see the
3572      comment at the function header).  This doesn't work well with the
3573      scalarizer, which changes arrays' offset when the scalarization loops
3574      are generated (see gfc_trans_preloop_setup).  Fortunately, {min,max}val
3575      are  currently inlined in the scalar case only.  As there is no dependency
3576      to care about in that case, there is no temporary, so that we can use the
3577      scalarizer temporary code to handle multiple loops.  Thus, we set temp_dim
3578      here, we call gfc_mark_ss_chain_used with flag=3 later, and we use
3579      gfc_trans_scalarized_loop_boundary even later to restore offset.
3580      TODO: this prevents inlining of rank > 0 minmaxval calls, so this
3581      should eventually go away.  We could either create two loops properly,
3582      or find another way to save/restore the array offsets between the two
3583      loops (without conflicting with temporary management), or use a single
3584      loop minmaxval implementation.  See PR 31067.  */
3585   loop.temp_dim = loop.dimen;
3586   gfc_conv_loop_setup (&loop, &expr->where);
3587
3588   if (nonempty == NULL && maskss == NULL
3589       && loop.dimen == 1 && loop.from[0] && loop.to[0])
3590     nonempty = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
3591                                 loop.from[0], loop.to[0]);
3592   nonempty_var = NULL;
3593   if (nonempty == NULL
3594       && (HONOR_INFINITIES (DECL_MODE (limit))
3595           || HONOR_NANS (DECL_MODE (limit))))
3596     {
3597       nonempty_var = gfc_create_var (boolean_type_node, "nonempty");
3598       gfc_add_modify (&se->pre, nonempty_var, boolean_false_node);
3599       nonempty = nonempty_var;
3600     }
3601   lab = NULL;
3602   fast = NULL;
3603   if (HONOR_NANS (DECL_MODE (limit)))
3604     {
3605       if (loop.dimen == 1)
3606         {
3607           lab = gfc_build_label_decl (NULL_TREE);
3608           TREE_USED (lab) = 1;
3609         }
3610       else
3611         {
3612           fast = gfc_create_var (boolean_type_node, "fast");
3613           gfc_add_modify (&se->pre, fast, boolean_false_node);
3614         }
3615     }
3616
3617   gfc_mark_ss_chain_used (arrayss, lab ? 3 : 1);
3618   if (maskss)
3619     gfc_mark_ss_chain_used (maskss, lab ? 3 : 1);
3620   /* Generate the loop body.  */
3621   gfc_start_scalarized_body (&loop, &body);
3622
3623   /* If we have a mask, only add this element if the mask is set.  */
3624   if (maskss)
3625     {
3626       gfc_init_se (&maskse, NULL);
3627       gfc_copy_loopinfo_to_se (&maskse, &loop);
3628       maskse.ss = maskss;
3629       gfc_conv_expr_val (&maskse, maskexpr);
3630       gfc_add_block_to_block (&body, &maskse.pre);
3631
3632       gfc_start_block (&block);
3633     }
3634   else
3635     gfc_init_block (&block);
3636
3637   /* Compare with the current limit.  */
3638   gfc_init_se (&arrayse, NULL);
3639   gfc_copy_loopinfo_to_se (&arrayse, &loop);
3640   arrayse.ss = arrayss;
3641   gfc_conv_expr_val (&arrayse, arrayexpr);
3642   gfc_add_block_to_block (&block, &arrayse.pre);
3643
3644   gfc_init_block (&block2);
3645
3646   if (nonempty_var)
3647     gfc_add_modify (&block2, nonempty_var, boolean_true_node);
3648
3649   if (HONOR_NANS (DECL_MODE (limit)))
3650     {
3651       tmp = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
3652                              boolean_type_node, arrayse.expr, limit);
3653       if (lab)
3654         ifbody = build1_v (GOTO_EXPR, lab);
3655       else
3656         {
3657           stmtblock_t ifblock;
3658
3659           gfc_init_block (&ifblock);
3660           gfc_add_modify (&ifblock, limit, arrayse.expr);
3661           gfc_add_modify (&ifblock, fast, boolean_true_node);
3662           ifbody = gfc_finish_block (&ifblock);
3663         }
3664       tmp = build3_v (COND_EXPR, tmp, ifbody,
3665                       build_empty_stmt (input_location));
3666       gfc_add_expr_to_block (&block2, tmp);
3667     }
3668   else
3669     {
3670       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3671          signed zeros.  */
3672       if (HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3673         {
3674           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3675                                  arrayse.expr, limit);
3676           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3677           tmp = build3_v (COND_EXPR, tmp, ifbody,
3678                           build_empty_stmt (input_location));
3679           gfc_add_expr_to_block (&block2, tmp);
3680         }
3681       else
3682         {
3683           tmp = fold_build2_loc (input_location,
3684                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3685                                  type, arrayse.expr, limit);
3686           gfc_add_modify (&block2, limit, tmp);
3687         }
3688     }
3689
3690   if (fast)
3691     {
3692       tree elsebody = gfc_finish_block (&block2);
3693
3694       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3695          signed zeros.  */
3696       if (HONOR_NANS (DECL_MODE (limit))
3697           || HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3698         {
3699           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3700                                  arrayse.expr, limit);
3701           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3702           ifbody = build3_v (COND_EXPR, tmp, ifbody,
3703                              build_empty_stmt (input_location));
3704         }
3705       else
3706         {
3707           tmp = fold_build2_loc (input_location,
3708                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3709                                  type, arrayse.expr, limit);
3710           ifbody = build2_v (MODIFY_EXPR, limit, tmp);
3711         }
3712       tmp = build3_v (COND_EXPR, fast, ifbody, elsebody);
3713       gfc_add_expr_to_block (&block, tmp);
3714     }
3715   else
3716     gfc_add_block_to_block (&block, &block2);
3717
3718   gfc_add_block_to_block (&block, &arrayse.post);
3719
3720   tmp = gfc_finish_block (&block);
3721   if (maskss)
3722     /* We enclose the above in if (mask) {...}.  */
3723     tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3724                     build_empty_stmt (input_location));
3725   gfc_add_expr_to_block (&body, tmp);
3726
3727   if (lab)
3728     {
3729       gfc_trans_scalarized_loop_boundary (&loop, &body);
3730
3731       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
3732                              nan_cst, huge_cst);
3733       gfc_add_modify (&loop.code[0], limit, tmp);
3734       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab));
3735
3736       /* If we have a mask, only add this element if the mask is set.  */
3737       if (maskss)
3738         {
3739           gfc_init_se (&maskse, NULL);
3740           gfc_copy_loopinfo_to_se (&maskse, &loop);
3741           maskse.ss = maskss;
3742           gfc_conv_expr_val (&maskse, maskexpr);
3743           gfc_add_block_to_block (&body, &maskse.pre);
3744
3745           gfc_start_block (&block);
3746         }
3747       else
3748         gfc_init_block (&block);
3749
3750       /* Compare with the current limit.  */
3751       gfc_init_se (&arrayse, NULL);
3752       gfc_copy_loopinfo_to_se (&arrayse, &loop);
3753       arrayse.ss = arrayss;
3754       gfc_conv_expr_val (&arrayse, arrayexpr);
3755       gfc_add_block_to_block (&block, &arrayse.pre);
3756
3757       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3758          signed zeros.  */
3759       if (HONOR_NANS (DECL_MODE (limit))
3760           || HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3761         {
3762           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3763                                  arrayse.expr, limit);
3764           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3765           tmp = build3_v (COND_EXPR, tmp, ifbody,
3766                           build_empty_stmt (input_location));
3767           gfc_add_expr_to_block (&block, tmp);
3768         }
3769       else
3770         {
3771           tmp = fold_build2_loc (input_location,
3772                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3773                                  type, arrayse.expr, limit);
3774           gfc_add_modify (&block, limit, tmp);
3775         }
3776
3777       gfc_add_block_to_block (&block, &arrayse.post);
3778
3779       tmp = gfc_finish_block (&block);
3780       if (maskss)
3781         /* We enclose the above in if (mask) {...}.  */
3782         tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3783                         build_empty_stmt (input_location));
3784       gfc_add_expr_to_block (&body, tmp);
3785       /* Avoid initializing loopvar[0] again, it should be left where
3786          it finished by the first loop.  */
3787       loop.from[0] = loop.loopvar[0];
3788     }
3789   gfc_trans_scalarizing_loops (&loop, &body);
3790
3791   if (fast)
3792     {
3793       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
3794                              nan_cst, huge_cst);
3795       ifbody = build2_v (MODIFY_EXPR, limit, tmp);
3796       tmp = build3_v (COND_EXPR, fast, build_empty_stmt (input_location),
3797                       ifbody);
3798       gfc_add_expr_to_block (&loop.pre, tmp);
3799     }
3800   else if (HONOR_INFINITIES (DECL_MODE (limit)) && !lab)
3801     {
3802       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty, limit,
3803                              huge_cst);
3804       gfc_add_modify (&loop.pre, limit, tmp);
3805     }
3806
3807   /* For a scalar mask, enclose the loop in an if statement.  */
3808   if (maskexpr && maskss == NULL)
3809     {
3810       tree else_stmt;
3811
3812       gfc_init_se (&maskse, NULL);
3813       gfc_conv_expr_val (&maskse, maskexpr);
3814       gfc_init_block (&block);
3815       gfc_add_block_to_block (&block, &loop.pre);
3816       gfc_add_block_to_block (&block, &loop.post);
3817       tmp = gfc_finish_block (&block);
3818
3819       if (HONOR_INFINITIES (DECL_MODE (limit)))
3820         else_stmt = build2_v (MODIFY_EXPR, limit, huge_cst);
3821       else
3822         else_stmt = build_empty_stmt (input_location);
3823       tmp = build3_v (COND_EXPR, maskse.expr, tmp, else_stmt);
3824       gfc_add_expr_to_block (&block, tmp);
3825       gfc_add_block_to_block (&se->pre, &block);
3826     }
3827   else
3828     {
3829       gfc_add_block_to_block (&se->pre, &loop.pre);
3830       gfc_add_block_to_block (&se->pre, &loop.post);
3831     }
3832
3833   gfc_cleanup_loop (&loop);
3834
3835   se->expr = limit;
3836 }
3837
3838 /* BTEST (i, pos) = (i & (1 << pos)) != 0.  */
3839 static void
3840 gfc_conv_intrinsic_btest (gfc_se * se, gfc_expr * expr)
3841 {
3842   tree args[2];
3843   tree type;
3844   tree tmp;
3845
3846   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3847   type = TREE_TYPE (args[0]);
3848
3849   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
3850                          build_int_cst (type, 1), args[1]);
3851   tmp = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], tmp);
3852   tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp,
3853                          build_int_cst (type, 0));
3854   type = gfc_typenode_for_spec (&expr->ts);
3855   se->expr = convert (type, tmp);
3856 }
3857
3858
3859 /* Generate code for BGE, BGT, BLE and BLT intrinsics.  */
3860 static void
3861 gfc_conv_intrinsic_bitcomp (gfc_se * se, gfc_expr * expr, enum tree_code op)
3862 {
3863   tree args[2];
3864
3865   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3866
3867   /* Convert both arguments to the unsigned type of the same size.  */
3868   args[0] = fold_convert (unsigned_type_for (TREE_TYPE (args[0])), args[0]);
3869   args[1] = fold_convert (unsigned_type_for (TREE_TYPE (args[1])), args[1]);
3870
3871   /* If they have unequal type size, convert to the larger one.  */
3872   if (TYPE_PRECISION (TREE_TYPE (args[0]))
3873       > TYPE_PRECISION (TREE_TYPE (args[1])))
3874     args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
3875   else if (TYPE_PRECISION (TREE_TYPE (args[1]))
3876            > TYPE_PRECISION (TREE_TYPE (args[0])))
3877     args[0] = fold_convert (TREE_TYPE (args[1]), args[0]);
3878
3879   /* Now, we compare them.  */
3880   se->expr = fold_build2_loc (input_location, op, boolean_type_node,
3881                               args[0], args[1]);
3882 }
3883
3884
3885 /* Generate code to perform the specified operation.  */
3886 static void
3887 gfc_conv_intrinsic_bitop (gfc_se * se, gfc_expr * expr, enum tree_code op)
3888 {
3889   tree args[2];
3890
3891   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3892   se->expr = fold_build2_loc (input_location, op, TREE_TYPE (args[0]),
3893                               args[0], args[1]);
3894 }
3895
3896 /* Bitwise not.  */
3897 static void
3898 gfc_conv_intrinsic_not (gfc_se * se, gfc_expr * expr)
3899 {
3900   tree arg;
3901
3902   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
3903   se->expr = fold_build1_loc (input_location, BIT_NOT_EXPR,
3904                               TREE_TYPE (arg), arg);
3905 }
3906
3907 /* Set or clear a single bit.  */
3908 static void
3909 gfc_conv_intrinsic_singlebitop (gfc_se * se, gfc_expr * expr, int set)
3910 {
3911   tree args[2];
3912   tree type;
3913   tree tmp;
3914   enum tree_code op;
3915
3916   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3917   type = TREE_TYPE (args[0]);
3918
3919   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
3920                          build_int_cst (type, 1), args[1]);
3921   if (set)
3922     op = BIT_IOR_EXPR;
3923   else
3924     {
3925       op = BIT_AND_EXPR;
3926       tmp = fold_build1_loc (input_location, BIT_NOT_EXPR, type, tmp);
3927     }
3928   se->expr = fold_build2_loc (input_location, op, type, args[0], tmp);
3929 }
3930
3931 /* Extract a sequence of bits.
3932     IBITS(I, POS, LEN) = (I >> POS) & ~((~0) << LEN).  */
3933 static void
3934 gfc_conv_intrinsic_ibits (gfc_se * se, gfc_expr * expr)
3935 {
3936   tree args[3];
3937   tree type;
3938   tree tmp;
3939   tree mask;
3940
3941   gfc_conv_intrinsic_function_args (se, expr, args, 3);
3942   type = TREE_TYPE (args[0]);
3943
3944   mask = build_int_cst (type, -1);
3945   mask = fold_build2_loc (input_location, LSHIFT_EXPR, type, mask, args[2]);
3946   mask = fold_build1_loc (input_location, BIT_NOT_EXPR, type, mask);
3947
3948   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, args[0], args[1]);
3949
3950   se->expr = fold_build2_loc (input_location, BIT_AND_EXPR, type, tmp, mask);
3951 }
3952
3953 static void
3954 gfc_conv_intrinsic_shift (gfc_se * se, gfc_expr * expr, bool right_shift,
3955                           bool arithmetic)
3956 {
3957   tree args[2], type, num_bits, cond;
3958
3959   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3960
3961   args[0] = gfc_evaluate_now (args[0], &se->pre);
3962   args[1] = gfc_evaluate_now (args[1], &se->pre);
3963   type = TREE_TYPE (args[0]);
3964
3965   if (!arithmetic)
3966     args[0] = fold_convert (unsigned_type_for (type), args[0]);
3967   else
3968     gcc_assert (right_shift);
3969
3970   se->expr = fold_build2_loc (input_location,
3971                               right_shift ? RSHIFT_EXPR : LSHIFT_EXPR,
3972                               TREE_TYPE (args[0]), args[0], args[1]);
3973
3974   if (!arithmetic)
3975     se->expr = fold_convert (type, se->expr);
3976
3977   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
3978      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
3979      special case.  */
3980   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
3981   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
3982                           args[1], num_bits);
3983
3984   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
3985                               build_int_cst (type, 0), se->expr);
3986 }
3987
3988 /* ISHFT (I, SHIFT) = (abs (shift) >= BIT_SIZE (i))
3989                         ? 0
3990                         : ((shift >= 0) ? i << shift : i >> -shift)
3991    where all shifts are logical shifts.  */
3992 static void
3993 gfc_conv_intrinsic_ishft (gfc_se * se, gfc_expr * expr)
3994 {
3995   tree args[2];
3996   tree type;
3997   tree utype;
3998   tree tmp;
3999   tree width;
4000   tree num_bits;
4001   tree cond;
4002   tree lshift;
4003   tree rshift;
4004
4005   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4006
4007   args[0] = gfc_evaluate_now (args[0], &se->pre);
4008   args[1] = gfc_evaluate_now (args[1], &se->pre);
4009
4010   type = TREE_TYPE (args[0]);
4011   utype = unsigned_type_for (type);
4012
4013   width = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (args[1]),
4014                            args[1]);
4015
4016   /* Left shift if positive.  */
4017   lshift = fold_build2_loc (input_location, LSHIFT_EXPR, type, args[0], width);
4018
4019   /* Right shift if negative.
4020      We convert to an unsigned type because we want a logical shift.
4021      The standard doesn't define the case of shifting negative
4022      numbers, and we try to be compatible with other compilers, most
4023      notably g77, here.  */
4024   rshift = fold_convert (type, fold_build2_loc (input_location, RSHIFT_EXPR,
4025                                     utype, convert (utype, args[0]), width));
4026
4027   tmp = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, args[1],
4028                          build_int_cst (TREE_TYPE (args[1]), 0));
4029   tmp = fold_build3_loc (input_location, COND_EXPR, type, tmp, lshift, rshift);
4030
4031   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
4032      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
4033      special case.  */
4034   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
4035   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, width,
4036                           num_bits);
4037   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
4038                               build_int_cst (type, 0), tmp);
4039 }
4040
4041
4042 /* Circular shift.  AKA rotate or barrel shift.  */
4043
4044 static void
4045 gfc_conv_intrinsic_ishftc (gfc_se * se, gfc_expr * expr)
4046 {
4047   tree *args;
4048   tree type;
4049   tree tmp;
4050   tree lrot;
4051   tree rrot;
4052   tree zero;
4053   unsigned int num_args;
4054
4055   num_args = gfc_intrinsic_argument_list_length (expr);
4056   args = XALLOCAVEC (tree, num_args);
4057
4058   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
4059
4060   if (num_args == 3)
4061     {
4062       /* Use a library function for the 3 parameter version.  */
4063       tree int4type = gfc_get_int_type (4);
4064
4065       type = TREE_TYPE (args[0]);
4066       /* We convert the first argument to at least 4 bytes, and
4067          convert back afterwards.  This removes the need for library
4068          functions for all argument sizes, and function will be
4069          aligned to at least 32 bits, so there's no loss.  */
4070       if (expr->ts.kind < 4)
4071         args[0] = convert (int4type, args[0]);
4072
4073       /* Convert the SHIFT and SIZE args to INTEGER*4 otherwise we would
4074          need loads of library  functions.  They cannot have values >
4075          BIT_SIZE (I) so the conversion is safe.  */
4076       args[1] = convert (int4type, args[1]);
4077       args[2] = convert (int4type, args[2]);
4078
4079       switch (expr->ts.kind)
4080         {
4081         case 1:
4082         case 2:
4083         case 4:
4084           tmp = gfor_fndecl_math_ishftc4;
4085           break;
4086         case 8:
4087           tmp = gfor_fndecl_math_ishftc8;
4088           break;
4089         case 16:
4090           tmp = gfor_fndecl_math_ishftc16;
4091           break;
4092         default:
4093           gcc_unreachable ();
4094         }
4095       se->expr = build_call_expr_loc (input_location,
4096                                       tmp, 3, args[0], args[1], args[2]);
4097       /* Convert the result back to the original type, if we extended
4098          the first argument's width above.  */
4099       if (expr->ts.kind < 4)
4100         se->expr = convert (type, se->expr);
4101
4102       return;
4103     }
4104   type = TREE_TYPE (args[0]);
4105
4106   /* Evaluate arguments only once.  */
4107   args[0] = gfc_evaluate_now (args[0], &se->pre);
4108   args[1] = gfc_evaluate_now (args[1], &se->pre);
4109
4110   /* Rotate left if positive.  */
4111   lrot = fold_build2_loc (input_location, LROTATE_EXPR, type, args[0], args[1]);
4112
4113   /* Rotate right if negative.  */
4114   tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (args[1]),
4115                          args[1]);
4116   rrot = fold_build2_loc (input_location,RROTATE_EXPR, type, args[0], tmp);
4117
4118   zero = build_int_cst (TREE_TYPE (args[1]), 0);
4119   tmp = fold_build2_loc (input_location, GT_EXPR, boolean_type_node, args[1],
4120                          zero);
4121   rrot = fold_build3_loc (input_location, COND_EXPR, type, tmp, lrot, rrot);
4122
4123   /* Do nothing if shift == 0.  */
4124   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, args[1],
4125                          zero);
4126   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, args[0],
4127                               rrot);
4128 }
4129
4130
4131 /* LEADZ (i) = (i == 0) ? BIT_SIZE (i)
4132                         : __builtin_clz(i) - (BIT_SIZE('int') - BIT_SIZE(i))
4133
4134    The conditional expression is necessary because the result of LEADZ(0)
4135    is defined, but the result of __builtin_clz(0) is undefined for most
4136    targets.
4137
4138    For INTEGER kinds smaller than the C 'int' type, we have to subtract the
4139    difference in bit size between the argument of LEADZ and the C int.  */
4140  
4141 static void
4142 gfc_conv_intrinsic_leadz (gfc_se * se, gfc_expr * expr)
4143 {
4144   tree arg;
4145   tree arg_type;
4146   tree cond;
4147   tree result_type;
4148   tree leadz;
4149   tree bit_size;
4150   tree tmp;
4151   tree func;
4152   int s, argsize;
4153
4154   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4155   argsize = TYPE_PRECISION (TREE_TYPE (arg));
4156
4157   /* Which variant of __builtin_clz* should we call?  */
4158   if (argsize <= INT_TYPE_SIZE)
4159     {
4160       arg_type = unsigned_type_node;
4161       func = builtin_decl_explicit (BUILT_IN_CLZ);
4162     }
4163   else if (argsize <= LONG_TYPE_SIZE)
4164     {
4165       arg_type = long_unsigned_type_node;
4166       func = builtin_decl_explicit (BUILT_IN_CLZL);
4167     }
4168   else if (argsize <= LONG_LONG_TYPE_SIZE)
4169     {
4170       arg_type = long_long_unsigned_type_node;
4171       func = builtin_decl_explicit (BUILT_IN_CLZLL);
4172     }
4173   else
4174     {
4175       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
4176       arg_type = gfc_build_uint_type (argsize);
4177       func = NULL_TREE;
4178     }
4179
4180   /* Convert the actual argument twice: first, to the unsigned type of the
4181      same size; then, to the proper argument type for the built-in
4182      function.  But the return type is of the default INTEGER kind.  */
4183   arg = fold_convert (gfc_build_uint_type (argsize), arg);
4184   arg = fold_convert (arg_type, arg);
4185   arg = gfc_evaluate_now (arg, &se->pre);
4186   result_type = gfc_get_int_type (gfc_default_integer_kind);
4187
4188   /* Compute LEADZ for the case i .ne. 0.  */
4189   if (func)
4190     {
4191       s = TYPE_PRECISION (arg_type) - argsize;
4192       tmp = fold_convert (result_type,
4193                           build_call_expr_loc (input_location, func,
4194                                                1, arg));
4195       leadz = fold_build2_loc (input_location, MINUS_EXPR, result_type,
4196                                tmp, build_int_cst (result_type, s));
4197     }
4198   else
4199     {
4200       /* We end up here if the argument type is larger than 'long long'.
4201          We generate this code:
4202   
4203             if (x & (ULL_MAX << ULL_SIZE) != 0)
4204               return clzll ((unsigned long long) (x >> ULLSIZE));
4205             else
4206               return ULL_SIZE + clzll ((unsigned long long) x);
4207          where ULL_MAX is the largest value that a ULL_MAX can hold
4208          (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
4209          is the bit-size of the long long type (64 in this example).  */
4210       tree ullsize, ullmax, tmp1, tmp2, btmp;
4211
4212       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
4213       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
4214                                 long_long_unsigned_type_node,
4215                                 build_int_cst (long_long_unsigned_type_node,
4216                                                0));
4217
4218       cond = fold_build2_loc (input_location, LSHIFT_EXPR, arg_type,
4219                               fold_convert (arg_type, ullmax), ullsize);
4220       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type,
4221                               arg, cond);
4222       cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
4223                               cond, build_int_cst (arg_type, 0));
4224
4225       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
4226                               arg, ullsize);
4227       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
4228       btmp = builtin_decl_explicit (BUILT_IN_CLZLL);
4229       tmp1 = fold_convert (result_type,
4230                            build_call_expr_loc (input_location, btmp, 1, tmp1));
4231
4232       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
4233       btmp = builtin_decl_explicit (BUILT_IN_CLZLL);
4234       tmp2 = fold_convert (result_type,
4235                            build_call_expr_loc (input_location, btmp, 1, tmp2));
4236       tmp2 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
4237                               tmp2, ullsize);
4238
4239       leadz = fold_build3_loc (input_location, COND_EXPR, result_type,
4240                                cond, tmp1, tmp2);
4241     }
4242
4243   /* Build BIT_SIZE.  */
4244   bit_size = build_int_cst (result_type, argsize);
4245
4246   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
4247                           arg, build_int_cst (arg_type, 0));
4248   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
4249                               bit_size, leadz);
4250 }
4251
4252
4253 /* TRAILZ(i) = (i == 0) ? BIT_SIZE (i) : __builtin_ctz(i)
4254
4255    The conditional expression is necessary because the result of TRAILZ(0)
4256    is defined, but the result of __builtin_ctz(0) is undefined for most
4257    targets.  */
4258  
4259 static void
4260 gfc_conv_intrinsic_trailz (gfc_se * se, gfc_expr *expr)
4261 {
4262   tree arg;
4263   tree arg_type;
4264   tree cond;
4265   tree result_type;
4266   tree trailz;
4267   tree bit_size;
4268   tree func;
4269   int argsize;
4270
4271   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4272   argsize = TYPE_PRECISION (TREE_TYPE (arg));
4273
4274   /* Which variant of __builtin_ctz* should we call?  */
4275   if (argsize <= INT_TYPE_SIZE)
4276     {
4277       arg_type = unsigned_type_node;
4278       func = builtin_decl_explicit (BUILT_IN_CTZ);
4279     }
4280   else if (argsize <= LONG_TYPE_SIZE)
4281     {
4282       arg_type = long_unsigned_type_node;
4283       func = builtin_decl_explicit (BUILT_IN_CTZL);
4284     }
4285   else if (argsize <= LONG_LONG_TYPE_SIZE)
4286     {
4287       arg_type = long_long_unsigned_type_node;
4288       func = builtin_decl_explicit (BUILT_IN_CTZLL);
4289     }
4290   else
4291     {
4292       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
4293       arg_type = gfc_build_uint_type (argsize);
4294       func = NULL_TREE;
4295     }
4296
4297   /* Convert the actual argument twice: first, to the unsigned type of the
4298      same size; then, to the proper argument type for the built-in
4299      function.  But the return type is of the default INTEGER kind.  */
4300   arg = fold_convert (gfc_build_uint_type (argsize), arg);
4301   arg = fold_convert (arg_type, arg);
4302   arg = gfc_evaluate_now (arg, &se->pre);
4303   result_type = gfc_get_int_type (gfc_default_integer_kind);
4304
4305   /* Compute TRAILZ for the case i .ne. 0.  */
4306   if (func)
4307     trailz = fold_convert (result_type, build_call_expr_loc (input_location,
4308                                                              func, 1, arg));
4309   else
4310     {
4311       /* We end up here if the argument type is larger than 'long long'.
4312          We generate this code:
4313   
4314             if ((x & ULL_MAX) == 0)
4315               return ULL_SIZE + ctzll ((unsigned long long) (x >> ULLSIZE));
4316             else
4317               return ctzll ((unsigned long long) x);
4318
4319          where ULL_MAX is the largest value that a ULL_MAX can hold
4320          (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
4321          is the bit-size of the long long type (64 in this example).  */
4322       tree ullsize, ullmax, tmp1, tmp2, btmp;
4323
4324       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
4325       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
4326                                 long_long_unsigned_type_node,
4327                                 build_int_cst (long_long_unsigned_type_node, 0));
4328
4329       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type, arg,
4330                               fold_convert (arg_type, ullmax));
4331       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, cond,
4332                               build_int_cst (arg_type, 0));
4333
4334       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
4335                               arg, ullsize);
4336       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
4337       btmp = builtin_decl_explicit (BUILT_IN_CTZLL);
4338       tmp1 = fold_convert (result_type,
4339                            build_call_expr_loc (input_location, btmp, 1, tmp1));
4340       tmp1 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
4341                               tmp1, ullsize);
4342
4343       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
4344       btmp = builtin_decl_explicit (BUILT_IN_CTZLL);
4345       tmp2 = fold_convert (result_type,
4346                            build_call_expr_loc (input_location, btmp, 1, tmp2));
4347
4348       trailz = fold_build3_loc (input_location, COND_EXPR, result_type,
4349                                 cond, tmp1, tmp2);
4350     }
4351
4352   /* Build BIT_SIZE.  */
4353   bit_size = build_int_cst (result_type, argsize);
4354
4355   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
4356                           arg, build_int_cst (arg_type, 0));
4357   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
4358                               bit_size, trailz);
4359 }
4360
4361 /* Using __builtin_popcount for POPCNT and __builtin_parity for POPPAR;
4362    for types larger than "long long", we call the long long built-in for
4363    the lower and higher bits and combine the result.  */
4364  
4365 static void
4366 gfc_conv_intrinsic_popcnt_poppar (gfc_se * se, gfc_expr *expr, int parity)
4367 {
4368   tree arg;
4369   tree arg_type;
4370   tree result_type;
4371   tree func;
4372   int argsize;
4373
4374   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4375   argsize = TYPE_PRECISION (TREE_TYPE (arg));
4376   result_type = gfc_get_int_type (gfc_default_integer_kind);
4377
4378   /* Which variant of the builtin should we call?  */
4379   if (argsize <= INT_TYPE_SIZE)
4380     {
4381       arg_type = unsigned_type_node;
4382       func = builtin_decl_explicit (parity
4383                                     ? BUILT_IN_PARITY
4384                                     : BUILT_IN_POPCOUNT);
4385     }
4386   else if (argsize <= LONG_TYPE_SIZE)
4387     {
4388       arg_type = long_unsigned_type_node;
4389       func = builtin_decl_explicit (parity
4390                                     ? BUILT_IN_PARITYL
4391                                     : BUILT_IN_POPCOUNTL);
4392     }
4393   else if (argsize <= LONG_LONG_TYPE_SIZE)
4394     {
4395       arg_type = long_long_unsigned_type_node;
4396       func = builtin_decl_explicit (parity
4397                                     ? BUILT_IN_PARITYLL
4398                                     : BUILT_IN_POPCOUNTLL);
4399     }
4400   else
4401     {
4402       /* Our argument type is larger than 'long long', which mean none
4403          of the POPCOUNT builtins covers it.  We thus call the 'long long'
4404          variant multiple times, and add the results.  */
4405       tree utype, arg2, call1, call2;
4406
4407       /* For now, we only cover the case where argsize is twice as large
4408          as 'long long'.  */
4409       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
4410
4411       func = builtin_decl_explicit (parity
4412                                     ? BUILT_IN_PARITYLL
4413                                     : BUILT_IN_POPCOUNTLL);
4414
4415       /* Convert it to an integer, and store into a variable.  */
4416       utype = gfc_build_uint_type (argsize);
4417       arg = fold_convert (utype, arg);
4418       arg = gfc_evaluate_now (arg, &se->pre);
4419
4420       /* Call the builtin twice.  */
4421       call1 = build_call_expr_loc (input_location, func, 1,
4422                                    fold_convert (long_long_unsigned_type_node,
4423                                                  arg));
4424
4425       arg2 = fold_build2_loc (input_location, RSHIFT_EXPR, utype, arg,
4426                               build_int_cst (utype, LONG_LONG_TYPE_SIZE));
4427       call2 = build_call_expr_loc (input_location, func, 1,
4428                                    fold_convert (long_long_unsigned_type_node,
4429                                                  arg2));
4430                           
4431       /* Combine the results.  */
4432       if (parity)
4433         se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR, result_type,
4434                                     call1, call2);
4435       else
4436         se->expr = fold_build2_loc (input_location, PLUS_EXPR, result_type,
4437                                     call1, call2);
4438
4439       return;
4440     }
4441
4442   /* Convert the actual argument twice: first, to the unsigned type of the
4443      same size; then, to the proper argument type for the built-in
4444      function.  */
4445   arg = fold_convert (gfc_build_uint_type (argsize), arg);
4446   arg = fold_convert (arg_type, arg);
4447
4448   se->expr = fold_convert (result_type,
4449                            build_call_expr_loc (input_location, func, 1, arg));
4450 }
4451
4452
4453 /* Process an intrinsic with unspecified argument-types that has an optional
4454    argument (which could be of type character), e.g. EOSHIFT.  For those, we
4455    need to append the string length of the optional argument if it is not
4456    present and the type is really character.
4457    primary specifies the position (starting at 1) of the non-optional argument
4458    specifying the type and optional gives the position of the optional
4459    argument in the arglist.  */
4460
4461 static void
4462 conv_generic_with_optional_char_arg (gfc_se* se, gfc_expr* expr,
4463                                      unsigned primary, unsigned optional)
4464 {
4465   gfc_actual_arglist* prim_arg;
4466   gfc_actual_arglist* opt_arg;
4467   unsigned cur_pos;
4468   gfc_actual_arglist* arg;
4469   gfc_symbol* sym;
4470   VEC(tree,gc) *append_args;
4471
4472   /* Find the two arguments given as position.  */
4473   cur_pos = 0;
4474   prim_arg = NULL;
4475   opt_arg = NULL;
4476   for (arg = expr->value.function.actual; arg; arg = arg->next)
4477     {
4478       ++cur_pos;
4479
4480       if (cur_pos == primary)
4481         prim_arg = arg;
4482       if (cur_pos == optional)
4483         opt_arg = arg;
4484
4485       if (cur_pos >= primary && cur_pos >= optional)
4486         break;
4487     }
4488   gcc_assert (prim_arg);
4489   gcc_assert (prim_arg->expr);
4490   gcc_assert (opt_arg);
4491
4492   /* If we do have type CHARACTER and the optional argument is really absent,
4493      append a dummy 0 as string length.  */
4494   append_args = NULL;
4495   if (prim_arg->expr->ts.type == BT_CHARACTER && !opt_arg->expr)
4496     {
4497       tree dummy;
4498
4499       dummy = build_int_cst (gfc_charlen_type_node, 0);
4500       append_args = VEC_alloc (tree, gc, 1);
4501       VEC_quick_push (tree, append_args, dummy);
4502     }
4503
4504   /* Build the call itself.  */
4505   sym = gfc_get_symbol_for_expr (expr);
4506   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
4507                           append_args);
4508   free (sym);
4509 }
4510
4511
4512 /* The length of a character string.  */
4513 static void
4514 gfc_conv_intrinsic_len (gfc_se * se, gfc_expr * expr)
4515 {
4516   tree len;
4517   tree type;
4518   tree decl;
4519   gfc_symbol *sym;
4520   gfc_se argse;
4521   gfc_expr *arg;
4522   gfc_ss *ss;
4523
4524   gcc_assert (!se->ss);
4525
4526   arg = expr->value.function.actual->expr;
4527
4528   type = gfc_typenode_for_spec (&expr->ts);
4529   switch (arg->expr_type)
4530     {
4531     case EXPR_CONSTANT:
4532       len = build_int_cst (gfc_charlen_type_node, arg->value.character.length);
4533       break;
4534
4535     case EXPR_ARRAY:
4536       /* Obtain the string length from the function used by
4537          trans-array.c(gfc_trans_array_constructor).  */
4538       len = NULL_TREE;
4539       get_array_ctor_strlen (&se->pre, arg->value.constructor, &len);
4540       break;
4541
4542     case EXPR_VARIABLE:
4543       if (arg->ref == NULL
4544             || (arg->ref->next == NULL && arg->ref->type == REF_ARRAY))
4545         {
4546           /* This doesn't catch all cases.
4547              See http://gcc.gnu.org/ml/fortran/2004-06/msg00165.html
4548              and the surrounding thread.  */
4549           sym = arg->symtree->n.sym;
4550           decl = gfc_get_symbol_decl (sym);
4551           if (decl == current_function_decl && sym->attr.function
4552                 && (sym->result == sym))
4553             decl = gfc_get_fake_result_decl (sym, 0);
4554
4555           len = sym->ts.u.cl->backend_decl;
4556           gcc_assert (len);
4557           break;
4558         }
4559
4560       /* Otherwise fall through.  */
4561
4562     default:
4563       /* Anybody stupid enough to do this deserves inefficient code.  */
4564       ss = gfc_walk_expr (arg);
4565       gfc_init_se (&argse, se);
4566       if (ss == gfc_ss_terminator)
4567         gfc_conv_expr (&argse, arg);
4568       else
4569         gfc_conv_expr_descriptor (&argse, arg, ss);
4570       gfc_add_block_to_block (&se->pre, &argse.pre);
4571       gfc_add_block_to_block (&se->post, &argse.post);
4572       len = argse.string_length;
4573       break;
4574     }
4575   se->expr = convert (type, len);
4576 }
4577
4578 /* The length of a character string not including trailing blanks.  */
4579 static void
4580 gfc_conv_intrinsic_len_trim (gfc_se * se, gfc_expr * expr)
4581 {
4582   int kind = expr->value.function.actual->expr->ts.kind;
4583   tree args[2], type, fndecl;
4584
4585   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4586   type = gfc_typenode_for_spec (&expr->ts);
4587
4588   if (kind == 1)
4589     fndecl = gfor_fndecl_string_len_trim;
4590   else if (kind == 4)
4591     fndecl = gfor_fndecl_string_len_trim_char4;
4592   else
4593     gcc_unreachable ();
4594
4595   se->expr = build_call_expr_loc (input_location,
4596                               fndecl, 2, args[0], args[1]);
4597   se->expr = convert (type, se->expr);
4598 }
4599
4600
4601 /* Returns the starting position of a substring within a string.  */
4602
4603 static void
4604 gfc_conv_intrinsic_index_scan_verify (gfc_se * se, gfc_expr * expr,
4605                                       tree function)
4606 {
4607   tree logical4_type_node = gfc_get_logical_type (4);
4608   tree type;
4609   tree fndecl;
4610   tree *args;
4611   unsigned int num_args;
4612
4613   args = XALLOCAVEC (tree, 5);
4614
4615   /* Get number of arguments; characters count double due to the
4616      string length argument. Kind= is not passed to the library
4617      and thus ignored.  */
4618   if (expr->value.function.actual->next->next->expr == NULL)
4619     num_args = 4;
4620   else
4621     num_args = 5;
4622
4623   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
4624   type = gfc_typenode_for_spec (&expr->ts);
4625
4626   if (num_args == 4)
4627     args[4] = build_int_cst (logical4_type_node, 0);
4628   else
4629     args[4] = convert (logical4_type_node, args[4]);
4630
4631   fndecl = build_addr (function, current_function_decl);
4632   se->expr = build_call_array_loc (input_location,
4633                                TREE_TYPE (TREE_TYPE (function)), fndecl,
4634                                5, args);
4635   se->expr = convert (type, se->expr);
4636
4637 }
4638
4639 /* The ascii value for a single character.  */
4640 static void
4641 gfc_conv_intrinsic_ichar (gfc_se * se, gfc_expr * expr)
4642 {
4643   tree args[2], type, pchartype;
4644
4645   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4646   gcc_assert (POINTER_TYPE_P (TREE_TYPE (args[1])));
4647   pchartype = gfc_get_pchar_type (expr->value.function.actual->expr->ts.kind);
4648   args[1] = fold_build1_loc (input_location, NOP_EXPR, pchartype, args[1]);
4649   type = gfc_typenode_for_spec (&expr->ts);
4650
4651   se->expr = build_fold_indirect_ref_loc (input_location,
4652                                       args[1]);
4653   se->expr = convert (type, se->expr);
4654 }
4655
4656
4657 /* Intrinsic ISNAN calls __builtin_isnan.  */
4658
4659 static void
4660 gfc_conv_intrinsic_isnan (gfc_se * se, gfc_expr * expr)
4661 {
4662   tree arg;
4663
4664   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4665   se->expr = build_call_expr_loc (input_location,
4666                                   builtin_decl_explicit (BUILT_IN_ISNAN),
4667                                   1, arg);
4668   STRIP_TYPE_NOPS (se->expr);
4669   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
4670 }
4671
4672
4673 /* Intrinsics IS_IOSTAT_END and IS_IOSTAT_EOR just need to compare
4674    their argument against a constant integer value.  */
4675
4676 static void
4677 gfc_conv_has_intvalue (gfc_se * se, gfc_expr * expr, const int value)
4678 {
4679   tree arg;
4680
4681   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4682   se->expr = fold_build2_loc (input_location, EQ_EXPR,
4683                               gfc_typenode_for_spec (&expr->ts),
4684                               arg, build_int_cst (TREE_TYPE (arg), value));
4685 }
4686
4687
4688
4689 /* MERGE (tsource, fsource, mask) = mask ? tsource : fsource.  */
4690
4691 static void
4692 gfc_conv_intrinsic_merge (gfc_se * se, gfc_expr * expr)
4693 {
4694   tree tsource;
4695   tree fsource;
4696   tree mask;
4697   tree type;
4698   tree len, len2;
4699   tree *args;
4700   unsigned int num_args;
4701
4702   num_args = gfc_intrinsic_argument_list_length (expr);
4703   args = XALLOCAVEC (tree, num_args);
4704
4705   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
4706   if (expr->ts.type != BT_CHARACTER)
4707     {
4708       tsource = args[0];
4709       fsource = args[1];
4710       mask = args[2];
4711     }
4712   else
4713     {
4714       /* We do the same as in the non-character case, but the argument
4715          list is different because of the string length arguments. We
4716          also have to set the string length for the result.  */
4717       len = args[0];
4718       tsource = args[1];
4719       len2 = args[2];
4720       fsource = args[3];
4721       mask = args[4];
4722
4723       gfc_trans_same_strlen_check ("MERGE intrinsic", &expr->where, len, len2,
4724                                    &se->pre);
4725       se->string_length = len;
4726     }
4727   type = TREE_TYPE (tsource);
4728   se->expr = fold_build3_loc (input_location, COND_EXPR, type, mask, tsource,
4729                               fold_convert (type, fsource));
4730 }
4731
4732
4733 /* MERGE_BITS (I, J, MASK) = (I & MASK) | (I & (~MASK)).  */
4734
4735 static void
4736 gfc_conv_intrinsic_merge_bits (gfc_se * se, gfc_expr * expr)
4737 {
4738   tree args[3], mask, type;
4739
4740   gfc_conv_intrinsic_function_args (se, expr, args, 3);
4741   mask = gfc_evaluate_now (args[2], &se->pre);
4742
4743   type = TREE_TYPE (args[0]);
4744   gcc_assert (TREE_TYPE (args[1]) == type);
4745   gcc_assert (TREE_TYPE (mask) == type);
4746
4747   args[0] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], mask);
4748   args[1] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[1],
4749                              fold_build1_loc (input_location, BIT_NOT_EXPR,
4750                                               type, mask));
4751   se->expr = fold_build2_loc (input_location, BIT_IOR_EXPR, type,
4752                               args[0], args[1]);
4753 }
4754
4755
4756 /* MASKL(n)  =  n == 0 ? 0 : (~0) << (BIT_SIZE - n)
4757    MASKR(n)  =  n == BIT_SIZE ? ~0 : ~((~0) << n)  */
4758
4759 static void
4760 gfc_conv_intrinsic_mask (gfc_se * se, gfc_expr * expr, int left)
4761 {
4762   tree arg, allones, type, utype, res, cond, bitsize;
4763   int i;
4764  
4765   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4766   arg = gfc_evaluate_now (arg, &se->pre);
4767
4768   type = gfc_get_int_type (expr->ts.kind);
4769   utype = unsigned_type_for (type);
4770
4771   i = gfc_validate_kind (BT_INTEGER, expr->ts.kind, false);
4772   bitsize = build_int_cst (TREE_TYPE (arg), gfc_integer_kinds[i].bit_size);
4773
4774   allones = fold_build1_loc (input_location, BIT_NOT_EXPR, utype,
4775                              build_int_cst (utype, 0));
4776
4777   if (left)
4778     {
4779       /* Left-justified mask.  */
4780       res = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (arg),
4781                              bitsize, arg);
4782       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
4783                              fold_convert (utype, res));
4784
4785       /* Special case arg == 0, because SHIFT_EXPR wants a shift strictly
4786          smaller than type width.  */
4787       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, arg,
4788                               build_int_cst (TREE_TYPE (arg), 0));
4789       res = fold_build3_loc (input_location, COND_EXPR, utype, cond,
4790                              build_int_cst (utype, 0), res);
4791     }
4792   else
4793     {
4794       /* Right-justified mask.  */
4795       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
4796                              fold_convert (utype, arg));
4797       res = fold_build1_loc (input_location, BIT_NOT_EXPR, utype, res);
4798
4799       /* Special case agr == bit_size, because SHIFT_EXPR wants a shift
4800          strictly smaller than type width.  */
4801       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
4802                               arg, bitsize);
4803       res = fold_build3_loc (input_location, COND_EXPR, utype,
4804                              cond, allones, res);
4805     }
4806
4807   se->expr = fold_convert (type, res);
4808 }
4809
4810
4811 /* FRACTION (s) is translated into frexp (s, &dummy_int).  */
4812 static void
4813 gfc_conv_intrinsic_fraction (gfc_se * se, gfc_expr * expr)
4814 {
4815   tree arg, type, tmp, frexp;
4816
4817   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4818
4819   type = gfc_typenode_for_spec (&expr->ts);
4820   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4821   tmp = gfc_create_var (integer_type_node, NULL);
4822   se->expr = build_call_expr_loc (input_location, frexp, 2,
4823                                   fold_convert (type, arg),
4824                                   gfc_build_addr_expr (NULL_TREE, tmp));
4825   se->expr = fold_convert (type, se->expr);
4826 }
4827
4828
4829 /* NEAREST (s, dir) is translated into
4830      tmp = copysign (HUGE_VAL, dir);
4831      return nextafter (s, tmp);
4832  */
4833 static void
4834 gfc_conv_intrinsic_nearest (gfc_se * se, gfc_expr * expr)
4835 {
4836   tree args[2], type, tmp, nextafter, copysign, huge_val;
4837
4838   nextafter = gfc_builtin_decl_for_float_kind (BUILT_IN_NEXTAFTER, expr->ts.kind);
4839   copysign = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
4840
4841   type = gfc_typenode_for_spec (&expr->ts);
4842   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4843
4844   huge_val = gfc_build_inf_or_huge (type, expr->ts.kind);
4845   tmp = build_call_expr_loc (input_location, copysign, 2, huge_val,
4846                              fold_convert (type, args[1]));
4847   se->expr = build_call_expr_loc (input_location, nextafter, 2,
4848                                   fold_convert (type, args[0]), tmp);
4849   se->expr = fold_convert (type, se->expr);
4850 }
4851
4852
4853 /* SPACING (s) is translated into
4854     int e;
4855     if (s == 0)
4856       res = tiny;
4857     else
4858     {
4859       frexp (s, &e);
4860       e = e - prec;
4861       e = MAX_EXPR (e, emin);
4862       res = scalbn (1., e);
4863     }
4864     return res;
4865
4866  where prec is the precision of s, gfc_real_kinds[k].digits,
4867        emin is min_exponent - 1, gfc_real_kinds[k].min_exponent - 1,
4868    and tiny is tiny(s), gfc_real_kinds[k].tiny.  */
4869
4870 static void
4871 gfc_conv_intrinsic_spacing (gfc_se * se, gfc_expr * expr)
4872 {
4873   tree arg, type, prec, emin, tiny, res, e;
4874   tree cond, tmp, frexp, scalbn;
4875   int k;
4876   stmtblock_t block;
4877
4878   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
4879   prec = build_int_cst (integer_type_node, gfc_real_kinds[k].digits);
4880   emin = build_int_cst (integer_type_node, gfc_real_kinds[k].min_exponent - 1);
4881   tiny = gfc_conv_mpfr_to_tree (gfc_real_kinds[k].tiny, expr->ts.kind, 0);
4882
4883   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4884   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4885
4886   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4887   arg = gfc_evaluate_now (arg, &se->pre);
4888
4889   type = gfc_typenode_for_spec (&expr->ts);
4890   e = gfc_create_var (integer_type_node, NULL);
4891   res = gfc_create_var (type, NULL);
4892
4893
4894   /* Build the block for s /= 0.  */
4895   gfc_start_block (&block);
4896   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
4897                              gfc_build_addr_expr (NULL_TREE, e));
4898   gfc_add_expr_to_block (&block, tmp);
4899
4900   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node, e,
4901                          prec);
4902   gfc_add_modify (&block, e, fold_build2_loc (input_location, MAX_EXPR,
4903                                               integer_type_node, tmp, emin));
4904
4905   tmp = build_call_expr_loc (input_location, scalbn, 2,
4906                          build_real_from_int_cst (type, integer_one_node), e);
4907   gfc_add_modify (&block, res, tmp);
4908
4909   /* Finish by building the IF statement.  */
4910   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, arg,
4911                           build_real_from_int_cst (type, integer_zero_node));
4912   tmp = build3_v (COND_EXPR, cond, build2_v (MODIFY_EXPR, res, tiny),
4913                   gfc_finish_block (&block));
4914
4915   gfc_add_expr_to_block (&se->pre, tmp);
4916   se->expr = res;
4917 }
4918
4919
4920 /* RRSPACING (s) is translated into
4921       int e;
4922       real x;
4923       x = fabs (s);
4924       if (x != 0)
4925       {
4926         frexp (s, &e);
4927         x = scalbn (x, precision - e);
4928       }
4929       return x;
4930
4931  where precision is gfc_real_kinds[k].digits.  */
4932
4933 static void
4934 gfc_conv_intrinsic_rrspacing (gfc_se * se, gfc_expr * expr)
4935 {
4936   tree arg, type, e, x, cond, stmt, tmp, frexp, scalbn, fabs;
4937   int prec, k;
4938   stmtblock_t block;
4939
4940   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
4941   prec = gfc_real_kinds[k].digits;
4942
4943   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4944   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4945   fabs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
4946
4947   type = gfc_typenode_for_spec (&expr->ts);
4948   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4949   arg = gfc_evaluate_now (arg, &se->pre);
4950
4951   e = gfc_create_var (integer_type_node, NULL);
4952   x = gfc_create_var (type, NULL);
4953   gfc_add_modify (&se->pre, x,
4954                   build_call_expr_loc (input_location, fabs, 1, arg));
4955
4956
4957   gfc_start_block (&block);
4958   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
4959                              gfc_build_addr_expr (NULL_TREE, e));
4960   gfc_add_expr_to_block (&block, tmp);
4961
4962   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node,
4963                          build_int_cst (integer_type_node, prec), e);
4964   tmp = build_call_expr_loc (input_location, scalbn, 2, x, tmp);
4965   gfc_add_modify (&block, x, tmp);
4966   stmt = gfc_finish_block (&block);
4967
4968   cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, x,
4969                           build_real_from_int_cst (type, integer_zero_node));
4970   tmp = build3_v (COND_EXPR, cond, stmt, build_empty_stmt (input_location));
4971   gfc_add_expr_to_block (&se->pre, tmp);
4972
4973   se->expr = fold_convert (type, x);
4974 }
4975
4976
4977 /* SCALE (s, i) is translated into scalbn (s, i).  */
4978 static void
4979 gfc_conv_intrinsic_scale (gfc_se * se, gfc_expr * expr)
4980 {
4981   tree args[2], type, scalbn;
4982
4983   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4984
4985   type = gfc_typenode_for_spec (&expr->ts);
4986   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4987   se->expr = build_call_expr_loc (input_location, scalbn, 2,
4988                                   fold_convert (type, args[0]),
4989                                   fold_convert (integer_type_node, args[1]));
4990   se->expr = fold_convert (type, se->expr);
4991 }
4992
4993
4994 /* SET_EXPONENT (s, i) is translated into
4995    scalbn (frexp (s, &dummy_int), i).  */
4996 static void
4997 gfc_conv_intrinsic_set_exponent (gfc_se * se, gfc_expr * expr)
4998 {
4999   tree args[2], type, tmp, frexp, scalbn;
5000
5001   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
5002   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
5003
5004   type = gfc_typenode_for_spec (&expr->ts);
5005   gfc_conv_intrinsic_function_args (se, expr, args, 2);
5006
5007   tmp = gfc_create_var (integer_type_node, NULL);
5008   tmp = build_call_expr_loc (input_location, frexp, 2,
5009                              fold_convert (type, args[0]),
5010                              gfc_build_addr_expr (NULL_TREE, tmp));
5011   se->expr = build_call_expr_loc (input_location, scalbn, 2, tmp,
5012                                   fold_convert (integer_type_node, args[1]));
5013   se->expr = fold_convert (type, se->expr);
5014 }
5015
5016
5017 static void
5018 gfc_conv_intrinsic_size (gfc_se * se, gfc_expr * expr)
5019 {
5020   gfc_actual_arglist *actual;
5021   tree arg1;
5022   tree type;
5023   tree fncall0;
5024   tree fncall1;
5025   gfc_se argse;
5026   gfc_ss *ss;
5027
5028   gfc_init_se (&argse, NULL);
5029   actual = expr->value.function.actual;
5030
5031   if (actual->expr->ts.type == BT_CLASS)
5032     gfc_add_class_array_ref (actual->expr);
5033
5034   ss = gfc_walk_expr (actual->expr);
5035   gcc_assert (ss != gfc_ss_terminator);
5036   argse.want_pointer = 1;
5037   argse.data_not_needed = 1;
5038   gfc_conv_expr_descriptor (&argse, actual->expr, ss);
5039   gfc_add_block_to_block (&se->pre, &argse.pre);
5040   gfc_add_block_to_block (&se->post, &argse.post);
5041   arg1 = gfc_evaluate_now (argse.expr, &se->pre);
5042
5043   /* Build the call to size0.  */
5044   fncall0 = build_call_expr_loc (input_location,
5045                              gfor_fndecl_size0, 1, arg1);
5046
5047   actual = actual->next;
5048
5049   if (actual->expr)
5050     {
5051       gfc_init_se (&argse, NULL);
5052       gfc_conv_expr_type (&argse, actual->expr,
5053                           gfc_array_index_type);
5054       gfc_add_block_to_block (&se->pre, &argse.pre);
5055
5056       /* Unusually, for an intrinsic, size does not exclude
5057          an optional arg2, so we must test for it.  */  
5058       if (actual->expr->expr_type == EXPR_VARIABLE
5059             && actual->expr->symtree->n.sym->attr.dummy
5060             && actual->expr->symtree->n.sym->attr.optional)
5061         {
5062           tree tmp;
5063           /* Build the call to size1.  */
5064           fncall1 = build_call_expr_loc (input_location,
5065                                      gfor_fndecl_size1, 2,
5066                                      arg1, argse.expr);
5067
5068           gfc_init_se (&argse, NULL);
5069           argse.want_pointer = 1;
5070           argse.data_not_needed = 1;
5071           gfc_conv_expr (&argse, actual->expr);
5072           gfc_add_block_to_block (&se->pre, &argse.pre);
5073           tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
5074                                  argse.expr, null_pointer_node);
5075           tmp = gfc_evaluate_now (tmp, &se->pre);
5076           se->expr = fold_build3_loc (input_location, COND_EXPR,
5077                                       pvoid_type_node, tmp, fncall1, fncall0);
5078         }
5079       else
5080         {
5081           se->expr = NULL_TREE;
5082           argse.expr = fold_build2_loc (input_location, MINUS_EXPR,
5083                                         gfc_array_index_type,
5084                                         argse.expr, gfc_index_one_node);
5085         }
5086     }
5087   else if (expr->value.function.actual->expr->rank == 1)
5088     {
5089       argse.expr = gfc_index_zero_node;
5090       se->expr = NULL_TREE;
5091     }
5092   else
5093     se->expr = fncall0;
5094
5095   if (se->expr == NULL_TREE)
5096     {
5097       tree ubound, lbound;
5098
5099       arg1 = build_fold_indirect_ref_loc (input_location,
5100                                       arg1);
5101       ubound = gfc_conv_descriptor_ubound_get (arg1, argse.expr);
5102       lbound = gfc_conv_descriptor_lbound_get (arg1, argse.expr);
5103       se->expr = fold_build2_loc (input_location, MINUS_EXPR,
5104                                   gfc_array_index_type, ubound, lbound);
5105       se->expr = fold_build2_loc (input_location, PLUS_EXPR,
5106                                   gfc_array_index_type,
5107                                   se->expr, gfc_index_one_node);
5108       se->expr = fold_build2_loc (input_location, MAX_EXPR,
5109                                   gfc_array_index_type, se->expr,
5110                                   gfc_index_zero_node);
5111     }
5112
5113   type = gfc_typenode_for_spec (&expr->ts);
5114   se->expr = convert (type, se->expr);
5115 }
5116
5117
5118 /* Helper function to compute the size of a character variable,
5119    excluding the terminating null characters.  The result has
5120    gfc_array_index_type type.  */
5121
5122 static tree
5123 size_of_string_in_bytes (int kind, tree string_length)
5124 {
5125   tree bytesize;
5126   int i = gfc_validate_kind (BT_CHARACTER, kind, false);
5127  
5128   bytesize = build_int_cst (gfc_array_index_type,
5129                             gfc_character_kinds[i].bit_size / 8);
5130
5131   return fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
5132                           bytesize,
5133                           fold_convert (gfc_array_index_type, string_length));
5134 }
5135
5136
5137 static void
5138 gfc_conv_intrinsic_sizeof (gfc_se *se, gfc_expr *expr)
5139 {
5140   gfc_expr *arg;
5141   gfc_ss *ss;
5142   gfc_se argse;
5143   tree source_bytes;
5144   tree type;
5145   tree tmp;
5146   tree lower;
5147   tree upper;
5148   int n;
5149
5150   arg = expr->value.function.actual->expr;
5151
5152   gfc_init_se (&argse, NULL);
5153   ss = gfc_walk_expr (arg);
5154
5155   if (ss == gfc_ss_terminator)
5156     {
5157       if (arg->ts.type == BT_CLASS)
5158         gfc_add_data_component (arg);
5159
5160       gfc_conv_expr_reference (&argse, arg);
5161
5162       type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
5163                                                  argse.expr));
5164
5165       /* Obtain the source word length.  */
5166       if (arg->ts.type == BT_CHARACTER)
5167         se->expr = size_of_string_in_bytes (arg->ts.kind,
5168                                             argse.string_length);
5169       else
5170         se->expr = fold_convert (gfc_array_index_type, size_in_bytes (type)); 
5171     }
5172   else
5173     {
5174       source_bytes = gfc_create_var (gfc_array_index_type, "bytes");
5175       argse.want_pointer = 0;
5176       gfc_conv_expr_descriptor (&argse, arg, ss);
5177       type = gfc_get_element_type (TREE_TYPE (argse.expr));
5178
5179       /* Obtain the argument's word length.  */
5180       if (arg->ts.type == BT_CHARACTER)
5181         tmp = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
5182       else
5183         tmp = fold_convert (gfc_array_index_type,
5184                             size_in_bytes (type)); 
5185       gfc_add_modify (&argse.pre, source_bytes, tmp);
5186
5187       /* Obtain the size of the array in bytes.  */
5188       for (n = 0; n < arg->rank; n++)
5189         {
5190           tree idx;
5191           idx = gfc_rank_cst[n];
5192           lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
5193           upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
5194           tmp = fold_build2_loc (input_location, MINUS_EXPR,
5195                                  gfc_array_index_type, upper, lower);
5196           tmp = fold_build2_loc (input_location, PLUS_EXPR,
5197                                  gfc_array_index_type, tmp, gfc_index_one_node);
5198           tmp = fold_build2_loc (input_location, MULT_EXPR,
5199                                  gfc_array_index_type, tmp, source_bytes);
5200           gfc_add_modify (&argse.pre, source_bytes, tmp);
5201         }
5202       se->expr = source_bytes;
5203     }
5204
5205   gfc_add_block_to_block (&se->pre, &argse.pre);
5206 }
5207
5208
5209 static void
5210 gfc_conv_intrinsic_storage_size (gfc_se *se, gfc_expr *expr)
5211 {
5212   gfc_expr *arg;
5213   gfc_ss *ss;
5214   gfc_se argse,eight;
5215   tree type, result_type, tmp;
5216
5217   arg = expr->value.function.actual->expr;
5218   gfc_init_se (&eight, NULL);
5219   gfc_conv_expr (&eight, gfc_get_int_expr (expr->ts.kind, NULL, 8));
5220   
5221   gfc_init_se (&argse, NULL);
5222   ss = gfc_walk_expr (arg);
5223   result_type = gfc_get_int_type (expr->ts.kind);
5224
5225   if (ss == gfc_ss_terminator)
5226     {
5227       if (arg->ts.type == BT_CLASS)
5228       {
5229         gfc_add_vptr_component (arg);
5230         gfc_add_size_component (arg);
5231         gfc_conv_expr (&argse, arg);
5232         tmp = fold_convert (result_type, argse.expr);
5233         goto done;
5234       }
5235
5236       gfc_conv_expr_reference (&argse, arg);
5237       type = TREE_TYPE (build_fold_indirect_ref_loc (input_location, 
5238                                                      argse.expr));
5239     }
5240   else
5241     {
5242       argse.want_pointer = 0;
5243       gfc_conv_expr_descriptor (&argse, arg, ss);
5244       type = gfc_get_element_type (TREE_TYPE (argse.expr));
5245     }
5246     
5247   /* Obtain the argument's word length.  */
5248   if (arg->ts.type == BT_CHARACTER)
5249     tmp = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
5250   else
5251     tmp = fold_convert (result_type, size_in_bytes (type)); 
5252
5253 done:
5254   se->expr = fold_build2_loc (input_location, MULT_EXPR, result_type, tmp,
5255                               eight.expr);
5256   gfc_add_block_to_block (&se->pre, &argse.pre);
5257 }
5258
5259
5260 /* Intrinsic string comparison functions.  */
5261
5262 static void
5263 gfc_conv_intrinsic_strcmp (gfc_se * se, gfc_expr * expr, enum tree_code op)
5264 {
5265   tree args[4];
5266
5267   gfc_conv_intrinsic_function_args (se, expr, args, 4);
5268
5269   se->expr
5270     = gfc_build_compare_string (args[0], args[1], args[2], args[3],
5271                                 expr->value.function.actual->expr->ts.kind,
5272                                 op);
5273   se->expr = fold_build2_loc (input_location, op,
5274                               gfc_typenode_for_spec (&expr->ts), se->expr,
5275                               build_int_cst (TREE_TYPE (se->expr), 0));
5276 }
5277
5278 /* Generate a call to the adjustl/adjustr library function.  */
5279 static void
5280 gfc_conv_intrinsic_adjust (gfc_se * se, gfc_expr * expr, tree fndecl)
5281 {
5282   tree args[3];
5283   tree len;
5284   tree type;
5285   tree var;
5286   tree tmp;
5287
5288   gfc_conv_intrinsic_function_args (se, expr, &args[1], 2);
5289   len = args[1];
5290
5291   type = TREE_TYPE (args[2]);
5292   var = gfc_conv_string_tmp (se, type, len);
5293   args[0] = var;
5294
5295   tmp = build_call_expr_loc (input_location,
5296                          fndecl, 3, args[0], args[1], args[2]);
5297   gfc_add_expr_to_block (&se->pre, tmp);
5298   se->expr = var;
5299   se->string_length = len;
5300 }
5301
5302
5303 /* Generate code for the TRANSFER intrinsic:
5304         For scalar results:
5305           DEST = TRANSFER (SOURCE, MOLD)
5306         where:
5307           typeof<DEST> = typeof<MOLD>
5308         and:
5309           MOLD is scalar.
5310
5311         For array results:
5312           DEST(1:N) = TRANSFER (SOURCE, MOLD[, SIZE])
5313         where:
5314           typeof<DEST> = typeof<MOLD>
5315         and:
5316           N = min (sizeof (SOURCE(:)), sizeof (DEST(:)),
5317               sizeof (DEST(0) * SIZE).  */
5318 static void
5319 gfc_conv_intrinsic_transfer (gfc_se * se, gfc_expr * expr)
5320 {
5321   tree tmp;
5322   tree tmpdecl;
5323   tree ptr;
5324   tree extent;
5325   tree source;
5326   tree source_type;
5327   tree source_bytes;
5328   tree mold_type;
5329   tree dest_word_len;
5330   tree size_words;
5331   tree size_bytes;
5332   tree upper;
5333   tree lower;
5334   tree stmt;
5335   gfc_actual_arglist *arg;
5336   gfc_se argse;
5337   gfc_ss *ss;
5338   gfc_array_info *info;
5339   stmtblock_t block;
5340   int n;
5341   bool scalar_mold;
5342
5343   info = NULL;
5344   if (se->loop)
5345     info = &se->ss->info->data.array;
5346
5347   /* Convert SOURCE.  The output from this stage is:-
5348         source_bytes = length of the source in bytes
5349         source = pointer to the source data.  */
5350   arg = expr->value.function.actual;
5351
5352   /* Ensure double transfer through LOGICAL preserves all
5353      the needed bits.  */
5354   if (arg->expr->expr_type == EXPR_FUNCTION
5355         && arg->expr->value.function.esym == NULL
5356         && arg->expr->value.function.isym != NULL
5357         && arg->expr->value.function.isym->id == GFC_ISYM_TRANSFER
5358         && arg->expr->ts.type == BT_LOGICAL
5359         && expr->ts.type != arg->expr->ts.type)
5360     arg->expr->value.function.name = "__transfer_in_transfer";
5361
5362   gfc_init_se (&argse, NULL);
5363   ss = gfc_walk_expr (arg->expr);
5364
5365   source_bytes = gfc_create_var (gfc_array_index_type, NULL);
5366
5367   /* Obtain the pointer to source and the length of source in bytes.  */
5368   if (ss == gfc_ss_terminator)
5369     {
5370       gfc_conv_expr_reference (&argse, arg->expr);
5371       source = argse.expr;
5372
5373       source_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
5374                                                         argse.expr));
5375
5376       /* Obtain the source word length.  */
5377       if (arg->expr->ts.type == BT_CHARACTER)
5378         tmp = size_of_string_in_bytes (arg->expr->ts.kind,
5379                                        argse.string_length);
5380       else
5381         tmp = fold_convert (gfc_array_index_type,
5382                             size_in_bytes (source_type)); 
5383     }
5384   else
5385     {
5386       argse.want_pointer = 0;
5387       gfc_conv_expr_descriptor (&argse, arg->expr, ss);
5388       source = gfc_conv_descriptor_data_get (argse.expr);
5389       source_type = gfc_get_element_type (TREE_TYPE (argse.expr));
5390
5391       /* Repack the source if not a full variable array.  */
5392       if (arg->expr->expr_type == EXPR_VARIABLE
5393               && arg->expr->ref->u.ar.type != AR_FULL)
5394         {
5395           tmp = gfc_build_addr_expr (NULL_TREE, argse.expr);
5396
5397           if (gfc_option.warn_array_temp)
5398             gfc_warning ("Creating array temporary at %L", &expr->where);
5399
5400           source = build_call_expr_loc (input_location,
5401                                     gfor_fndecl_in_pack, 1, tmp);
5402           source = gfc_evaluate_now (source, &argse.pre);
5403
5404           /* Free the temporary.  */
5405           gfc_start_block (&block);
5406           tmp = gfc_call_free (convert (pvoid_type_node, source));
5407           gfc_add_expr_to_block (&block, tmp);
5408           stmt = gfc_finish_block (&block);
5409
5410           /* Clean up if it was repacked.  */
5411           gfc_init_block (&block);
5412           tmp = gfc_conv_array_data (argse.expr);
5413           tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
5414                                  source, tmp);
5415           tmp = build3_v (COND_EXPR, tmp, stmt,
5416                           build_empty_stmt (input_location));
5417           gfc_add_expr_to_block (&block, tmp);
5418           gfc_add_block_to_block (&block, &se->post);
5419           gfc_init_block (&se->post);
5420           gfc_add_block_to_block (&se->post, &block);
5421         }
5422
5423       /* Obtain the source word length.  */
5424       if (arg->expr->ts.type == BT_CHARACTER)
5425         tmp = size_of_string_in_bytes (arg->expr->ts.kind,
5426                                        argse.string_length);
5427       else
5428         tmp = fold_convert (gfc_array_index_type,
5429                             size_in_bytes (source_type)); 
5430
5431       /* Obtain the size of the array in bytes.  */
5432       extent = gfc_create_var (gfc_array_index_type, NULL);
5433       for (n = 0; n < arg->expr->rank; n++)
5434         {
5435           tree idx;
5436           idx = gfc_rank_cst[n];
5437           gfc_add_modify (&argse.pre, source_bytes, tmp);
5438           lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
5439           upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
5440           tmp = fold_build2_loc (input_location, MINUS_EXPR,
5441                                  gfc_array_index_type, upper, lower);
5442           gfc_add_modify (&argse.pre, extent, tmp);
5443           tmp = fold_build2_loc (input_location, PLUS_EXPR,
5444                                  gfc_array_index_type, extent,
5445                                  gfc_index_one_node);
5446           tmp = fold_build2_loc (input_location, MULT_EXPR,
5447                                  gfc_array_index_type, tmp, source_bytes);
5448         }
5449     }
5450
5451   gfc_add_modify (&argse.pre, source_bytes, tmp);
5452   gfc_add_block_to_block (&se->pre, &argse.pre);
5453   gfc_add_block_to_block (&se->post, &argse.post);
5454
5455   /* Now convert MOLD.  The outputs are:
5456         mold_type = the TREE type of MOLD
5457         dest_word_len = destination word length in bytes.  */
5458   arg = arg->next;
5459
5460   gfc_init_se (&argse, NULL);
5461   ss = gfc_walk_expr (arg->expr);
5462
5463   scalar_mold = arg->expr->rank == 0;
5464
5465   if (ss == gfc_ss_terminator)
5466     {
5467       gfc_conv_expr_reference (&argse, arg->expr);
5468       mold_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
5469                                                       argse.expr));
5470     }
5471   else
5472     {
5473       gfc_init_se (&argse, NULL);
5474       argse.want_pointer = 0;
5475       gfc_conv_expr_descriptor (&argse, arg->expr, ss);
5476       mold_type = gfc_get_element_type (TREE_TYPE (argse.expr));
5477     }
5478
5479   gfc_add_block_to_block (&se->pre, &argse.pre);
5480   gfc_add_block_to_block (&se->post, &argse.post);
5481
5482   if (strcmp (expr->value.function.name, "__transfer_in_transfer") == 0)
5483     {
5484       /* If this TRANSFER is nested in another TRANSFER, use a type
5485          that preserves all bits.  */
5486       if (arg->expr->ts.type == BT_LOGICAL)
5487         mold_type = gfc_get_int_type (arg->expr->ts.kind);
5488     }
5489
5490   if (arg->expr->ts.type == BT_CHARACTER)
5491     {
5492       tmp = size_of_string_in_bytes (arg->expr->ts.kind, argse.string_length);
5493       mold_type = gfc_get_character_type_len (arg->expr->ts.kind, tmp);
5494     }
5495   else
5496     tmp = fold_convert (gfc_array_index_type,
5497                         size_in_bytes (mold_type)); 
5498  
5499   dest_word_len = gfc_create_var (gfc_array_index_type, NULL);
5500   gfc_add_modify (&se->pre, dest_word_len, tmp);
5501
5502   /* Finally convert SIZE, if it is present.  */
5503   arg = arg->next;
5504   size_words = gfc_create_var (gfc_array_index_type, NULL);
5505
5506   if (arg->expr)
5507     {
5508       gfc_init_se (&argse, NULL);
5509       gfc_conv_expr_reference (&argse, arg->expr);
5510       tmp = convert (gfc_array_index_type,
5511                      build_fold_indirect_ref_loc (input_location,
5512                                               argse.expr));
5513       gfc_add_block_to_block (&se->pre, &argse.pre);
5514       gfc_add_block_to_block (&se->post, &argse.post);
5515     }
5516   else
5517     tmp = NULL_TREE;
5518
5519   /* Separate array and scalar results.  */
5520   if (scalar_mold && tmp == NULL_TREE)
5521     goto scalar_transfer;
5522
5523   size_bytes = gfc_create_var (gfc_array_index_type, NULL);
5524   if (tmp != NULL_TREE)
5525     tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
5526                            tmp, dest_word_len);
5527   else
5528     tmp = source_bytes;
5529
5530   gfc_add_modify (&se->pre, size_bytes, tmp);
5531   gfc_add_modify (&se->pre, size_words,
5532                        fold_build2_loc (input_location, CEIL_DIV_EXPR,
5533                                         gfc_array_index_type,
5534                                         size_bytes, dest_word_len));
5535
5536   /* Evaluate the bounds of the result.  If the loop range exists, we have
5537      to check if it is too large.  If so, we modify loop->to be consistent
5538      with min(size, size(source)).  Otherwise, size is made consistent with
5539      the loop range, so that the right number of bytes is transferred.*/
5540   n = se->loop->order[0];
5541   if (se->loop->to[n] != NULL_TREE)
5542     {
5543       tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5544                              se->loop->to[n], se->loop->from[n]);
5545       tmp = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
5546                              tmp, gfc_index_one_node);
5547       tmp = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
5548                          tmp, size_words);
5549       gfc_add_modify (&se->pre, size_words, tmp);
5550       gfc_add_modify (&se->pre, size_bytes,
5551                            fold_build2_loc (input_location, MULT_EXPR,
5552                                             gfc_array_index_type,
5553                                             size_words, dest_word_len));
5554       upper = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
5555                                size_words, se->loop->from[n]);
5556       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5557                                upper, gfc_index_one_node);
5558     }
5559   else
5560     {
5561       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5562                                size_words, gfc_index_one_node);
5563       se->loop->from[n] = gfc_index_zero_node;
5564     }
5565
5566   se->loop->to[n] = upper;
5567
5568   /* Build a destination descriptor, using the pointer, source, as the
5569      data field.  */
5570   gfc_trans_create_temp_array (&se->pre, &se->post, se->ss, mold_type,
5571                                NULL_TREE, false, true, false, &expr->where);
5572
5573   /* Cast the pointer to the result.  */
5574   tmp = gfc_conv_descriptor_data_get (info->descriptor);
5575   tmp = fold_convert (pvoid_type_node, tmp);
5576
5577   /* Use memcpy to do the transfer.  */
5578   tmp = build_call_expr_loc (input_location,
5579                          builtin_decl_explicit (BUILT_IN_MEMCPY),
5580                          3,
5581                          tmp,
5582                          fold_convert (pvoid_type_node, source),
5583                          fold_build2_loc (input_location, MIN_EXPR,
5584                                           gfc_array_index_type,
5585                                           size_bytes, source_bytes));
5586   gfc_add_expr_to_block (&se->pre, tmp);
5587
5588   se->expr = info->descriptor;
5589   if (expr->ts.type == BT_CHARACTER)
5590     se->string_length = fold_convert (gfc_charlen_type_node, dest_word_len);
5591
5592   return;
5593
5594 /* Deal with scalar results.  */
5595 scalar_transfer:
5596   extent = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
5597                             dest_word_len, source_bytes);
5598   extent = fold_build2_loc (input_location, MAX_EXPR, gfc_array_index_type,
5599                             extent, gfc_index_zero_node);
5600
5601   if (expr->ts.type == BT_CHARACTER)
5602     {
5603       tree direct;
5604       tree indirect;
5605
5606       ptr = convert (gfc_get_pchar_type (expr->ts.kind), source);
5607       tmpdecl = gfc_create_var (gfc_get_pchar_type (expr->ts.kind),
5608                                 "transfer");
5609
5610       /* If source is longer than the destination, use a pointer to
5611          the source directly.  */
5612       gfc_init_block (&block);
5613       gfc_add_modify (&block, tmpdecl, ptr);
5614       direct = gfc_finish_block (&block);
5615
5616       /* Otherwise, allocate a string with the length of the destination
5617          and copy the source into it.  */
5618       gfc_init_block (&block);
5619       tmp = gfc_get_pchar_type (expr->ts.kind);
5620       tmp = gfc_call_malloc (&block, tmp, dest_word_len);
5621       gfc_add_modify (&block, tmpdecl,
5622                       fold_convert (TREE_TYPE (ptr), tmp));
5623       tmp = build_call_expr_loc (input_location,
5624                              builtin_decl_explicit (BUILT_IN_MEMCPY), 3,
5625                              fold_convert (pvoid_type_node, tmpdecl),
5626                              fold_convert (pvoid_type_node, ptr),
5627                              extent);
5628       gfc_add_expr_to_block (&block, tmp);
5629       indirect = gfc_finish_block (&block);
5630
5631       /* Wrap it up with the condition.  */
5632       tmp = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
5633                              dest_word_len, source_bytes);
5634       tmp = build3_v (COND_EXPR, tmp, direct, indirect);
5635       gfc_add_expr_to_block (&se->pre, tmp);
5636
5637       se->expr = tmpdecl;
5638       se->string_length = dest_word_len;
5639     }
5640   else
5641     {
5642       tmpdecl = gfc_create_var (mold_type, "transfer");
5643
5644       ptr = convert (build_pointer_type (mold_type), source);
5645
5646       /* Use memcpy to do the transfer.  */
5647       tmp = gfc_build_addr_expr (NULL_TREE, tmpdecl);
5648       tmp = build_call_expr_loc (input_location,
5649                              builtin_decl_explicit (BUILT_IN_MEMCPY), 3,
5650                              fold_convert (pvoid_type_node, tmp),
5651                              fold_convert (pvoid_type_node, ptr),
5652                              extent);
5653       gfc_add_expr_to_block (&se->pre, tmp);
5654
5655       se->expr = tmpdecl;
5656     }
5657 }
5658
5659
5660 /* Generate code for the ALLOCATED intrinsic.
5661    Generate inline code that directly check the address of the argument.  */
5662
5663 static void
5664 gfc_conv_allocated (gfc_se *se, gfc_expr *expr)
5665 {
5666   gfc_actual_arglist *arg1;
5667   gfc_se arg1se;
5668   gfc_ss *ss1;
5669   tree tmp;
5670
5671   gfc_init_se (&arg1se, NULL);
5672   arg1 = expr->value.function.actual;
5673
5674   if (arg1->expr->ts.type == BT_CLASS)
5675     {
5676       /* Make sure that class array expressions have both a _data
5677          component reference and an array reference....  */
5678       if (CLASS_DATA (arg1->expr)->attr.dimension)
5679         gfc_add_class_array_ref (arg1->expr);
5680       /* .... whilst scalars only need the _data component.  */
5681       else
5682         gfc_add_data_component (arg1->expr);
5683     }
5684
5685   ss1 = gfc_walk_expr (arg1->expr);
5686
5687   if (ss1 == gfc_ss_terminator)
5688     {
5689       /* Allocatable scalar.  */
5690       arg1se.want_pointer = 1;
5691       gfc_conv_expr (&arg1se, arg1->expr);
5692       tmp = arg1se.expr;
5693     }
5694   else
5695     {
5696       /* Allocatable array.  */
5697       arg1se.descriptor_only = 1;
5698       gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5699       tmp = gfc_conv_descriptor_data_get (arg1se.expr);
5700     }
5701
5702   tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp,
5703                          fold_convert (TREE_TYPE (tmp), null_pointer_node));
5704   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
5705 }
5706
5707
5708 /* Generate code for the ASSOCIATED intrinsic.
5709    If both POINTER and TARGET are arrays, generate a call to library function
5710    _gfor_associated, and pass descriptors of POINTER and TARGET to it.
5711    In other cases, generate inline code that directly compare the address of
5712    POINTER with the address of TARGET.  */
5713
5714 static void
5715 gfc_conv_associated (gfc_se *se, gfc_expr *expr)
5716 {
5717   gfc_actual_arglist *arg1;
5718   gfc_actual_arglist *arg2;
5719   gfc_se arg1se;
5720   gfc_se arg2se;
5721   tree tmp2;
5722   tree tmp;
5723   tree nonzero_charlen;
5724   tree nonzero_arraylen;
5725   gfc_ss *ss1, *ss2;
5726
5727   gfc_init_se (&arg1se, NULL);
5728   gfc_init_se (&arg2se, NULL);
5729   arg1 = expr->value.function.actual;
5730   if (arg1->expr->ts.type == BT_CLASS)
5731     gfc_add_data_component (arg1->expr);
5732   arg2 = arg1->next;
5733   ss1 = gfc_walk_expr (arg1->expr);
5734
5735   if (!arg2->expr)
5736     {
5737       /* No optional target.  */
5738       if (ss1 == gfc_ss_terminator)
5739         {
5740           /* A pointer to a scalar.  */
5741           arg1se.want_pointer = 1;
5742           gfc_conv_expr (&arg1se, arg1->expr);
5743           tmp2 = arg1se.expr;
5744         }
5745       else
5746         {
5747           /* A pointer to an array.  */
5748           gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5749           tmp2 = gfc_conv_descriptor_data_get (arg1se.expr);
5750         }
5751       gfc_add_block_to_block (&se->pre, &arg1se.pre);
5752       gfc_add_block_to_block (&se->post, &arg1se.post);
5753       tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp2,
5754                              fold_convert (TREE_TYPE (tmp2), null_pointer_node));
5755       se->expr = tmp;
5756     }
5757   else
5758     {
5759       /* An optional target.  */
5760       if (arg2->expr->ts.type == BT_CLASS)
5761         gfc_add_data_component (arg2->expr);
5762       ss2 = gfc_walk_expr (arg2->expr);
5763
5764       nonzero_charlen = NULL_TREE;
5765       if (arg1->expr->ts.type == BT_CHARACTER)
5766         nonzero_charlen = fold_build2_loc (input_location, NE_EXPR,
5767                                            boolean_type_node,
5768                                            arg1->expr->ts.u.cl->backend_decl,
5769                                            integer_zero_node);
5770
5771       if (ss1 == gfc_ss_terminator)
5772         {
5773           /* A pointer to a scalar.  */
5774           gcc_assert (ss2 == gfc_ss_terminator);
5775           arg1se.want_pointer = 1;
5776           gfc_conv_expr (&arg1se, arg1->expr);
5777           arg2se.want_pointer = 1;
5778           gfc_conv_expr (&arg2se, arg2->expr);
5779           gfc_add_block_to_block (&se->pre, &arg1se.pre);
5780           gfc_add_block_to_block (&se->post, &arg1se.post);
5781           tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
5782                                  arg1se.expr, arg2se.expr);
5783           tmp2 = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
5784                                   arg1se.expr, null_pointer_node);
5785           se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5786                                       boolean_type_node, tmp, tmp2);
5787         }
5788       else
5789         {
5790           /* An array pointer of zero length is not associated if target is
5791              present.  */
5792           arg1se.descriptor_only = 1;
5793           gfc_conv_expr_lhs (&arg1se, arg1->expr);
5794           tmp = gfc_conv_descriptor_stride_get (arg1se.expr,
5795                                             gfc_rank_cst[arg1->expr->rank - 1]);
5796           nonzero_arraylen = fold_build2_loc (input_location, NE_EXPR,
5797                                               boolean_type_node, tmp,
5798                                               build_int_cst (TREE_TYPE (tmp), 0));
5799
5800           /* A pointer to an array, call library function _gfor_associated.  */
5801           gcc_assert (ss2 != gfc_ss_terminator);
5802           arg1se.want_pointer = 1;
5803           gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5804
5805           arg2se.want_pointer = 1;
5806           gfc_conv_expr_descriptor (&arg2se, arg2->expr, ss2);
5807           gfc_add_block_to_block (&se->pre, &arg2se.pre);
5808           gfc_add_block_to_block (&se->post, &arg2se.post);
5809           se->expr = build_call_expr_loc (input_location,
5810                                       gfor_fndecl_associated, 2,
5811                                       arg1se.expr, arg2se.expr);
5812           se->expr = convert (boolean_type_node, se->expr);
5813           se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5814                                       boolean_type_node, se->expr,
5815                                       nonzero_arraylen);
5816         }
5817
5818       /* If target is present zero character length pointers cannot
5819          be associated.  */
5820       if (nonzero_charlen != NULL_TREE)
5821         se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5822                                     boolean_type_node,
5823                                     se->expr, nonzero_charlen);
5824     }
5825
5826   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
5827 }
5828
5829
5830 /* Generate code for the SAME_TYPE_AS intrinsic.
5831    Generate inline code that directly checks the vindices.  */
5832
5833 static void
5834 gfc_conv_same_type_as (gfc_se *se, gfc_expr *expr)
5835 {
5836   gfc_expr *a, *b;
5837   gfc_se se1, se2;
5838   tree tmp;
5839
5840   gfc_init_se (&se1, NULL);
5841   gfc_init_se (&se2, NULL);
5842
5843   a = expr->value.function.actual->expr;
5844   b = expr->value.function.actual->next->expr;
5845
5846   if (a->ts.type == BT_CLASS)
5847     {
5848       gfc_add_vptr_component (a);
5849       gfc_add_hash_component (a);
5850     }
5851   else if (a->ts.type == BT_DERIVED)
5852     a = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5853                           a->ts.u.derived->hash_value);
5854
5855   if (b->ts.type == BT_CLASS)
5856     {
5857       gfc_add_vptr_component (b);
5858       gfc_add_hash_component (b);
5859     }
5860   else if (b->ts.type == BT_DERIVED)
5861     b = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5862                           b->ts.u.derived->hash_value);
5863
5864   gfc_conv_expr (&se1, a);
5865   gfc_conv_expr (&se2, b);
5866
5867   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
5868                          se1.expr, fold_convert (TREE_TYPE (se1.expr), se2.expr));
5869   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
5870 }
5871
5872
5873 /* Generate code for SELECTED_CHAR_KIND (NAME) intrinsic function.  */
5874
5875 static void
5876 gfc_conv_intrinsic_sc_kind (gfc_se *se, gfc_expr *expr)
5877 {
5878   tree args[2];
5879
5880   gfc_conv_intrinsic_function_args (se, expr, args, 2);
5881   se->expr = build_call_expr_loc (input_location,
5882                               gfor_fndecl_sc_kind, 2, args[0], args[1]);
5883   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
5884 }
5885
5886
5887 /* Generate code for SELECTED_INT_KIND (R) intrinsic function.  */
5888
5889 static void
5890 gfc_conv_intrinsic_si_kind (gfc_se *se, gfc_expr *expr)
5891 {
5892   tree arg, type;
5893
5894   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
5895
5896   /* The argument to SELECTED_INT_KIND is INTEGER(4).  */
5897   type = gfc_get_int_type (4); 
5898   arg = gfc_build_addr_expr (NULL_TREE, fold_convert (type, arg));
5899
5900   /* Convert it to the required type.  */
5901   type = gfc_typenode_for_spec (&expr->ts);
5902   se->expr = build_call_expr_loc (input_location,
5903                               gfor_fndecl_si_kind, 1, arg);
5904   se->expr = fold_convert (type, se->expr);
5905 }
5906
5907
5908 /* Generate code for SELECTED_REAL_KIND (P, R, RADIX) intrinsic function.  */
5909
5910 static void
5911 gfc_conv_intrinsic_sr_kind (gfc_se *se, gfc_expr *expr)
5912 {
5913   gfc_actual_arglist *actual;
5914   tree type;
5915   gfc_se argse;
5916   VEC(tree,gc) *args = NULL;
5917
5918   for (actual = expr->value.function.actual; actual; actual = actual->next)
5919     {
5920       gfc_init_se (&argse, se);
5921
5922       /* Pass a NULL pointer for an absent arg.  */
5923       if (actual->expr == NULL)
5924         argse.expr = null_pointer_node;
5925       else
5926         {
5927           gfc_typespec ts;
5928           gfc_clear_ts (&ts);
5929
5930           if (actual->expr->ts.kind != gfc_c_int_kind)
5931             {
5932               /* The arguments to SELECTED_REAL_KIND are INTEGER(4).  */
5933               ts.type = BT_INTEGER;
5934               ts.kind = gfc_c_int_kind;
5935               gfc_convert_type (actual->expr, &ts, 2);
5936             }
5937           gfc_conv_expr_reference (&argse, actual->expr);
5938         } 
5939
5940       gfc_add_block_to_block (&se->pre, &argse.pre);
5941       gfc_add_block_to_block (&se->post, &argse.post);
5942       VEC_safe_push (tree, gc, args, argse.expr);
5943     }
5944
5945   /* Convert it to the required type.  */
5946   type = gfc_typenode_for_spec (&expr->ts);
5947   se->expr = build_call_expr_loc_vec (input_location,
5948                                       gfor_fndecl_sr_kind, args);
5949   se->expr = fold_convert (type, se->expr);
5950 }
5951
5952
5953 /* Generate code for TRIM (A) intrinsic function.  */
5954
5955 static void
5956 gfc_conv_intrinsic_trim (gfc_se * se, gfc_expr * expr)
5957 {
5958   tree var;
5959   tree len;
5960   tree addr;
5961   tree tmp;
5962   tree cond;
5963   tree fndecl;
5964   tree function;
5965   tree *args;
5966   unsigned int num_args;
5967
5968   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
5969   args = XALLOCAVEC (tree, num_args);
5970
5971   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
5972   addr = gfc_build_addr_expr (ppvoid_type_node, var);
5973   len = gfc_create_var (gfc_charlen_type_node, "len");
5974
5975   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
5976   args[0] = gfc_build_addr_expr (NULL_TREE, len);
5977   args[1] = addr;
5978
5979   if (expr->ts.kind == 1)
5980     function = gfor_fndecl_string_trim;
5981   else if (expr->ts.kind == 4)
5982     function = gfor_fndecl_string_trim_char4;
5983   else
5984     gcc_unreachable ();
5985
5986   fndecl = build_addr (function, current_function_decl);
5987   tmp = build_call_array_loc (input_location,
5988                           TREE_TYPE (TREE_TYPE (function)), fndecl,
5989                           num_args, args);
5990   gfc_add_expr_to_block (&se->pre, tmp);
5991
5992   /* Free the temporary afterwards, if necessary.  */
5993   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
5994                           len, build_int_cst (TREE_TYPE (len), 0));
5995   tmp = gfc_call_free (var);
5996   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
5997   gfc_add_expr_to_block (&se->post, tmp);
5998
5999   se->expr = var;
6000   se->string_length = len;
6001 }
6002
6003
6004 /* Generate code for REPEAT (STRING, NCOPIES) intrinsic function.  */
6005
6006 static void
6007 gfc_conv_intrinsic_repeat (gfc_se * se, gfc_expr * expr)
6008 {
6009   tree args[3], ncopies, dest, dlen, src, slen, ncopies_type;
6010   tree type, cond, tmp, count, exit_label, n, max, largest;
6011   tree size;
6012   stmtblock_t block, body;
6013   int i;
6014
6015   /* We store in charsize the size of a character.  */
6016   i = gfc_validate_kind (BT_CHARACTER, expr->ts.kind, false);
6017   size = build_int_cst (size_type_node, gfc_character_kinds[i].bit_size / 8);
6018
6019   /* Get the arguments.  */
6020   gfc_conv_intrinsic_function_args (se, expr, args, 3);
6021   slen = fold_convert (size_type_node, gfc_evaluate_now (args[0], &se->pre));
6022   src = args[1];
6023   ncopies = gfc_evaluate_now (args[2], &se->pre);
6024   ncopies_type = TREE_TYPE (ncopies);
6025
6026   /* Check that NCOPIES is not negative.  */
6027   cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node, ncopies,
6028                           build_int_cst (ncopies_type, 0));
6029   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
6030                            "Argument NCOPIES of REPEAT intrinsic is negative "
6031                            "(its value is %ld)",
6032                            fold_convert (long_integer_type_node, ncopies));
6033
6034   /* If the source length is zero, any non negative value of NCOPIES
6035      is valid, and nothing happens.  */
6036   n = gfc_create_var (ncopies_type, "ncopies");
6037   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, slen,
6038                           build_int_cst (size_type_node, 0));
6039   tmp = fold_build3_loc (input_location, COND_EXPR, ncopies_type, cond,
6040                          build_int_cst (ncopies_type, 0), ncopies);
6041   gfc_add_modify (&se->pre, n, tmp);
6042   ncopies = n;
6043
6044   /* Check that ncopies is not too large: ncopies should be less than
6045      (or equal to) MAX / slen, where MAX is the maximal integer of
6046      the gfc_charlen_type_node type.  If slen == 0, we need a special
6047      case to avoid the division by zero.  */
6048   i = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
6049   max = gfc_conv_mpz_to_tree (gfc_integer_kinds[i].huge, gfc_charlen_int_kind);
6050   max = fold_build2_loc (input_location, TRUNC_DIV_EXPR, size_type_node,
6051                           fold_convert (size_type_node, max), slen);
6052   largest = TYPE_PRECISION (size_type_node) > TYPE_PRECISION (ncopies_type)
6053               ? size_type_node : ncopies_type;
6054   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
6055                           fold_convert (largest, ncopies),
6056                           fold_convert (largest, max));
6057   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, slen,
6058                          build_int_cst (size_type_node, 0));
6059   cond = fold_build3_loc (input_location, COND_EXPR, boolean_type_node, tmp,
6060                           boolean_false_node, cond);
6061   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
6062                            "Argument NCOPIES of REPEAT intrinsic is too large");
6063
6064   /* Compute the destination length.  */
6065   dlen = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
6066                           fold_convert (gfc_charlen_type_node, slen),
6067                           fold_convert (gfc_charlen_type_node, ncopies));
6068   type = gfc_get_character_type (expr->ts.kind, expr->ts.u.cl);
6069   dest = gfc_conv_string_tmp (se, build_pointer_type (type), dlen);
6070
6071   /* Generate the code to do the repeat operation:
6072        for (i = 0; i < ncopies; i++)
6073          memmove (dest + (i * slen * size), src, slen*size);  */
6074   gfc_start_block (&block);
6075   count = gfc_create_var (ncopies_type, "count");
6076   gfc_add_modify (&block, count, build_int_cst (ncopies_type, 0));
6077   exit_label = gfc_build_label_decl (NULL_TREE);
6078
6079   /* Start the loop body.  */
6080   gfc_start_block (&body);
6081
6082   /* Exit the loop if count >= ncopies.  */
6083   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, count,
6084                           ncopies);
6085   tmp = build1_v (GOTO_EXPR, exit_label);
6086   TREE_USED (exit_label) = 1;
6087   tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond, tmp,
6088                          build_empty_stmt (input_location));
6089   gfc_add_expr_to_block (&body, tmp);
6090
6091   /* Call memmove (dest + (i*slen*size), src, slen*size).  */
6092   tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
6093                          fold_convert (gfc_charlen_type_node, slen),
6094                          fold_convert (gfc_charlen_type_node, count));
6095   tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
6096                          tmp, fold_convert (gfc_charlen_type_node, size));
6097   tmp = fold_build_pointer_plus_loc (input_location,
6098                                      fold_convert (pvoid_type_node, dest), tmp);
6099   tmp = build_call_expr_loc (input_location,
6100                              builtin_decl_explicit (BUILT_IN_MEMMOVE),
6101                              3, tmp, src,
6102                              fold_build2_loc (input_location, MULT_EXPR,
6103                                               size_type_node, slen,
6104                                               fold_convert (size_type_node,
6105                                                             size)));
6106   gfc_add_expr_to_block (&body, tmp);
6107
6108   /* Increment count.  */
6109   tmp = fold_build2_loc (input_location, PLUS_EXPR, ncopies_type,
6110                          count, build_int_cst (TREE_TYPE (count), 1));
6111   gfc_add_modify (&body, count, tmp);
6112
6113   /* Build the loop.  */
6114   tmp = build1_v (LOOP_EXPR, gfc_finish_block (&body));
6115   gfc_add_expr_to_block (&block, tmp);
6116
6117   /* Add the exit label.  */
6118   tmp = build1_v (LABEL_EXPR, exit_label);
6119   gfc_add_expr_to_block (&block, tmp);
6120
6121   /* Finish the block.  */
6122   tmp = gfc_finish_block (&block);
6123   gfc_add_expr_to_block (&se->pre, tmp);
6124
6125   /* Set the result value.  */
6126   se->expr = dest;
6127   se->string_length = dlen;
6128 }
6129
6130
6131 /* Generate code for the IARGC intrinsic.  */
6132
6133 static void
6134 gfc_conv_intrinsic_iargc (gfc_se * se, gfc_expr * expr)
6135 {
6136   tree tmp;
6137   tree fndecl;
6138   tree type;
6139
6140   /* Call the library function.  This always returns an INTEGER(4).  */
6141   fndecl = gfor_fndecl_iargc;
6142   tmp = build_call_expr_loc (input_location,
6143                          fndecl, 0);
6144
6145   /* Convert it to the required type.  */
6146   type = gfc_typenode_for_spec (&expr->ts);
6147   tmp = fold_convert (type, tmp);
6148
6149   se->expr = tmp;
6150 }
6151
6152
6153 /* The loc intrinsic returns the address of its argument as
6154    gfc_index_integer_kind integer.  */
6155
6156 static void
6157 gfc_conv_intrinsic_loc (gfc_se * se, gfc_expr * expr)
6158 {
6159   tree temp_var;
6160   gfc_expr *arg_expr;
6161   gfc_ss *ss;
6162
6163   gcc_assert (!se->ss);
6164
6165   arg_expr = expr->value.function.actual->expr;
6166   ss = gfc_walk_expr (arg_expr);
6167   if (ss == gfc_ss_terminator)
6168     gfc_conv_expr_reference (se, arg_expr);
6169   else
6170     gfc_conv_array_parameter (se, arg_expr, ss, true, NULL, NULL, NULL);
6171   se->expr= convert (gfc_get_int_type (gfc_index_integer_kind), se->expr);
6172    
6173   /* Create a temporary variable for loc return value.  Without this, 
6174      we get an error an ICE in gcc/expr.c(expand_expr_addr_expr_1).  */
6175   temp_var = gfc_create_var (gfc_get_int_type (gfc_index_integer_kind), NULL);
6176   gfc_add_modify (&se->pre, temp_var, se->expr);
6177   se->expr = temp_var;
6178 }
6179
6180 /* Generate code for an intrinsic function.  Some map directly to library
6181    calls, others get special handling.  In some cases the name of the function
6182    used depends on the type specifiers.  */
6183
6184 void
6185 gfc_conv_intrinsic_function (gfc_se * se, gfc_expr * expr)
6186 {
6187   const char *name;
6188   int lib, kind;
6189   tree fndecl;
6190
6191   name = &expr->value.function.name[2];
6192
6193   if (expr->rank > 0)
6194     {
6195       lib = gfc_is_intrinsic_libcall (expr);
6196       if (lib != 0)
6197         {
6198           if (lib == 1)
6199             se->ignore_optional = 1;
6200
6201           switch (expr->value.function.isym->id)
6202             {
6203             case GFC_ISYM_EOSHIFT:
6204             case GFC_ISYM_PACK:
6205             case GFC_ISYM_RESHAPE:
6206               /* For all of those the first argument specifies the type and the
6207                  third is optional.  */
6208               conv_generic_with_optional_char_arg (se, expr, 1, 3);
6209               break;
6210
6211             default:
6212               gfc_conv_intrinsic_funcall (se, expr);
6213               break;
6214             }
6215
6216           return;
6217         }
6218     }
6219
6220   switch (expr->value.function.isym->id)
6221     {
6222     case GFC_ISYM_NONE:
6223       gcc_unreachable ();
6224
6225     case GFC_ISYM_REPEAT:
6226       gfc_conv_intrinsic_repeat (se, expr);
6227       break;
6228
6229     case GFC_ISYM_TRIM:
6230       gfc_conv_intrinsic_trim (se, expr);
6231       break;
6232
6233     case GFC_ISYM_SC_KIND:
6234       gfc_conv_intrinsic_sc_kind (se, expr);
6235       break;
6236
6237     case GFC_ISYM_SI_KIND:
6238       gfc_conv_intrinsic_si_kind (se, expr);
6239       break;
6240
6241     case GFC_ISYM_SR_KIND:
6242       gfc_conv_intrinsic_sr_kind (se, expr);
6243       break;
6244
6245     case GFC_ISYM_EXPONENT:
6246       gfc_conv_intrinsic_exponent (se, expr);
6247       break;
6248
6249     case GFC_ISYM_SCAN:
6250       kind = expr->value.function.actual->expr->ts.kind;
6251       if (kind == 1)
6252        fndecl = gfor_fndecl_string_scan;
6253       else if (kind == 4)
6254        fndecl = gfor_fndecl_string_scan_char4;
6255       else
6256        gcc_unreachable ();
6257
6258       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
6259       break;
6260
6261     case GFC_ISYM_VERIFY:
6262       kind = expr->value.function.actual->expr->ts.kind;
6263       if (kind == 1)
6264        fndecl = gfor_fndecl_string_verify;
6265       else if (kind == 4)
6266        fndecl = gfor_fndecl_string_verify_char4;
6267       else
6268        gcc_unreachable ();
6269
6270       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
6271       break;
6272
6273     case GFC_ISYM_ALLOCATED:
6274       gfc_conv_allocated (se, expr);
6275       break;
6276
6277     case GFC_ISYM_ASSOCIATED:
6278       gfc_conv_associated(se, expr);
6279       break;
6280
6281     case GFC_ISYM_SAME_TYPE_AS:
6282       gfc_conv_same_type_as (se, expr);
6283       break;
6284
6285     case GFC_ISYM_ABS:
6286       gfc_conv_intrinsic_abs (se, expr);
6287       break;
6288
6289     case GFC_ISYM_ADJUSTL:
6290       if (expr->ts.kind == 1)
6291        fndecl = gfor_fndecl_adjustl;
6292       else if (expr->ts.kind == 4)
6293        fndecl = gfor_fndecl_adjustl_char4;
6294       else
6295        gcc_unreachable ();
6296
6297       gfc_conv_intrinsic_adjust (se, expr, fndecl);
6298       break;
6299
6300     case GFC_ISYM_ADJUSTR:
6301       if (expr->ts.kind == 1)
6302        fndecl = gfor_fndecl_adjustr;
6303       else if (expr->ts.kind == 4)
6304        fndecl = gfor_fndecl_adjustr_char4;
6305       else
6306        gcc_unreachable ();
6307
6308       gfc_conv_intrinsic_adjust (se, expr, fndecl);
6309       break;
6310
6311     case GFC_ISYM_AIMAG:
6312       gfc_conv_intrinsic_imagpart (se, expr);
6313       break;
6314
6315     case GFC_ISYM_AINT:
6316       gfc_conv_intrinsic_aint (se, expr, RND_TRUNC);
6317       break;
6318
6319     case GFC_ISYM_ALL:
6320       gfc_conv_intrinsic_anyall (se, expr, EQ_EXPR);
6321       break;
6322
6323     case GFC_ISYM_ANINT:
6324       gfc_conv_intrinsic_aint (se, expr, RND_ROUND);
6325       break;
6326
6327     case GFC_ISYM_AND:
6328       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
6329       break;
6330
6331     case GFC_ISYM_ANY:
6332       gfc_conv_intrinsic_anyall (se, expr, NE_EXPR);
6333       break;
6334
6335     case GFC_ISYM_BTEST:
6336       gfc_conv_intrinsic_btest (se, expr);
6337       break;
6338
6339     case GFC_ISYM_BGE:
6340       gfc_conv_intrinsic_bitcomp (se, expr, GE_EXPR);
6341       break;
6342
6343     case GFC_ISYM_BGT:
6344       gfc_conv_intrinsic_bitcomp (se, expr, GT_EXPR);
6345       break;
6346
6347     case GFC_ISYM_BLE:
6348       gfc_conv_intrinsic_bitcomp (se, expr, LE_EXPR);
6349       break;
6350
6351     case GFC_ISYM_BLT:
6352       gfc_conv_intrinsic_bitcomp (se, expr, LT_EXPR);
6353       break;
6354
6355     case GFC_ISYM_ACHAR:
6356     case GFC_ISYM_CHAR:
6357       gfc_conv_intrinsic_char (se, expr);
6358       break;
6359
6360     case GFC_ISYM_CONVERSION:
6361     case GFC_ISYM_REAL:
6362     case GFC_ISYM_LOGICAL:
6363     case GFC_ISYM_DBLE:
6364       gfc_conv_intrinsic_conversion (se, expr);
6365       break;
6366
6367       /* Integer conversions are handled separately to make sure we get the
6368          correct rounding mode.  */
6369     case GFC_ISYM_INT:
6370     case GFC_ISYM_INT2:
6371     case GFC_ISYM_INT8:
6372     case GFC_ISYM_LONG:
6373       gfc_conv_intrinsic_int (se, expr, RND_TRUNC);
6374       break;
6375
6376     case GFC_ISYM_NINT:
6377       gfc_conv_intrinsic_int (se, expr, RND_ROUND);
6378       break;
6379
6380     case GFC_ISYM_CEILING:
6381       gfc_conv_intrinsic_int (se, expr, RND_CEIL);
6382       break;
6383
6384     case GFC_ISYM_FLOOR:
6385       gfc_conv_intrinsic_int (se, expr, RND_FLOOR);
6386       break;
6387
6388     case GFC_ISYM_MOD:
6389       gfc_conv_intrinsic_mod (se, expr, 0);
6390       break;
6391
6392     case GFC_ISYM_MODULO:
6393       gfc_conv_intrinsic_mod (se, expr, 1);
6394       break;
6395
6396     case GFC_ISYM_CMPLX:
6397       gfc_conv_intrinsic_cmplx (se, expr, name[5] == '1');
6398       break;
6399
6400     case GFC_ISYM_COMMAND_ARGUMENT_COUNT:
6401       gfc_conv_intrinsic_iargc (se, expr);
6402       break;
6403
6404     case GFC_ISYM_COMPLEX:
6405       gfc_conv_intrinsic_cmplx (se, expr, 1);
6406       break;
6407
6408     case GFC_ISYM_CONJG:
6409       gfc_conv_intrinsic_conjg (se, expr);
6410       break;
6411
6412     case GFC_ISYM_COUNT:
6413       gfc_conv_intrinsic_count (se, expr);
6414       break;
6415
6416     case GFC_ISYM_CTIME:
6417       gfc_conv_intrinsic_ctime (se, expr);
6418       break;
6419
6420     case GFC_ISYM_DIM:
6421       gfc_conv_intrinsic_dim (se, expr);
6422       break;
6423
6424     case GFC_ISYM_DOT_PRODUCT:
6425       gfc_conv_intrinsic_dot_product (se, expr);
6426       break;
6427
6428     case GFC_ISYM_DPROD:
6429       gfc_conv_intrinsic_dprod (se, expr);
6430       break;
6431
6432     case GFC_ISYM_DSHIFTL:
6433       gfc_conv_intrinsic_dshift (se, expr, true);
6434       break;
6435
6436     case GFC_ISYM_DSHIFTR:
6437       gfc_conv_intrinsic_dshift (se, expr, false);
6438       break;
6439
6440     case GFC_ISYM_FDATE:
6441       gfc_conv_intrinsic_fdate (se, expr);
6442       break;
6443
6444     case GFC_ISYM_FRACTION:
6445       gfc_conv_intrinsic_fraction (se, expr);
6446       break;
6447
6448     case GFC_ISYM_IALL:
6449       gfc_conv_intrinsic_arith (se, expr, BIT_AND_EXPR, false);
6450       break;
6451
6452     case GFC_ISYM_IAND:
6453       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
6454       break;
6455
6456     case GFC_ISYM_IANY:
6457       gfc_conv_intrinsic_arith (se, expr, BIT_IOR_EXPR, false);
6458       break;
6459
6460     case GFC_ISYM_IBCLR:
6461       gfc_conv_intrinsic_singlebitop (se, expr, 0);
6462       break;
6463
6464     case GFC_ISYM_IBITS:
6465       gfc_conv_intrinsic_ibits (se, expr);
6466       break;
6467
6468     case GFC_ISYM_IBSET:
6469       gfc_conv_intrinsic_singlebitop (se, expr, 1);
6470       break;
6471
6472     case GFC_ISYM_IACHAR:
6473     case GFC_ISYM_ICHAR:
6474       /* We assume ASCII character sequence.  */
6475       gfc_conv_intrinsic_ichar (se, expr);
6476       break;
6477
6478     case GFC_ISYM_IARGC:
6479       gfc_conv_intrinsic_iargc (se, expr);
6480       break;
6481
6482     case GFC_ISYM_IEOR:
6483       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
6484       break;
6485
6486     case GFC_ISYM_INDEX:
6487       kind = expr->value.function.actual->expr->ts.kind;
6488       if (kind == 1)
6489        fndecl = gfor_fndecl_string_index;
6490       else if (kind == 4)
6491        fndecl = gfor_fndecl_string_index_char4;
6492       else
6493        gcc_unreachable ();
6494
6495       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
6496       break;
6497
6498     case GFC_ISYM_IOR:
6499       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
6500       break;
6501
6502     case GFC_ISYM_IPARITY:
6503       gfc_conv_intrinsic_arith (se, expr, BIT_XOR_EXPR, false);
6504       break;
6505
6506     case GFC_ISYM_IS_IOSTAT_END:
6507       gfc_conv_has_intvalue (se, expr, LIBERROR_END);
6508       break;
6509
6510     case GFC_ISYM_IS_IOSTAT_EOR:
6511       gfc_conv_has_intvalue (se, expr, LIBERROR_EOR);
6512       break;
6513
6514     case GFC_ISYM_ISNAN:
6515       gfc_conv_intrinsic_isnan (se, expr);
6516       break;
6517
6518     case GFC_ISYM_LSHIFT:
6519       gfc_conv_intrinsic_shift (se, expr, false, false);
6520       break;
6521
6522     case GFC_ISYM_RSHIFT:
6523       gfc_conv_intrinsic_shift (se, expr, true, true);
6524       break;
6525
6526     case GFC_ISYM_SHIFTA:
6527       gfc_conv_intrinsic_shift (se, expr, true, true);
6528       break;
6529
6530     case GFC_ISYM_SHIFTL:
6531       gfc_conv_intrinsic_shift (se, expr, false, false);
6532       break;
6533
6534     case GFC_ISYM_SHIFTR:
6535       gfc_conv_intrinsic_shift (se, expr, true, false);
6536       break;
6537
6538     case GFC_ISYM_ISHFT:
6539       gfc_conv_intrinsic_ishft (se, expr);
6540       break;
6541
6542     case GFC_ISYM_ISHFTC:
6543       gfc_conv_intrinsic_ishftc (se, expr);
6544       break;
6545
6546     case GFC_ISYM_LEADZ:
6547       gfc_conv_intrinsic_leadz (se, expr);
6548       break;
6549
6550     case GFC_ISYM_TRAILZ:
6551       gfc_conv_intrinsic_trailz (se, expr);
6552       break;
6553
6554     case GFC_ISYM_POPCNT:
6555       gfc_conv_intrinsic_popcnt_poppar (se, expr, 0);
6556       break;
6557
6558     case GFC_ISYM_POPPAR:
6559       gfc_conv_intrinsic_popcnt_poppar (se, expr, 1);
6560       break;
6561
6562     case GFC_ISYM_LBOUND:
6563       gfc_conv_intrinsic_bound (se, expr, 0);
6564       break;
6565
6566     case GFC_ISYM_LCOBOUND:
6567       conv_intrinsic_cobound (se, expr);
6568       break;
6569
6570     case GFC_ISYM_TRANSPOSE:
6571       /* The scalarizer has already been set up for reversed dimension access
6572          order ; now we just get the argument value normally.  */
6573       gfc_conv_expr (se, expr->value.function.actual->expr);
6574       break;
6575
6576     case GFC_ISYM_LEN:
6577       gfc_conv_intrinsic_len (se, expr);
6578       break;
6579
6580     case GFC_ISYM_LEN_TRIM:
6581       gfc_conv_intrinsic_len_trim (se, expr);
6582       break;
6583
6584     case GFC_ISYM_LGE:
6585       gfc_conv_intrinsic_strcmp (se, expr, GE_EXPR);
6586       break;
6587
6588     case GFC_ISYM_LGT:
6589       gfc_conv_intrinsic_strcmp (se, expr, GT_EXPR);
6590       break;
6591
6592     case GFC_ISYM_LLE:
6593       gfc_conv_intrinsic_strcmp (se, expr, LE_EXPR);
6594       break;
6595
6596     case GFC_ISYM_LLT:
6597       gfc_conv_intrinsic_strcmp (se, expr, LT_EXPR);
6598       break;
6599
6600     case GFC_ISYM_MASKL:
6601       gfc_conv_intrinsic_mask (se, expr, 1);
6602       break;
6603
6604     case GFC_ISYM_MASKR:
6605       gfc_conv_intrinsic_mask (se, expr, 0);
6606       break;
6607
6608     case GFC_ISYM_MAX:
6609       if (expr->ts.type == BT_CHARACTER)
6610         gfc_conv_intrinsic_minmax_char (se, expr, 1);
6611       else
6612         gfc_conv_intrinsic_minmax (se, expr, GT_EXPR);
6613       break;
6614
6615     case GFC_ISYM_MAXLOC:
6616       gfc_conv_intrinsic_minmaxloc (se, expr, GT_EXPR);
6617       break;
6618
6619     case GFC_ISYM_MAXVAL:
6620       gfc_conv_intrinsic_minmaxval (se, expr, GT_EXPR);
6621       break;
6622
6623     case GFC_ISYM_MERGE:
6624       gfc_conv_intrinsic_merge (se, expr);
6625       break;
6626
6627     case GFC_ISYM_MERGE_BITS:
6628       gfc_conv_intrinsic_merge_bits (se, expr);
6629       break;
6630
6631     case GFC_ISYM_MIN:
6632       if (expr->ts.type == BT_CHARACTER)
6633         gfc_conv_intrinsic_minmax_char (se, expr, -1);
6634       else
6635         gfc_conv_intrinsic_minmax (se, expr, LT_EXPR);
6636       break;
6637
6638     case GFC_ISYM_MINLOC:
6639       gfc_conv_intrinsic_minmaxloc (se, expr, LT_EXPR);
6640       break;
6641
6642     case GFC_ISYM_MINVAL:
6643       gfc_conv_intrinsic_minmaxval (se, expr, LT_EXPR);
6644       break;
6645
6646     case GFC_ISYM_NEAREST:
6647       gfc_conv_intrinsic_nearest (se, expr);
6648       break;
6649
6650     case GFC_ISYM_NORM2:
6651       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, true);
6652       break;
6653
6654     case GFC_ISYM_NOT:
6655       gfc_conv_intrinsic_not (se, expr);
6656       break;
6657
6658     case GFC_ISYM_OR:
6659       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
6660       break;
6661
6662     case GFC_ISYM_PARITY:
6663       gfc_conv_intrinsic_arith (se, expr, NE_EXPR, false);
6664       break;
6665
6666     case GFC_ISYM_PRESENT:
6667       gfc_conv_intrinsic_present (se, expr);
6668       break;
6669
6670     case GFC_ISYM_PRODUCT:
6671       gfc_conv_intrinsic_arith (se, expr, MULT_EXPR, false);
6672       break;
6673
6674     case GFC_ISYM_RRSPACING:
6675       gfc_conv_intrinsic_rrspacing (se, expr);
6676       break;
6677
6678     case GFC_ISYM_SET_EXPONENT:
6679       gfc_conv_intrinsic_set_exponent (se, expr);
6680       break;
6681
6682     case GFC_ISYM_SCALE:
6683       gfc_conv_intrinsic_scale (se, expr);
6684       break;
6685
6686     case GFC_ISYM_SIGN:
6687       gfc_conv_intrinsic_sign (se, expr);
6688       break;
6689
6690     case GFC_ISYM_SIZE:
6691       gfc_conv_intrinsic_size (se, expr);
6692       break;
6693
6694     case GFC_ISYM_SIZEOF:
6695     case GFC_ISYM_C_SIZEOF:
6696       gfc_conv_intrinsic_sizeof (se, expr);
6697       break;
6698
6699     case GFC_ISYM_STORAGE_SIZE:
6700       gfc_conv_intrinsic_storage_size (se, expr);
6701       break;
6702
6703     case GFC_ISYM_SPACING:
6704       gfc_conv_intrinsic_spacing (se, expr);
6705       break;
6706
6707     case GFC_ISYM_SUM:
6708       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, false);
6709       break;
6710
6711     case GFC_ISYM_TRANSFER:
6712       if (se->ss && se->ss->info->useflags)
6713         /* Access the previously obtained result.  */
6714         gfc_conv_tmp_array_ref (se);
6715       else
6716         gfc_conv_intrinsic_transfer (se, expr);
6717       break;
6718
6719     case GFC_ISYM_TTYNAM:
6720       gfc_conv_intrinsic_ttynam (se, expr);
6721       break;
6722
6723     case GFC_ISYM_UBOUND:
6724       gfc_conv_intrinsic_bound (se, expr, 1);
6725       break;
6726
6727     case GFC_ISYM_UCOBOUND:
6728       conv_intrinsic_cobound (se, expr);
6729       break;
6730
6731     case GFC_ISYM_XOR:
6732       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
6733       break;
6734
6735     case GFC_ISYM_LOC:
6736       gfc_conv_intrinsic_loc (se, expr);
6737       break;
6738
6739     case GFC_ISYM_THIS_IMAGE:
6740       /* For num_images() == 1, handle as LCOBOUND.  */
6741       if (expr->value.function.actual->expr
6742           && gfc_option.coarray == GFC_FCOARRAY_SINGLE)
6743         conv_intrinsic_cobound (se, expr);
6744       else
6745         trans_this_image (se, expr);
6746       break;
6747
6748     case GFC_ISYM_IMAGE_INDEX:
6749       trans_image_index (se, expr);
6750       break;
6751
6752     case GFC_ISYM_NUM_IMAGES:
6753       trans_num_images (se);
6754       break;
6755
6756     case GFC_ISYM_ACCESS:
6757     case GFC_ISYM_CHDIR:
6758     case GFC_ISYM_CHMOD:
6759     case GFC_ISYM_DTIME:
6760     case GFC_ISYM_ETIME:
6761     case GFC_ISYM_EXTENDS_TYPE_OF:
6762     case GFC_ISYM_FGET:
6763     case GFC_ISYM_FGETC:
6764     case GFC_ISYM_FNUM:
6765     case GFC_ISYM_FPUT:
6766     case GFC_ISYM_FPUTC:
6767     case GFC_ISYM_FSTAT:
6768     case GFC_ISYM_FTELL:
6769     case GFC_ISYM_GETCWD:
6770     case GFC_ISYM_GETGID:
6771     case GFC_ISYM_GETPID:
6772     case GFC_ISYM_GETUID:
6773     case GFC_ISYM_HOSTNM:
6774     case GFC_ISYM_KILL:
6775     case GFC_ISYM_IERRNO:
6776     case GFC_ISYM_IRAND:
6777     case GFC_ISYM_ISATTY:
6778     case GFC_ISYM_JN2:
6779     case GFC_ISYM_LINK:
6780     case GFC_ISYM_LSTAT:
6781     case GFC_ISYM_MALLOC:
6782     case GFC_ISYM_MATMUL:
6783     case GFC_ISYM_MCLOCK:
6784     case GFC_ISYM_MCLOCK8:
6785     case GFC_ISYM_RAND:
6786     case GFC_ISYM_RENAME:
6787     case GFC_ISYM_SECOND:
6788     case GFC_ISYM_SECNDS:
6789     case GFC_ISYM_SIGNAL:
6790     case GFC_ISYM_STAT:
6791     case GFC_ISYM_SYMLNK:
6792     case GFC_ISYM_SYSTEM:
6793     case GFC_ISYM_TIME:
6794     case GFC_ISYM_TIME8:
6795     case GFC_ISYM_UMASK:
6796     case GFC_ISYM_UNLINK:
6797     case GFC_ISYM_YN2:
6798       gfc_conv_intrinsic_funcall (se, expr);
6799       break;
6800
6801     case GFC_ISYM_EOSHIFT:
6802     case GFC_ISYM_PACK:
6803     case GFC_ISYM_RESHAPE:
6804       /* For those, expr->rank should always be >0 and thus the if above the
6805          switch should have matched.  */
6806       gcc_unreachable ();
6807       break;
6808
6809     default:
6810       gfc_conv_intrinsic_lib_function (se, expr);
6811       break;
6812     }
6813 }
6814
6815
6816 static gfc_ss *
6817 walk_inline_intrinsic_transpose (gfc_ss *ss, gfc_expr *expr)
6818 {
6819   gfc_ss *arg_ss, *tmp_ss;
6820   gfc_actual_arglist *arg;
6821
6822   arg = expr->value.function.actual;
6823
6824   gcc_assert (arg->expr);
6825
6826   arg_ss = gfc_walk_subexpr (gfc_ss_terminator, arg->expr);
6827   gcc_assert (arg_ss != gfc_ss_terminator);
6828
6829   for (tmp_ss = arg_ss; ; tmp_ss = tmp_ss->next)
6830     {
6831       if (tmp_ss->info->type != GFC_SS_SCALAR
6832           && tmp_ss->info->type != GFC_SS_REFERENCE)
6833         {
6834           int tmp_dim;
6835
6836           gcc_assert (tmp_ss->dimen == 2);
6837
6838           /* We just invert dimensions.  */
6839           tmp_dim = tmp_ss->dim[0];
6840           tmp_ss->dim[0] = tmp_ss->dim[1];
6841           tmp_ss->dim[1] = tmp_dim;
6842         }
6843
6844       /* Stop when tmp_ss points to the last valid element of the chain...  */
6845       if (tmp_ss->next == gfc_ss_terminator)
6846         break;
6847     }
6848
6849   /* ... so that we can attach the rest of the chain to it.  */
6850   tmp_ss->next = ss;
6851
6852   return arg_ss;
6853 }
6854
6855
6856 /* Move the given dimension of the given gfc_ss list to a nested gfc_ss list.
6857    This has the side effect of reversing the nested list, so there is no
6858    need to call gfc_reverse_ss on it (the given list is assumed not to be
6859    reversed yet).   */
6860
6861 static gfc_ss *
6862 nest_loop_dimension (gfc_ss *ss, int dim)
6863 {
6864   int ss_dim, i;
6865   gfc_ss *new_ss, *prev_ss = gfc_ss_terminator;
6866   gfc_loopinfo *new_loop;
6867
6868   gcc_assert (ss != gfc_ss_terminator);
6869
6870   for (; ss != gfc_ss_terminator; ss = ss->next)
6871     {
6872       new_ss = gfc_get_ss ();
6873       new_ss->next = prev_ss;
6874       new_ss->parent = ss;
6875       new_ss->info = ss->info;
6876       new_ss->info->refcount++;
6877       if (ss->dimen != 0)
6878         {
6879           gcc_assert (ss->info->type != GFC_SS_SCALAR
6880                       && ss->info->type != GFC_SS_REFERENCE);
6881
6882           new_ss->dimen = 1;
6883           new_ss->dim[0] = ss->dim[dim];
6884
6885           gcc_assert (dim < ss->dimen);
6886
6887           ss_dim = --ss->dimen;
6888           for (i = dim; i < ss_dim; i++)
6889             ss->dim[i] = ss->dim[i + 1];
6890
6891           ss->dim[ss_dim] = 0;
6892         }
6893       prev_ss = new_ss;
6894
6895       if (ss->nested_ss)
6896         {
6897           ss->nested_ss->parent = new_ss;
6898           new_ss->nested_ss = ss->nested_ss;
6899         }
6900       ss->nested_ss = new_ss;
6901     }
6902
6903   new_loop = gfc_get_loopinfo ();
6904   gfc_init_loopinfo (new_loop);
6905
6906   gcc_assert (prev_ss != NULL);
6907   gcc_assert (prev_ss != gfc_ss_terminator);
6908   gfc_add_ss_to_loop (new_loop, prev_ss);
6909   return new_ss->parent;
6910 }
6911
6912
6913 /* Create the gfc_ss list for the SUM/PRODUCT arguments when the function
6914    is to be inlined.  */
6915
6916 static gfc_ss *
6917 walk_inline_intrinsic_arith (gfc_ss *ss, gfc_expr *expr)
6918 {
6919   gfc_ss *tmp_ss, *tail, *array_ss;
6920   gfc_actual_arglist *arg1, *arg2, *arg3;
6921   int sum_dim;
6922   bool scalar_mask = false;
6923
6924   /* The rank of the result will be determined later.  */
6925   arg1 = expr->value.function.actual;
6926   arg2 = arg1->next;
6927   arg3 = arg2->next;
6928   gcc_assert (arg3 != NULL);
6929
6930   if (expr->rank == 0)
6931     return ss;
6932
6933   tmp_ss = gfc_ss_terminator;
6934
6935   if (arg3->expr)
6936     {
6937       gfc_ss *mask_ss;
6938
6939       mask_ss = gfc_walk_subexpr (tmp_ss, arg3->expr);
6940       if (mask_ss == tmp_ss)
6941         scalar_mask = 1;
6942
6943       tmp_ss = mask_ss;
6944     }
6945
6946   array_ss = gfc_walk_subexpr (tmp_ss, arg1->expr);
6947   gcc_assert (array_ss != tmp_ss);
6948
6949   /* Odd thing: If the mask is scalar, it is used by the frontend after
6950      the array (to make an if around the nested loop). Thus it shall
6951      be after array_ss once the gfc_ss list is reversed.  */
6952   if (scalar_mask)
6953     tmp_ss = gfc_get_scalar_ss (array_ss, arg3->expr);
6954   else
6955     tmp_ss = array_ss;
6956
6957   /* "Hide" the dimension on which we will sum in the first arg's scalarization
6958      chain.  */
6959   sum_dim = mpz_get_si (arg2->expr->value.integer) - 1;
6960   tail = nest_loop_dimension (tmp_ss, sum_dim);
6961   tail->next = ss;
6962
6963   return tmp_ss;
6964 }
6965
6966
6967 static gfc_ss *
6968 walk_inline_intrinsic_function (gfc_ss * ss, gfc_expr * expr)
6969 {
6970
6971   switch (expr->value.function.isym->id)
6972     {
6973       case GFC_ISYM_PRODUCT:
6974       case GFC_ISYM_SUM:
6975         return walk_inline_intrinsic_arith (ss, expr);
6976
6977       case GFC_ISYM_TRANSPOSE:
6978         return walk_inline_intrinsic_transpose (ss, expr);
6979
6980       default:
6981         gcc_unreachable ();
6982     }
6983   gcc_unreachable ();
6984 }
6985
6986
6987 /* This generates code to execute before entering the scalarization loop.
6988    Currently does nothing.  */
6989
6990 void
6991 gfc_add_intrinsic_ss_code (gfc_loopinfo * loop ATTRIBUTE_UNUSED, gfc_ss * ss)
6992 {
6993   switch (ss->info->expr->value.function.isym->id)
6994     {
6995     case GFC_ISYM_UBOUND:
6996     case GFC_ISYM_LBOUND:
6997     case GFC_ISYM_UCOBOUND:
6998     case GFC_ISYM_LCOBOUND:
6999     case GFC_ISYM_THIS_IMAGE:
7000       break;
7001
7002     default:
7003       gcc_unreachable ();
7004     }
7005 }
7006
7007
7008 /* The LBOUND, LCOBOUND, UBOUND and UCOBOUND intrinsics with one parameter
7009    are expanded into code inside the scalarization loop.  */
7010
7011 static gfc_ss *
7012 gfc_walk_intrinsic_bound (gfc_ss * ss, gfc_expr * expr)
7013 {
7014   if (expr->value.function.actual->expr->ts.type == BT_CLASS)
7015     gfc_add_class_array_ref (expr->value.function.actual->expr);
7016
7017   /* The two argument version returns a scalar.  */
7018   if (expr->value.function.actual->next->expr)
7019     return ss;
7020
7021   return gfc_get_array_ss (ss, expr, 1, GFC_SS_INTRINSIC);
7022 }
7023
7024
7025 /* Walk an intrinsic array libcall.  */
7026
7027 static gfc_ss *
7028 gfc_walk_intrinsic_libfunc (gfc_ss * ss, gfc_expr * expr)
7029 {
7030   gcc_assert (expr->rank > 0);
7031   return gfc_get_array_ss (ss, expr, expr->rank, GFC_SS_FUNCTION);
7032 }
7033
7034
7035 /* Return whether the function call expression EXPR will be expanded
7036    inline by gfc_conv_intrinsic_function.  */
7037
7038 bool
7039 gfc_inline_intrinsic_function_p (gfc_expr *expr)
7040 {
7041   gfc_actual_arglist *args;
7042
7043   if (!expr->value.function.isym)
7044     return false;
7045
7046   switch (expr->value.function.isym->id)
7047     {
7048     case GFC_ISYM_PRODUCT:
7049     case GFC_ISYM_SUM:
7050       /* Disable inline expansion if code size matters.  */
7051       if (optimize_size)
7052         return false;
7053
7054       args = expr->value.function.actual;
7055       /* We need to be able to subset the SUM argument at compile-time.  */
7056       if (args->next->expr && args->next->expr->expr_type != EXPR_CONSTANT)
7057         return false;
7058
7059       return true;
7060
7061     case GFC_ISYM_TRANSPOSE:
7062       return true;
7063
7064     default:
7065       return false;
7066     }
7067 }
7068
7069
7070 /* Returns nonzero if the specified intrinsic function call maps directly to
7071    an external library call.  Should only be used for functions that return
7072    arrays.  */
7073
7074 int
7075 gfc_is_intrinsic_libcall (gfc_expr * expr)
7076 {
7077   gcc_assert (expr->expr_type == EXPR_FUNCTION && expr->value.function.isym);
7078   gcc_assert (expr->rank > 0);
7079
7080   if (gfc_inline_intrinsic_function_p (expr))
7081     return 0;
7082
7083   switch (expr->value.function.isym->id)
7084     {
7085     case GFC_ISYM_ALL:
7086     case GFC_ISYM_ANY:
7087     case GFC_ISYM_COUNT:
7088     case GFC_ISYM_JN2:
7089     case GFC_ISYM_IANY:
7090     case GFC_ISYM_IALL:
7091     case GFC_ISYM_IPARITY:
7092     case GFC_ISYM_MATMUL:
7093     case GFC_ISYM_MAXLOC:
7094     case GFC_ISYM_MAXVAL:
7095     case GFC_ISYM_MINLOC:
7096     case GFC_ISYM_MINVAL:
7097     case GFC_ISYM_NORM2:
7098     case GFC_ISYM_PARITY:
7099     case GFC_ISYM_PRODUCT:
7100     case GFC_ISYM_SUM:
7101     case GFC_ISYM_SHAPE:
7102     case GFC_ISYM_SPREAD:
7103     case GFC_ISYM_YN2:
7104       /* Ignore absent optional parameters.  */
7105       return 1;
7106
7107     case GFC_ISYM_RESHAPE:
7108     case GFC_ISYM_CSHIFT:
7109     case GFC_ISYM_EOSHIFT:
7110     case GFC_ISYM_PACK:
7111     case GFC_ISYM_UNPACK:
7112       /* Pass absent optional parameters.  */
7113       return 2;
7114
7115     default:
7116       return 0;
7117     }
7118 }
7119
7120 /* Walk an intrinsic function.  */
7121 gfc_ss *
7122 gfc_walk_intrinsic_function (gfc_ss * ss, gfc_expr * expr,
7123                              gfc_intrinsic_sym * isym)
7124 {
7125   gcc_assert (isym);
7126
7127   if (isym->elemental)
7128     return gfc_walk_elemental_function_args (ss, expr->value.function.actual,
7129                                              GFC_SS_SCALAR);
7130
7131   if (expr->rank == 0)
7132     return ss;
7133
7134   if (gfc_inline_intrinsic_function_p (expr))
7135     return walk_inline_intrinsic_function (ss, expr);
7136
7137   if (gfc_is_intrinsic_libcall (expr))
7138     return gfc_walk_intrinsic_libfunc (ss, expr);
7139
7140   /* Special cases.  */
7141   switch (isym->id)
7142     {
7143     case GFC_ISYM_LBOUND:
7144     case GFC_ISYM_LCOBOUND:
7145     case GFC_ISYM_UBOUND:
7146     case GFC_ISYM_UCOBOUND:
7147     case GFC_ISYM_THIS_IMAGE:
7148       return gfc_walk_intrinsic_bound (ss, expr);
7149
7150     case GFC_ISYM_TRANSFER:
7151       return gfc_walk_intrinsic_libfunc (ss, expr);
7152
7153     default:
7154       /* This probably meant someone forgot to add an intrinsic to the above
7155          list(s) when they implemented it, or something's gone horribly
7156          wrong.  */
7157       gcc_unreachable ();
7158     }
7159 }
7160
7161
7162 static tree
7163 conv_intrinsic_atomic_def (gfc_code *code)
7164 {
7165   gfc_se atom, value;
7166   stmtblock_t block;
7167
7168   gfc_init_se (&atom, NULL);
7169   gfc_init_se (&value, NULL);
7170   gfc_conv_expr (&atom, code->ext.actual->expr);
7171   gfc_conv_expr (&value, code->ext.actual->next->expr);
7172
7173   gfc_init_block (&block);
7174   gfc_add_modify (&block, atom.expr,
7175                   fold_convert (TREE_TYPE (atom.expr), value.expr));
7176   return gfc_finish_block (&block);
7177 }
7178
7179
7180 static tree
7181 conv_intrinsic_atomic_ref (gfc_code *code)
7182 {
7183   gfc_se atom, value;
7184   stmtblock_t block;
7185
7186   gfc_init_se (&atom, NULL);
7187   gfc_init_se (&value, NULL);
7188   gfc_conv_expr (&value, code->ext.actual->expr);
7189   gfc_conv_expr (&atom, code->ext.actual->next->expr);
7190
7191   gfc_init_block (&block);
7192   gfc_add_modify (&block, value.expr,
7193                   fold_convert (TREE_TYPE (value.expr), atom.expr));
7194   return gfc_finish_block (&block);
7195 }
7196
7197
7198 static tree
7199 conv_intrinsic_move_alloc (gfc_code *code)
7200 {
7201   stmtblock_t block;
7202   gfc_expr *from_expr, *to_expr;
7203   gfc_expr *to_expr2, *from_expr2 = NULL;
7204   gfc_se from_se, to_se;
7205   gfc_ss *from_ss, *to_ss;
7206   tree tmp;
7207
7208   gfc_start_block (&block);
7209
7210   from_expr = code->ext.actual->expr;
7211   to_expr = code->ext.actual->next->expr;
7212
7213   gfc_init_se (&from_se, NULL);
7214   gfc_init_se (&to_se, NULL);
7215
7216   if (from_expr->rank == 0)
7217     {
7218       gcc_assert (from_expr->ts.type != BT_CLASS
7219                   || to_expr->ts.type == BT_CLASS);
7220       if (from_expr->ts.type != BT_CLASS)
7221         from_expr2 = from_expr;
7222       else
7223         {
7224           from_expr2 = gfc_copy_expr (from_expr);
7225           gfc_add_data_component (from_expr2);
7226         }
7227
7228       if (to_expr->ts.type != BT_CLASS)
7229         to_expr2 = to_expr;
7230       else
7231         {
7232           to_expr2 = gfc_copy_expr (to_expr);
7233           gfc_add_data_component (to_expr2);
7234         }
7235
7236       from_se.want_pointer = 1;
7237       to_se.want_pointer = 1;
7238       gfc_conv_expr (&from_se, from_expr2);
7239       gfc_conv_expr (&to_se, to_expr2);
7240       gfc_add_block_to_block (&block, &from_se.pre);
7241       gfc_add_block_to_block (&block, &to_se.pre);
7242
7243       /* Deallocate "to".  */
7244       tmp = gfc_deallocate_scalar_with_status (to_se.expr, NULL_TREE, true,
7245                                                to_expr2, to_expr->ts);
7246       gfc_add_expr_to_block (&block, tmp);
7247
7248       /* Assign (_data) pointers.  */
7249       gfc_add_modify_loc (input_location, &block, to_se.expr,
7250                           fold_convert (TREE_TYPE (to_se.expr), from_se.expr));
7251
7252       /* Set "from" to NULL.  */
7253       gfc_add_modify_loc (input_location, &block, from_se.expr,
7254                           fold_convert (TREE_TYPE (from_se.expr), null_pointer_node));
7255
7256       gfc_add_block_to_block (&block, &from_se.post);
7257       gfc_add_block_to_block (&block, &to_se.post);
7258
7259       /* Set _vptr.  */
7260       if (to_expr->ts.type == BT_CLASS)
7261         {
7262           gfc_free_expr (to_expr2);
7263           gfc_init_se (&to_se, NULL);
7264           to_se.want_pointer = 1;
7265           gfc_add_vptr_component (to_expr);
7266           gfc_conv_expr (&to_se, to_expr);
7267
7268           if (from_expr->ts.type == BT_CLASS)
7269             {
7270               gfc_free_expr (from_expr2);
7271               gfc_init_se (&from_se, NULL);
7272               from_se.want_pointer = 1;
7273               gfc_add_vptr_component (from_expr);
7274               gfc_conv_expr (&from_se, from_expr);
7275               tmp = from_se.expr;
7276             }
7277           else
7278             {
7279               gfc_symbol *vtab;
7280               vtab = gfc_find_derived_vtab (from_expr->ts.u.derived);
7281               gcc_assert (vtab);
7282               tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
7283             }
7284
7285           gfc_add_modify_loc (input_location, &block, to_se.expr,
7286                               fold_convert (TREE_TYPE (to_se.expr), tmp));
7287         }
7288
7289       return gfc_finish_block (&block);
7290     }
7291
7292   /* Update _vptr component.  */
7293   if (to_expr->ts.type == BT_CLASS)
7294     {
7295       to_se.want_pointer = 1;
7296       to_expr2 = gfc_copy_expr (to_expr);
7297       gfc_add_vptr_component (to_expr2);
7298       gfc_conv_expr (&to_se, to_expr2);
7299
7300       if (from_expr->ts.type == BT_CLASS)
7301         {
7302           from_se.want_pointer = 1;
7303           from_expr2 = gfc_copy_expr (from_expr);
7304           gfc_add_vptr_component (from_expr2);
7305           gfc_conv_expr (&from_se, from_expr2);
7306           tmp = from_se.expr;
7307         }
7308       else
7309         {
7310           gfc_symbol *vtab;
7311           vtab = gfc_find_derived_vtab (from_expr->ts.u.derived);
7312           gcc_assert (vtab);
7313           tmp = gfc_build_addr_expr (NULL_TREE, gfc_get_symbol_decl (vtab));
7314         }
7315
7316       gfc_add_modify_loc (input_location, &block, to_se.expr,
7317                           fold_convert (TREE_TYPE (to_se.expr), tmp));
7318       gfc_free_expr (to_expr2);
7319       gfc_init_se (&to_se, NULL);
7320
7321       if (from_expr->ts.type == BT_CLASS)
7322         {
7323           gfc_free_expr (from_expr2);
7324           gfc_init_se (&from_se, NULL);
7325         }
7326     }
7327
7328   /* Deallocate "to".  */
7329   to_ss = gfc_walk_expr (to_expr);
7330   from_ss = gfc_walk_expr (from_expr);
7331   gfc_conv_expr_descriptor (&to_se, to_expr, to_ss);
7332   gfc_conv_expr_descriptor (&from_se, from_expr, from_ss);
7333
7334   tmp = gfc_conv_descriptor_data_get (to_se.expr);
7335   tmp = gfc_deallocate_with_status (tmp, NULL_TREE, true, to_expr);
7336   gfc_add_expr_to_block (&block, tmp);
7337
7338   /* Move the pointer and update the array descriptor data.  */
7339   gfc_add_modify_loc (input_location, &block, to_se.expr, from_se.expr);
7340
7341   /* Set "to" to NULL.  */
7342   tmp = gfc_conv_descriptor_data_get (from_se.expr);
7343   gfc_add_modify_loc (input_location, &block, tmp,
7344                       fold_convert (TREE_TYPE (tmp), null_pointer_node));
7345
7346   return gfc_finish_block (&block);
7347 }
7348
7349
7350 tree
7351 gfc_conv_intrinsic_subroutine (gfc_code *code)
7352 {
7353   tree res;
7354
7355   gcc_assert (code->resolved_isym);
7356
7357   switch (code->resolved_isym->id)
7358     {
7359     case GFC_ISYM_MOVE_ALLOC:
7360       res = conv_intrinsic_move_alloc (code);
7361       break;
7362
7363     case GFC_ISYM_ATOMIC_DEF:
7364       res = conv_intrinsic_atomic_def (code);
7365       break;
7366
7367     case GFC_ISYM_ATOMIC_REF:
7368       res = conv_intrinsic_atomic_ref (code);
7369       break;
7370
7371     default:
7372       res = NULL_TREE;
7373       break;
7374     }
7375
7376   return res;
7377 }
7378
7379 #include "gt-fortran-trans-intrinsic.h"