OSDN Git Service

* trans-intrinsic.c (gfc_conv_intrinsic_arith): Update conditions.
[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 /* Inline implementation of the sum and product intrinsics.  */
2561 static void
2562 gfc_conv_intrinsic_arith (gfc_se * se, gfc_expr * expr, enum tree_code op,
2563                           bool norm2)
2564 {
2565   tree resvar;
2566   tree scale = NULL_TREE;
2567   tree type;
2568   stmtblock_t body;
2569   stmtblock_t block;
2570   tree tmp;
2571   gfc_loopinfo loop;
2572   gfc_actual_arglist *actual;
2573   gfc_ss *arrayss;
2574   gfc_ss *maskss;
2575   gfc_se arrayse;
2576   gfc_se maskse;
2577   gfc_expr *arrayexpr;
2578   gfc_expr *maskexpr;
2579
2580   if (se->ss)
2581     {
2582       gfc_conv_intrinsic_funcall (se, expr);
2583       return;
2584     }
2585
2586   type = gfc_typenode_for_spec (&expr->ts);
2587   /* Initialize the result.  */
2588   resvar = gfc_create_var (type, "val");
2589   if (norm2)
2590     {
2591       /* result = 0.0;
2592          scale = 1.0.  */
2593       scale = gfc_create_var (type, "scale");
2594       gfc_add_modify (&se->pre, scale,
2595                       gfc_build_const (type, integer_one_node));
2596       tmp = gfc_build_const (type, integer_zero_node);
2597     }
2598   else if (op == PLUS_EXPR || op == BIT_IOR_EXPR || op == BIT_XOR_EXPR)
2599     tmp = gfc_build_const (type, integer_zero_node);
2600   else if (op == NE_EXPR)
2601     /* PARITY.  */
2602     tmp = convert (type, boolean_false_node);
2603   else if (op == BIT_AND_EXPR)
2604     tmp = gfc_build_const (type, fold_build1_loc (input_location, NEGATE_EXPR,
2605                                                   type, integer_one_node));
2606   else
2607     tmp = gfc_build_const (type, integer_one_node);
2608
2609   gfc_add_modify (&se->pre, resvar, tmp);
2610
2611   /* Walk the arguments.  */
2612   actual = expr->value.function.actual;
2613   arrayexpr = actual->expr;
2614   arrayss = gfc_walk_expr (arrayexpr);
2615   gcc_assert (arrayss != gfc_ss_terminator);
2616
2617   if (op == NE_EXPR || norm2)
2618     /* PARITY and NORM2.  */
2619     maskexpr = NULL;
2620   else
2621     {
2622       actual = actual->next->next;
2623       gcc_assert (actual);
2624       maskexpr = actual->expr;
2625     }
2626
2627   if (maskexpr && maskexpr->rank > 0)
2628     {
2629       maskss = gfc_walk_expr (maskexpr);
2630       gcc_assert (maskss != gfc_ss_terminator);
2631     }
2632   else
2633     maskss = NULL;
2634
2635   /* Initialize the scalarizer.  */
2636   gfc_init_loopinfo (&loop);
2637   gfc_add_ss_to_loop (&loop, arrayss);
2638   if (maskexpr && maskexpr->rank > 0)
2639     gfc_add_ss_to_loop (&loop, maskss);
2640
2641   /* Initialize the loop.  */
2642   gfc_conv_ss_startstride (&loop);
2643   gfc_conv_loop_setup (&loop, &expr->where);
2644
2645   gfc_mark_ss_chain_used (arrayss, 1);
2646   if (maskexpr && maskexpr->rank > 0)
2647     gfc_mark_ss_chain_used (maskss, 1);
2648   /* Generate the loop body.  */
2649   gfc_start_scalarized_body (&loop, &body);
2650
2651   /* If we have a mask, only add this element if the mask is set.  */
2652   if (maskexpr && maskexpr->rank > 0)
2653     {
2654       gfc_init_se (&maskse, NULL);
2655       gfc_copy_loopinfo_to_se (&maskse, &loop);
2656       maskse.ss = maskss;
2657       gfc_conv_expr_val (&maskse, maskexpr);
2658       gfc_add_block_to_block (&body, &maskse.pre);
2659
2660       gfc_start_block (&block);
2661     }
2662   else
2663     gfc_init_block (&block);
2664
2665   /* Do the actual summation/product.  */
2666   gfc_init_se (&arrayse, NULL);
2667   gfc_copy_loopinfo_to_se (&arrayse, &loop);
2668   arrayse.ss = arrayss;
2669   gfc_conv_expr_val (&arrayse, arrayexpr);
2670   gfc_add_block_to_block (&block, &arrayse.pre);
2671
2672   if (norm2)
2673     {
2674       /* if (x(i) != 0.0)
2675            {
2676              absX = abs(x(i))
2677              if (absX > scale)
2678                {
2679                  val = scale/absX;
2680                  result = 1.0 + result * val * val;
2681                  scale = absX;
2682                }
2683              else
2684                {
2685                  val = absX/scale;
2686                  result += val * val;
2687                }
2688            }  */
2689       tree res1, res2, cond, absX, val;
2690       stmtblock_t ifblock1, ifblock2, ifblock3;
2691
2692       gfc_init_block (&ifblock1);
2693
2694       absX = gfc_create_var (type, "absX");
2695       gfc_add_modify (&ifblock1, absX,
2696                       fold_build1_loc (input_location, ABS_EXPR, type,
2697                                        arrayse.expr));
2698       val = gfc_create_var (type, "val");
2699       gfc_add_expr_to_block (&ifblock1, val);
2700
2701       gfc_init_block (&ifblock2);
2702       gfc_add_modify (&ifblock2, val,
2703                       fold_build2_loc (input_location, RDIV_EXPR, type, scale,
2704                                        absX));
2705       res1 = fold_build2_loc (input_location, MULT_EXPR, type, val, val); 
2706       res1 = fold_build2_loc (input_location, MULT_EXPR, type, resvar, res1);
2707       res1 = fold_build2_loc (input_location, PLUS_EXPR, type, res1,
2708                               gfc_build_const (type, integer_one_node));
2709       gfc_add_modify (&ifblock2, resvar, res1);
2710       gfc_add_modify (&ifblock2, scale, absX);
2711       res1 = gfc_finish_block (&ifblock2); 
2712
2713       gfc_init_block (&ifblock3);
2714       gfc_add_modify (&ifblock3, val,
2715                       fold_build2_loc (input_location, RDIV_EXPR, type, absX,
2716                                        scale));
2717       res2 = fold_build2_loc (input_location, MULT_EXPR, type, val, val); 
2718       res2 = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, res2);
2719       gfc_add_modify (&ifblock3, resvar, res2);
2720       res2 = gfc_finish_block (&ifblock3);
2721
2722       cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
2723                               absX, scale);
2724       tmp = build3_v (COND_EXPR, cond, res1, res2);
2725       gfc_add_expr_to_block (&ifblock1, tmp);  
2726       tmp = gfc_finish_block (&ifblock1);
2727
2728       cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
2729                               arrayse.expr,
2730                               gfc_build_const (type, integer_zero_node));
2731
2732       tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
2733       gfc_add_expr_to_block (&block, tmp);  
2734     }
2735   else
2736     {
2737       tmp = fold_build2_loc (input_location, op, type, resvar, arrayse.expr);
2738       gfc_add_modify (&block, resvar, tmp);
2739     }
2740
2741   gfc_add_block_to_block (&block, &arrayse.post);
2742
2743   if (maskexpr && maskexpr->rank > 0)
2744     {
2745       /* We enclose the above in if (mask) {...} .  */
2746
2747       tmp = gfc_finish_block (&block);
2748       tmp = build3_v (COND_EXPR, maskse.expr, tmp,
2749                       build_empty_stmt (input_location));
2750     }
2751   else
2752     tmp = gfc_finish_block (&block);
2753   gfc_add_expr_to_block (&body, tmp);
2754
2755   gfc_trans_scalarizing_loops (&loop, &body);
2756
2757   /* For a scalar mask, enclose the loop in an if statement.  */
2758   if (maskexpr && maskexpr->rank == 0)
2759     {
2760       gfc_init_se (&maskse, NULL);
2761       gfc_conv_expr_val (&maskse, maskexpr);
2762       gfc_init_block (&block);
2763       gfc_add_block_to_block (&block, &loop.pre);
2764       gfc_add_block_to_block (&block, &loop.post);
2765       tmp = gfc_finish_block (&block);
2766
2767       tmp = build3_v (COND_EXPR, maskse.expr, tmp,
2768                       build_empty_stmt (input_location));
2769       gfc_add_expr_to_block (&block, tmp);
2770       gfc_add_block_to_block (&se->pre, &block);
2771     }
2772   else
2773     {
2774       gfc_add_block_to_block (&se->pre, &loop.pre);
2775       gfc_add_block_to_block (&se->pre, &loop.post);
2776     }
2777
2778   gfc_cleanup_loop (&loop);
2779
2780   if (norm2)
2781     {
2782       /* result = scale * sqrt(result).  */
2783       tree sqrt;
2784       sqrt = gfc_builtin_decl_for_float_kind (BUILT_IN_SQRT, expr->ts.kind);
2785       resvar = build_call_expr_loc (input_location,
2786                                     sqrt, 1, resvar);
2787       resvar = fold_build2_loc (input_location, MULT_EXPR, type, scale, resvar);
2788     }
2789
2790   se->expr = resvar;
2791 }
2792
2793
2794 /* Inline implementation of the dot_product intrinsic. This function
2795    is based on gfc_conv_intrinsic_arith (the previous function).  */
2796 static void
2797 gfc_conv_intrinsic_dot_product (gfc_se * se, gfc_expr * expr)
2798 {
2799   tree resvar;
2800   tree type;
2801   stmtblock_t body;
2802   stmtblock_t block;
2803   tree tmp;
2804   gfc_loopinfo loop;
2805   gfc_actual_arglist *actual;
2806   gfc_ss *arrayss1, *arrayss2;
2807   gfc_se arrayse1, arrayse2;
2808   gfc_expr *arrayexpr1, *arrayexpr2;
2809
2810   type = gfc_typenode_for_spec (&expr->ts);
2811
2812   /* Initialize the result.  */
2813   resvar = gfc_create_var (type, "val");
2814   if (expr->ts.type == BT_LOGICAL)
2815     tmp = build_int_cst (type, 0);
2816   else
2817     tmp = gfc_build_const (type, integer_zero_node);
2818
2819   gfc_add_modify (&se->pre, resvar, tmp);
2820
2821   /* Walk argument #1.  */
2822   actual = expr->value.function.actual;
2823   arrayexpr1 = actual->expr;
2824   arrayss1 = gfc_walk_expr (arrayexpr1);
2825   gcc_assert (arrayss1 != gfc_ss_terminator);
2826
2827   /* Walk argument #2.  */
2828   actual = actual->next;
2829   arrayexpr2 = actual->expr;
2830   arrayss2 = gfc_walk_expr (arrayexpr2);
2831   gcc_assert (arrayss2 != gfc_ss_terminator);
2832
2833   /* Initialize the scalarizer.  */
2834   gfc_init_loopinfo (&loop);
2835   gfc_add_ss_to_loop (&loop, arrayss1);
2836   gfc_add_ss_to_loop (&loop, arrayss2);
2837
2838   /* Initialize the loop.  */
2839   gfc_conv_ss_startstride (&loop);
2840   gfc_conv_loop_setup (&loop, &expr->where);
2841
2842   gfc_mark_ss_chain_used (arrayss1, 1);
2843   gfc_mark_ss_chain_used (arrayss2, 1);
2844
2845   /* Generate the loop body.  */
2846   gfc_start_scalarized_body (&loop, &body);
2847   gfc_init_block (&block);
2848
2849   /* Make the tree expression for [conjg(]array1[)].  */
2850   gfc_init_se (&arrayse1, NULL);
2851   gfc_copy_loopinfo_to_se (&arrayse1, &loop);
2852   arrayse1.ss = arrayss1;
2853   gfc_conv_expr_val (&arrayse1, arrayexpr1);
2854   if (expr->ts.type == BT_COMPLEX)
2855     arrayse1.expr = fold_build1_loc (input_location, CONJ_EXPR, type,
2856                                      arrayse1.expr);
2857   gfc_add_block_to_block (&block, &arrayse1.pre);
2858
2859   /* Make the tree expression for array2.  */
2860   gfc_init_se (&arrayse2, NULL);
2861   gfc_copy_loopinfo_to_se (&arrayse2, &loop);
2862   arrayse2.ss = arrayss2;
2863   gfc_conv_expr_val (&arrayse2, arrayexpr2);
2864   gfc_add_block_to_block (&block, &arrayse2.pre);
2865
2866   /* Do the actual product and sum.  */
2867   if (expr->ts.type == BT_LOGICAL)
2868     {
2869       tmp = fold_build2_loc (input_location, TRUTH_AND_EXPR, type,
2870                              arrayse1.expr, arrayse2.expr);
2871       tmp = fold_build2_loc (input_location, TRUTH_OR_EXPR, type, resvar, tmp);
2872     }
2873   else
2874     {
2875       tmp = fold_build2_loc (input_location, MULT_EXPR, type, arrayse1.expr,
2876                              arrayse2.expr);
2877       tmp = fold_build2_loc (input_location, PLUS_EXPR, type, resvar, tmp);
2878     }
2879   gfc_add_modify (&block, resvar, tmp);
2880
2881   /* Finish up the loop block and the loop.  */
2882   tmp = gfc_finish_block (&block);
2883   gfc_add_expr_to_block (&body, tmp);
2884
2885   gfc_trans_scalarizing_loops (&loop, &body);
2886   gfc_add_block_to_block (&se->pre, &loop.pre);
2887   gfc_add_block_to_block (&se->pre, &loop.post);
2888   gfc_cleanup_loop (&loop);
2889
2890   se->expr = resvar;
2891 }
2892
2893
2894 /* Emit code for minloc or maxloc intrinsic.  There are many different cases
2895    we need to handle.  For performance reasons we sometimes create two
2896    loops instead of one, where the second one is much simpler.
2897    Examples for minloc intrinsic:
2898    1) Result is an array, a call is generated
2899    2) Array mask is used and NaNs need to be supported:
2900       limit = Infinity;
2901       pos = 0;
2902       S = from;
2903       while (S <= to) {
2904         if (mask[S]) {
2905           if (pos == 0) pos = S + (1 - from);
2906           if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2907         }
2908         S++;
2909       }
2910       goto lab2;
2911       lab1:;
2912       while (S <= to) {
2913         if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2914         S++;
2915       }
2916       lab2:;
2917    3) NaNs need to be supported, but it is known at compile time or cheaply
2918       at runtime whether array is nonempty or not:
2919       limit = Infinity;
2920       pos = 0;
2921       S = from;
2922       while (S <= to) {
2923         if (a[S] <= limit) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2924         S++;
2925       }
2926       if (from <= to) pos = 1;
2927       goto lab2;
2928       lab1:;
2929       while (S <= to) {
2930         if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2931         S++;
2932       }
2933       lab2:;
2934    4) NaNs aren't supported, array mask is used:
2935       limit = infinities_supported ? Infinity : huge (limit);
2936       pos = 0;
2937       S = from;
2938       while (S <= to) {
2939         if (mask[S]) { limit = a[S]; pos = S + (1 - from); goto lab1; }
2940         S++;
2941       }
2942       goto lab2;
2943       lab1:;
2944       while (S <= to) {
2945         if (mask[S]) if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2946         S++;
2947       }
2948       lab2:;
2949    5) Same without array mask:
2950       limit = infinities_supported ? Infinity : huge (limit);
2951       pos = (from <= to) ? 1 : 0;
2952       S = from;
2953       while (S <= to) {
2954         if (a[S] < limit) { limit = a[S]; pos = S + (1 - from); }
2955         S++;
2956       }
2957    For 3) and 5), if mask is scalar, this all goes into a conditional,
2958    setting pos = 0; in the else branch.  */
2959
2960 static void
2961 gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * expr, enum tree_code op)
2962 {
2963   stmtblock_t body;
2964   stmtblock_t block;
2965   stmtblock_t ifblock;
2966   stmtblock_t elseblock;
2967   tree limit;
2968   tree type;
2969   tree tmp;
2970   tree cond;
2971   tree elsetmp;
2972   tree ifbody;
2973   tree offset;
2974   tree nonempty;
2975   tree lab1, lab2;
2976   gfc_loopinfo loop;
2977   gfc_actual_arglist *actual;
2978   gfc_ss *arrayss;
2979   gfc_ss *maskss;
2980   gfc_se arrayse;
2981   gfc_se maskse;
2982   gfc_expr *arrayexpr;
2983   gfc_expr *maskexpr;
2984   tree pos;
2985   int n;
2986
2987   if (se->ss)
2988     {
2989       gfc_conv_intrinsic_funcall (se, expr);
2990       return;
2991     }
2992
2993   /* Initialize the result.  */
2994   pos = gfc_create_var (gfc_array_index_type, "pos");
2995   offset = gfc_create_var (gfc_array_index_type, "offset");
2996   type = gfc_typenode_for_spec (&expr->ts);
2997
2998   /* Walk the arguments.  */
2999   actual = expr->value.function.actual;
3000   arrayexpr = actual->expr;
3001   arrayss = gfc_walk_expr (arrayexpr);
3002   gcc_assert (arrayss != gfc_ss_terminator);
3003
3004   actual = actual->next->next;
3005   gcc_assert (actual);
3006   maskexpr = actual->expr;
3007   nonempty = NULL;
3008   if (maskexpr && maskexpr->rank != 0)
3009     {
3010       maskss = gfc_walk_expr (maskexpr);
3011       gcc_assert (maskss != gfc_ss_terminator);
3012     }
3013   else
3014     {
3015       mpz_t asize;
3016       if (gfc_array_size (arrayexpr, &asize) == SUCCESS)
3017         {
3018           nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
3019           mpz_clear (asize);
3020           nonempty = fold_build2_loc (input_location, GT_EXPR,
3021                                       boolean_type_node, nonempty,
3022                                       gfc_index_zero_node);
3023         }
3024       maskss = NULL;
3025     }
3026
3027   limit = gfc_create_var (gfc_typenode_for_spec (&arrayexpr->ts), "limit");
3028   switch (arrayexpr->ts.type)
3029     {
3030     case BT_REAL:
3031       tmp = gfc_build_inf_or_huge (TREE_TYPE (limit), arrayexpr->ts.kind);
3032       break;
3033
3034     case BT_INTEGER:
3035       n = gfc_validate_kind (arrayexpr->ts.type, arrayexpr->ts.kind, false);
3036       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge,
3037                                   arrayexpr->ts.kind);
3038       break;
3039
3040     default:
3041       gcc_unreachable ();
3042     }
3043
3044   /* We start with the most negative possible value for MAXLOC, and the most
3045      positive possible value for MINLOC. The most negative possible value is
3046      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
3047      possible value is HUGE in both cases.  */
3048   if (op == GT_EXPR)
3049     tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
3050   if (op == GT_EXPR && expr->ts.type == BT_INTEGER)
3051     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp), tmp,
3052                            build_int_cst (type, 1));
3053
3054   gfc_add_modify (&se->pre, limit, tmp);
3055
3056   /* Initialize the scalarizer.  */
3057   gfc_init_loopinfo (&loop);
3058   gfc_add_ss_to_loop (&loop, arrayss);
3059   if (maskss)
3060     gfc_add_ss_to_loop (&loop, maskss);
3061
3062   /* Initialize the loop.  */
3063   gfc_conv_ss_startstride (&loop);
3064
3065   /* The code generated can have more than one loop in sequence (see the
3066      comment at the function header).  This doesn't work well with the
3067      scalarizer, which changes arrays' offset when the scalarization loops
3068      are generated (see gfc_trans_preloop_setup).  Fortunately, {min,max}loc
3069      are  currently inlined in the scalar case only (for which loop is of rank
3070      one).  As there is no dependency to care about in that case, there is no
3071      temporary, so that we can use the scalarizer temporary code to handle
3072      multiple loops.  Thus, we set temp_dim here, we call gfc_mark_ss_chain_used
3073      with flag=3 later, and we use gfc_trans_scalarized_loop_boundary even later
3074      to restore offset.
3075      TODO: this prevents inlining of rank > 0 minmaxloc calls, so this
3076      should eventually go away.  We could either create two loops properly,
3077      or find another way to save/restore the array offsets between the two
3078      loops (without conflicting with temporary management), or use a single
3079      loop minmaxloc implementation.  See PR 31067.  */
3080   loop.temp_dim = loop.dimen;
3081   gfc_conv_loop_setup (&loop, &expr->where);
3082
3083   gcc_assert (loop.dimen == 1);
3084   if (nonempty == NULL && maskss == NULL && loop.from[0] && loop.to[0])
3085     nonempty = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
3086                                 loop.from[0], loop.to[0]);
3087
3088   lab1 = NULL;
3089   lab2 = NULL;
3090   /* Initialize the position to zero, following Fortran 2003.  We are free
3091      to do this because Fortran 95 allows the result of an entirely false
3092      mask to be processor dependent.  If we know at compile time the array
3093      is non-empty and no MASK is used, we can initialize to 1 to simplify
3094      the inner loop.  */
3095   if (nonempty != NULL && !HONOR_NANS (DECL_MODE (limit)))
3096     gfc_add_modify (&loop.pre, pos,
3097                     fold_build3_loc (input_location, COND_EXPR,
3098                                      gfc_array_index_type,
3099                                      nonempty, gfc_index_one_node,
3100                                      gfc_index_zero_node));
3101   else
3102     {
3103       gfc_add_modify (&loop.pre, pos, gfc_index_zero_node);
3104       lab1 = gfc_build_label_decl (NULL_TREE);
3105       TREE_USED (lab1) = 1;
3106       lab2 = gfc_build_label_decl (NULL_TREE);
3107       TREE_USED (lab2) = 1;
3108     }
3109
3110   /* An offset must be added to the loop
3111      counter to obtain the required position.  */
3112   gcc_assert (loop.from[0]);
3113
3114   tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
3115                          gfc_index_one_node, loop.from[0]);
3116   gfc_add_modify (&loop.pre, offset, tmp);
3117
3118   gfc_mark_ss_chain_used (arrayss, lab1 ? 3 : 1);
3119   if (maskss)
3120     gfc_mark_ss_chain_used (maskss, lab1 ? 3 : 1);
3121   /* Generate the loop body.  */
3122   gfc_start_scalarized_body (&loop, &body);
3123
3124   /* If we have a mask, only check this element if the mask is set.  */
3125   if (maskss)
3126     {
3127       gfc_init_se (&maskse, NULL);
3128       gfc_copy_loopinfo_to_se (&maskse, &loop);
3129       maskse.ss = maskss;
3130       gfc_conv_expr_val (&maskse, maskexpr);
3131       gfc_add_block_to_block (&body, &maskse.pre);
3132
3133       gfc_start_block (&block);
3134     }
3135   else
3136     gfc_init_block (&block);
3137
3138   /* Compare with the current limit.  */
3139   gfc_init_se (&arrayse, NULL);
3140   gfc_copy_loopinfo_to_se (&arrayse, &loop);
3141   arrayse.ss = arrayss;
3142   gfc_conv_expr_val (&arrayse, arrayexpr);
3143   gfc_add_block_to_block (&block, &arrayse.pre);
3144
3145   /* We do the following if this is a more extreme value.  */
3146   gfc_start_block (&ifblock);
3147
3148   /* Assign the value to the limit...  */
3149   gfc_add_modify (&ifblock, limit, arrayse.expr);
3150
3151   if (nonempty == NULL && HONOR_NANS (DECL_MODE (limit)))
3152     {
3153       stmtblock_t ifblock2;
3154       tree ifbody2;
3155
3156       gfc_start_block (&ifblock2);
3157       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
3158                              loop.loopvar[0], offset);
3159       gfc_add_modify (&ifblock2, pos, tmp);
3160       ifbody2 = gfc_finish_block (&ifblock2);
3161       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, pos,
3162                               gfc_index_zero_node);
3163       tmp = build3_v (COND_EXPR, cond, ifbody2,
3164                       build_empty_stmt (input_location));
3165       gfc_add_expr_to_block (&block, tmp);
3166     }
3167
3168   tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
3169                          loop.loopvar[0], offset);
3170   gfc_add_modify (&ifblock, pos, tmp);
3171
3172   if (lab1)
3173     gfc_add_expr_to_block (&ifblock, build1_v (GOTO_EXPR, lab1));
3174
3175   ifbody = gfc_finish_block (&ifblock);
3176
3177   if (!lab1 || HONOR_NANS (DECL_MODE (limit)))
3178     {
3179       if (lab1)
3180         cond = fold_build2_loc (input_location,
3181                                 op == GT_EXPR ? GE_EXPR : LE_EXPR,
3182                                 boolean_type_node, arrayse.expr, limit);
3183       else
3184         cond = fold_build2_loc (input_location, op, boolean_type_node,
3185                                 arrayse.expr, limit);
3186
3187       ifbody = build3_v (COND_EXPR, cond, ifbody,
3188                          build_empty_stmt (input_location));
3189     }
3190   gfc_add_expr_to_block (&block, ifbody);
3191
3192   if (maskss)
3193     {
3194       /* We enclose the above in if (mask) {...}.  */
3195       tmp = gfc_finish_block (&block);
3196
3197       tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3198                       build_empty_stmt (input_location));
3199     }
3200   else
3201     tmp = gfc_finish_block (&block);
3202   gfc_add_expr_to_block (&body, tmp);
3203
3204   if (lab1)
3205     {
3206       gfc_trans_scalarized_loop_boundary (&loop, &body);
3207
3208       if (HONOR_NANS (DECL_MODE (limit)))
3209         {
3210           if (nonempty != NULL)
3211             {
3212               ifbody = build2_v (MODIFY_EXPR, pos, gfc_index_one_node);
3213               tmp = build3_v (COND_EXPR, nonempty, ifbody,
3214                               build_empty_stmt (input_location));
3215               gfc_add_expr_to_block (&loop.code[0], tmp);
3216             }
3217         }
3218
3219       gfc_add_expr_to_block (&loop.code[0], build1_v (GOTO_EXPR, lab2));
3220       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab1));
3221
3222       /* If we have a mask, only check this element if the mask is set.  */
3223       if (maskss)
3224         {
3225           gfc_init_se (&maskse, NULL);
3226           gfc_copy_loopinfo_to_se (&maskse, &loop);
3227           maskse.ss = maskss;
3228           gfc_conv_expr_val (&maskse, maskexpr);
3229           gfc_add_block_to_block (&body, &maskse.pre);
3230
3231           gfc_start_block (&block);
3232         }
3233       else
3234         gfc_init_block (&block);
3235
3236       /* Compare with the current limit.  */
3237       gfc_init_se (&arrayse, NULL);
3238       gfc_copy_loopinfo_to_se (&arrayse, &loop);
3239       arrayse.ss = arrayss;
3240       gfc_conv_expr_val (&arrayse, arrayexpr);
3241       gfc_add_block_to_block (&block, &arrayse.pre);
3242
3243       /* We do the following if this is a more extreme value.  */
3244       gfc_start_block (&ifblock);
3245
3246       /* Assign the value to the limit...  */
3247       gfc_add_modify (&ifblock, limit, arrayse.expr);
3248
3249       tmp = fold_build2_loc (input_location, PLUS_EXPR, TREE_TYPE (pos),
3250                              loop.loopvar[0], offset);
3251       gfc_add_modify (&ifblock, pos, tmp);
3252
3253       ifbody = gfc_finish_block (&ifblock);
3254
3255       cond = fold_build2_loc (input_location, op, boolean_type_node,
3256                               arrayse.expr, limit);
3257
3258       tmp = build3_v (COND_EXPR, cond, ifbody,
3259                       build_empty_stmt (input_location));
3260       gfc_add_expr_to_block (&block, tmp);
3261
3262       if (maskss)
3263         {
3264           /* We enclose the above in if (mask) {...}.  */
3265           tmp = gfc_finish_block (&block);
3266
3267           tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3268                           build_empty_stmt (input_location));
3269         }
3270       else
3271         tmp = gfc_finish_block (&block);
3272       gfc_add_expr_to_block (&body, tmp);
3273       /* Avoid initializing loopvar[0] again, it should be left where
3274          it finished by the first loop.  */
3275       loop.from[0] = loop.loopvar[0];
3276     }
3277
3278   gfc_trans_scalarizing_loops (&loop, &body);
3279
3280   if (lab2)
3281     gfc_add_expr_to_block (&loop.pre, build1_v (LABEL_EXPR, lab2));
3282
3283   /* For a scalar mask, enclose the loop in an if statement.  */
3284   if (maskexpr && maskss == NULL)
3285     {
3286       gfc_init_se (&maskse, NULL);
3287       gfc_conv_expr_val (&maskse, maskexpr);
3288       gfc_init_block (&block);
3289       gfc_add_block_to_block (&block, &loop.pre);
3290       gfc_add_block_to_block (&block, &loop.post);
3291       tmp = gfc_finish_block (&block);
3292
3293       /* For the else part of the scalar mask, just initialize
3294          the pos variable the same way as above.  */
3295
3296       gfc_init_block (&elseblock);
3297       gfc_add_modify (&elseblock, pos, gfc_index_zero_node);
3298       elsetmp = gfc_finish_block (&elseblock);
3299
3300       tmp = build3_v (COND_EXPR, maskse.expr, tmp, elsetmp);
3301       gfc_add_expr_to_block (&block, tmp);
3302       gfc_add_block_to_block (&se->pre, &block);
3303     }
3304   else
3305     {
3306       gfc_add_block_to_block (&se->pre, &loop.pre);
3307       gfc_add_block_to_block (&se->pre, &loop.post);
3308     }
3309   gfc_cleanup_loop (&loop);
3310
3311   se->expr = convert (type, pos);
3312 }
3313
3314 /* Emit code for minval or maxval intrinsic.  There are many different cases
3315    we need to handle.  For performance reasons we sometimes create two
3316    loops instead of one, where the second one is much simpler.
3317    Examples for minval intrinsic:
3318    1) Result is an array, a call is generated
3319    2) Array mask is used and NaNs need to be supported, rank 1:
3320       limit = Infinity;
3321       nonempty = false;
3322       S = from;
3323       while (S <= to) {
3324         if (mask[S]) { nonempty = true; if (a[S] <= limit) goto lab; }
3325         S++;
3326       }
3327       limit = nonempty ? NaN : huge (limit);
3328       lab:
3329       while (S <= to) { if(mask[S]) limit = min (a[S], limit); S++; }
3330    3) NaNs need to be supported, but it is known at compile time or cheaply
3331       at runtime whether array is nonempty or not, rank 1:
3332       limit = Infinity;
3333       S = from;
3334       while (S <= to) { if (a[S] <= limit) goto lab; S++; }
3335       limit = (from <= to) ? NaN : huge (limit);
3336       lab:
3337       while (S <= to) { limit = min (a[S], limit); S++; }
3338    4) Array mask is used and NaNs need to be supported, rank > 1:
3339       limit = Infinity;
3340       nonempty = false;
3341       fast = false;
3342       S1 = from1;
3343       while (S1 <= to1) {
3344         S2 = from2;
3345         while (S2 <= to2) {
3346           if (mask[S1][S2]) {
3347             if (fast) limit = min (a[S1][S2], limit);
3348             else {
3349               nonempty = true;
3350               if (a[S1][S2] <= limit) {
3351                 limit = a[S1][S2];
3352                 fast = true;
3353               }
3354             }
3355           }
3356           S2++;
3357         }
3358         S1++;
3359       }
3360       if (!fast)
3361         limit = nonempty ? NaN : huge (limit);
3362    5) NaNs need to be supported, but it is known at compile time or cheaply
3363       at runtime whether array is nonempty or not, rank > 1:
3364       limit = Infinity;
3365       fast = false;
3366       S1 = from1;
3367       while (S1 <= to1) {
3368         S2 = from2;
3369         while (S2 <= to2) {
3370           if (fast) limit = min (a[S1][S2], limit);
3371           else {
3372             if (a[S1][S2] <= limit) {
3373               limit = a[S1][S2];
3374               fast = true;
3375             }
3376           }
3377           S2++;
3378         }
3379         S1++;
3380       }
3381       if (!fast)
3382         limit = (nonempty_array) ? NaN : huge (limit);
3383    6) NaNs aren't supported, but infinities are.  Array mask is used:
3384       limit = Infinity;
3385       nonempty = false;
3386       S = from;
3387       while (S <= to) {
3388         if (mask[S]) { nonempty = true; limit = min (a[S], limit); }
3389         S++;
3390       }
3391       limit = nonempty ? limit : huge (limit);
3392    7) Same without array mask:
3393       limit = Infinity;
3394       S = from;
3395       while (S <= to) { limit = min (a[S], limit); S++; }
3396       limit = (from <= to) ? limit : huge (limit);
3397    8) Neither NaNs nor infinities are supported (-ffast-math or BT_INTEGER):
3398       limit = huge (limit);
3399       S = from;
3400       while (S <= to) { limit = min (a[S], limit); S++); }
3401       (or
3402       while (S <= to) { if (mask[S]) limit = min (a[S], limit); S++; }
3403       with array mask instead).
3404    For 3), 5), 7) and 8), if mask is scalar, this all goes into a conditional,
3405    setting limit = huge (limit); in the else branch.  */
3406
3407 static void
3408 gfc_conv_intrinsic_minmaxval (gfc_se * se, gfc_expr * expr, enum tree_code op)
3409 {
3410   tree limit;
3411   tree type;
3412   tree tmp;
3413   tree ifbody;
3414   tree nonempty;
3415   tree nonempty_var;
3416   tree lab;
3417   tree fast;
3418   tree huge_cst = NULL, nan_cst = NULL;
3419   stmtblock_t body;
3420   stmtblock_t block, block2;
3421   gfc_loopinfo loop;
3422   gfc_actual_arglist *actual;
3423   gfc_ss *arrayss;
3424   gfc_ss *maskss;
3425   gfc_se arrayse;
3426   gfc_se maskse;
3427   gfc_expr *arrayexpr;
3428   gfc_expr *maskexpr;
3429   int n;
3430
3431   if (se->ss)
3432     {
3433       gfc_conv_intrinsic_funcall (se, expr);
3434       return;
3435     }
3436
3437   type = gfc_typenode_for_spec (&expr->ts);
3438   /* Initialize the result.  */
3439   limit = gfc_create_var (type, "limit");
3440   n = gfc_validate_kind (expr->ts.type, expr->ts.kind, false);
3441   switch (expr->ts.type)
3442     {
3443     case BT_REAL:
3444       huge_cst = gfc_conv_mpfr_to_tree (gfc_real_kinds[n].huge,
3445                                         expr->ts.kind, 0);
3446       if (HONOR_INFINITIES (DECL_MODE (limit)))
3447         {
3448           REAL_VALUE_TYPE real;
3449           real_inf (&real);
3450           tmp = build_real (type, real);
3451         }
3452       else
3453         tmp = huge_cst;
3454       if (HONOR_NANS (DECL_MODE (limit)))
3455         {
3456           REAL_VALUE_TYPE real;
3457           real_nan (&real, "", 1, DECL_MODE (limit));
3458           nan_cst = build_real (type, real);
3459         }
3460       break;
3461
3462     case BT_INTEGER:
3463       tmp = gfc_conv_mpz_to_tree (gfc_integer_kinds[n].huge, expr->ts.kind);
3464       break;
3465
3466     default:
3467       gcc_unreachable ();
3468     }
3469
3470   /* We start with the most negative possible value for MAXVAL, and the most
3471      positive possible value for MINVAL. The most negative possible value is
3472      -HUGE for BT_REAL and (-HUGE - 1) for BT_INTEGER; the most positive
3473      possible value is HUGE in both cases.  */
3474   if (op == GT_EXPR)
3475     {
3476       tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (tmp), tmp);
3477       if (huge_cst)
3478         huge_cst = fold_build1_loc (input_location, NEGATE_EXPR,
3479                                     TREE_TYPE (huge_cst), huge_cst);
3480     }
3481
3482   if (op == GT_EXPR && expr->ts.type == BT_INTEGER)
3483     tmp = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (tmp),
3484                            tmp, build_int_cst (type, 1));
3485
3486   gfc_add_modify (&se->pre, limit, tmp);
3487
3488   /* Walk the arguments.  */
3489   actual = expr->value.function.actual;
3490   arrayexpr = actual->expr;
3491   arrayss = gfc_walk_expr (arrayexpr);
3492   gcc_assert (arrayss != gfc_ss_terminator);
3493
3494   actual = actual->next->next;
3495   gcc_assert (actual);
3496   maskexpr = actual->expr;
3497   nonempty = NULL;
3498   if (maskexpr && maskexpr->rank != 0)
3499     {
3500       maskss = gfc_walk_expr (maskexpr);
3501       gcc_assert (maskss != gfc_ss_terminator);
3502     }
3503   else
3504     {
3505       mpz_t asize;
3506       if (gfc_array_size (arrayexpr, &asize) == SUCCESS)
3507         {
3508           nonempty = gfc_conv_mpz_to_tree (asize, gfc_index_integer_kind);
3509           mpz_clear (asize);
3510           nonempty = fold_build2_loc (input_location, GT_EXPR,
3511                                       boolean_type_node, nonempty,
3512                                       gfc_index_zero_node);
3513         }
3514       maskss = NULL;
3515     }
3516
3517   /* Initialize the scalarizer.  */
3518   gfc_init_loopinfo (&loop);
3519   gfc_add_ss_to_loop (&loop, arrayss);
3520   if (maskss)
3521     gfc_add_ss_to_loop (&loop, maskss);
3522
3523   /* Initialize the loop.  */
3524   gfc_conv_ss_startstride (&loop);
3525
3526   /* The code generated can have more than one loop in sequence (see the
3527      comment at the function header).  This doesn't work well with the
3528      scalarizer, which changes arrays' offset when the scalarization loops
3529      are generated (see gfc_trans_preloop_setup).  Fortunately, {min,max}val
3530      are  currently inlined in the scalar case only.  As there is no dependency
3531      to care about in that case, there is no temporary, so that we can use the
3532      scalarizer temporary code to handle multiple loops.  Thus, we set temp_dim
3533      here, we call gfc_mark_ss_chain_used with flag=3 later, and we use
3534      gfc_trans_scalarized_loop_boundary even later to restore offset.
3535      TODO: this prevents inlining of rank > 0 minmaxval calls, so this
3536      should eventually go away.  We could either create two loops properly,
3537      or find another way to save/restore the array offsets between the two
3538      loops (without conflicting with temporary management), or use a single
3539      loop minmaxval implementation.  See PR 31067.  */
3540   loop.temp_dim = loop.dimen;
3541   gfc_conv_loop_setup (&loop, &expr->where);
3542
3543   if (nonempty == NULL && maskss == NULL
3544       && loop.dimen == 1 && loop.from[0] && loop.to[0])
3545     nonempty = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
3546                                 loop.from[0], loop.to[0]);
3547   nonempty_var = NULL;
3548   if (nonempty == NULL
3549       && (HONOR_INFINITIES (DECL_MODE (limit))
3550           || HONOR_NANS (DECL_MODE (limit))))
3551     {
3552       nonempty_var = gfc_create_var (boolean_type_node, "nonempty");
3553       gfc_add_modify (&se->pre, nonempty_var, boolean_false_node);
3554       nonempty = nonempty_var;
3555     }
3556   lab = NULL;
3557   fast = NULL;
3558   if (HONOR_NANS (DECL_MODE (limit)))
3559     {
3560       if (loop.dimen == 1)
3561         {
3562           lab = gfc_build_label_decl (NULL_TREE);
3563           TREE_USED (lab) = 1;
3564         }
3565       else
3566         {
3567           fast = gfc_create_var (boolean_type_node, "fast");
3568           gfc_add_modify (&se->pre, fast, boolean_false_node);
3569         }
3570     }
3571
3572   gfc_mark_ss_chain_used (arrayss, lab ? 3 : 1);
3573   if (maskss)
3574     gfc_mark_ss_chain_used (maskss, lab ? 3 : 1);
3575   /* Generate the loop body.  */
3576   gfc_start_scalarized_body (&loop, &body);
3577
3578   /* If we have a mask, only add this element if the mask is set.  */
3579   if (maskss)
3580     {
3581       gfc_init_se (&maskse, NULL);
3582       gfc_copy_loopinfo_to_se (&maskse, &loop);
3583       maskse.ss = maskss;
3584       gfc_conv_expr_val (&maskse, maskexpr);
3585       gfc_add_block_to_block (&body, &maskse.pre);
3586
3587       gfc_start_block (&block);
3588     }
3589   else
3590     gfc_init_block (&block);
3591
3592   /* Compare with the current limit.  */
3593   gfc_init_se (&arrayse, NULL);
3594   gfc_copy_loopinfo_to_se (&arrayse, &loop);
3595   arrayse.ss = arrayss;
3596   gfc_conv_expr_val (&arrayse, arrayexpr);
3597   gfc_add_block_to_block (&block, &arrayse.pre);
3598
3599   gfc_init_block (&block2);
3600
3601   if (nonempty_var)
3602     gfc_add_modify (&block2, nonempty_var, boolean_true_node);
3603
3604   if (HONOR_NANS (DECL_MODE (limit)))
3605     {
3606       tmp = fold_build2_loc (input_location, op == GT_EXPR ? GE_EXPR : LE_EXPR,
3607                              boolean_type_node, arrayse.expr, limit);
3608       if (lab)
3609         ifbody = build1_v (GOTO_EXPR, lab);
3610       else
3611         {
3612           stmtblock_t ifblock;
3613
3614           gfc_init_block (&ifblock);
3615           gfc_add_modify (&ifblock, limit, arrayse.expr);
3616           gfc_add_modify (&ifblock, fast, boolean_true_node);
3617           ifbody = gfc_finish_block (&ifblock);
3618         }
3619       tmp = build3_v (COND_EXPR, tmp, ifbody,
3620                       build_empty_stmt (input_location));
3621       gfc_add_expr_to_block (&block2, tmp);
3622     }
3623   else
3624     {
3625       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3626          signed zeros.  */
3627       if (HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3628         {
3629           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3630                                  arrayse.expr, limit);
3631           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3632           tmp = build3_v (COND_EXPR, tmp, ifbody,
3633                           build_empty_stmt (input_location));
3634           gfc_add_expr_to_block (&block2, tmp);
3635         }
3636       else
3637         {
3638           tmp = fold_build2_loc (input_location,
3639                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3640                                  type, arrayse.expr, limit);
3641           gfc_add_modify (&block2, limit, tmp);
3642         }
3643     }
3644
3645   if (fast)
3646     {
3647       tree elsebody = gfc_finish_block (&block2);
3648
3649       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3650          signed zeros.  */
3651       if (HONOR_NANS (DECL_MODE (limit))
3652           || HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3653         {
3654           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3655                                  arrayse.expr, limit);
3656           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3657           ifbody = build3_v (COND_EXPR, tmp, ifbody,
3658                              build_empty_stmt (input_location));
3659         }
3660       else
3661         {
3662           tmp = fold_build2_loc (input_location,
3663                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3664                                  type, arrayse.expr, limit);
3665           ifbody = build2_v (MODIFY_EXPR, limit, tmp);
3666         }
3667       tmp = build3_v (COND_EXPR, fast, ifbody, elsebody);
3668       gfc_add_expr_to_block (&block, tmp);
3669     }
3670   else
3671     gfc_add_block_to_block (&block, &block2);
3672
3673   gfc_add_block_to_block (&block, &arrayse.post);
3674
3675   tmp = gfc_finish_block (&block);
3676   if (maskss)
3677     /* We enclose the above in if (mask) {...}.  */
3678     tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3679                     build_empty_stmt (input_location));
3680   gfc_add_expr_to_block (&body, tmp);
3681
3682   if (lab)
3683     {
3684       gfc_trans_scalarized_loop_boundary (&loop, &body);
3685
3686       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
3687                              nan_cst, huge_cst);
3688       gfc_add_modify (&loop.code[0], limit, tmp);
3689       gfc_add_expr_to_block (&loop.code[0], build1_v (LABEL_EXPR, lab));
3690
3691       /* If we have a mask, only add this element if the mask is set.  */
3692       if (maskss)
3693         {
3694           gfc_init_se (&maskse, NULL);
3695           gfc_copy_loopinfo_to_se (&maskse, &loop);
3696           maskse.ss = maskss;
3697           gfc_conv_expr_val (&maskse, maskexpr);
3698           gfc_add_block_to_block (&body, &maskse.pre);
3699
3700           gfc_start_block (&block);
3701         }
3702       else
3703         gfc_init_block (&block);
3704
3705       /* Compare with the current limit.  */
3706       gfc_init_se (&arrayse, NULL);
3707       gfc_copy_loopinfo_to_se (&arrayse, &loop);
3708       arrayse.ss = arrayss;
3709       gfc_conv_expr_val (&arrayse, arrayexpr);
3710       gfc_add_block_to_block (&block, &arrayse.pre);
3711
3712       /* MIN_EXPR/MAX_EXPR has unspecified behavior with NaNs or
3713          signed zeros.  */
3714       if (HONOR_NANS (DECL_MODE (limit))
3715           || HONOR_SIGNED_ZEROS (DECL_MODE (limit)))
3716         {
3717           tmp = fold_build2_loc (input_location, op, boolean_type_node,
3718                                  arrayse.expr, limit);
3719           ifbody = build2_v (MODIFY_EXPR, limit, arrayse.expr);
3720           tmp = build3_v (COND_EXPR, tmp, ifbody,
3721                           build_empty_stmt (input_location));
3722           gfc_add_expr_to_block (&block, tmp);
3723         }
3724       else
3725         {
3726           tmp = fold_build2_loc (input_location,
3727                                  op == GT_EXPR ? MAX_EXPR : MIN_EXPR,
3728                                  type, arrayse.expr, limit);
3729           gfc_add_modify (&block, limit, tmp);
3730         }
3731
3732       gfc_add_block_to_block (&block, &arrayse.post);
3733
3734       tmp = gfc_finish_block (&block);
3735       if (maskss)
3736         /* We enclose the above in if (mask) {...}.  */
3737         tmp = build3_v (COND_EXPR, maskse.expr, tmp,
3738                         build_empty_stmt (input_location));
3739       gfc_add_expr_to_block (&body, tmp);
3740       /* Avoid initializing loopvar[0] again, it should be left where
3741          it finished by the first loop.  */
3742       loop.from[0] = loop.loopvar[0];
3743     }
3744   gfc_trans_scalarizing_loops (&loop, &body);
3745
3746   if (fast)
3747     {
3748       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty,
3749                              nan_cst, huge_cst);
3750       ifbody = build2_v (MODIFY_EXPR, limit, tmp);
3751       tmp = build3_v (COND_EXPR, fast, build_empty_stmt (input_location),
3752                       ifbody);
3753       gfc_add_expr_to_block (&loop.pre, tmp);
3754     }
3755   else if (HONOR_INFINITIES (DECL_MODE (limit)) && !lab)
3756     {
3757       tmp = fold_build3_loc (input_location, COND_EXPR, type, nonempty, limit,
3758                              huge_cst);
3759       gfc_add_modify (&loop.pre, limit, tmp);
3760     }
3761
3762   /* For a scalar mask, enclose the loop in an if statement.  */
3763   if (maskexpr && maskss == NULL)
3764     {
3765       tree else_stmt;
3766
3767       gfc_init_se (&maskse, NULL);
3768       gfc_conv_expr_val (&maskse, maskexpr);
3769       gfc_init_block (&block);
3770       gfc_add_block_to_block (&block, &loop.pre);
3771       gfc_add_block_to_block (&block, &loop.post);
3772       tmp = gfc_finish_block (&block);
3773
3774       if (HONOR_INFINITIES (DECL_MODE (limit)))
3775         else_stmt = build2_v (MODIFY_EXPR, limit, huge_cst);
3776       else
3777         else_stmt = build_empty_stmt (input_location);
3778       tmp = build3_v (COND_EXPR, maskse.expr, tmp, else_stmt);
3779       gfc_add_expr_to_block (&block, tmp);
3780       gfc_add_block_to_block (&se->pre, &block);
3781     }
3782   else
3783     {
3784       gfc_add_block_to_block (&se->pre, &loop.pre);
3785       gfc_add_block_to_block (&se->pre, &loop.post);
3786     }
3787
3788   gfc_cleanup_loop (&loop);
3789
3790   se->expr = limit;
3791 }
3792
3793 /* BTEST (i, pos) = (i & (1 << pos)) != 0.  */
3794 static void
3795 gfc_conv_intrinsic_btest (gfc_se * se, gfc_expr * expr)
3796 {
3797   tree args[2];
3798   tree type;
3799   tree tmp;
3800
3801   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3802   type = TREE_TYPE (args[0]);
3803
3804   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
3805                          build_int_cst (type, 1), args[1]);
3806   tmp = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], tmp);
3807   tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp,
3808                          build_int_cst (type, 0));
3809   type = gfc_typenode_for_spec (&expr->ts);
3810   se->expr = convert (type, tmp);
3811 }
3812
3813
3814 /* Generate code for BGE, BGT, BLE and BLT intrinsics.  */
3815 static void
3816 gfc_conv_intrinsic_bitcomp (gfc_se * se, gfc_expr * expr, enum tree_code op)
3817 {
3818   tree args[2];
3819
3820   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3821
3822   /* Convert both arguments to the unsigned type of the same size.  */
3823   args[0] = fold_convert (unsigned_type_for (TREE_TYPE (args[0])), args[0]);
3824   args[1] = fold_convert (unsigned_type_for (TREE_TYPE (args[1])), args[1]);
3825
3826   /* If they have unequal type size, convert to the larger one.  */
3827   if (TYPE_PRECISION (TREE_TYPE (args[0]))
3828       > TYPE_PRECISION (TREE_TYPE (args[1])))
3829     args[1] = fold_convert (TREE_TYPE (args[0]), args[1]);
3830   else if (TYPE_PRECISION (TREE_TYPE (args[1]))
3831            > TYPE_PRECISION (TREE_TYPE (args[0])))
3832     args[0] = fold_convert (TREE_TYPE (args[1]), args[0]);
3833
3834   /* Now, we compare them.  */
3835   se->expr = fold_build2_loc (input_location, op, boolean_type_node,
3836                               args[0], args[1]);
3837 }
3838
3839
3840 /* Generate code to perform the specified operation.  */
3841 static void
3842 gfc_conv_intrinsic_bitop (gfc_se * se, gfc_expr * expr, enum tree_code op)
3843 {
3844   tree args[2];
3845
3846   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3847   se->expr = fold_build2_loc (input_location, op, TREE_TYPE (args[0]),
3848                               args[0], args[1]);
3849 }
3850
3851 /* Bitwise not.  */
3852 static void
3853 gfc_conv_intrinsic_not (gfc_se * se, gfc_expr * expr)
3854 {
3855   tree arg;
3856
3857   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
3858   se->expr = fold_build1_loc (input_location, BIT_NOT_EXPR,
3859                               TREE_TYPE (arg), arg);
3860 }
3861
3862 /* Set or clear a single bit.  */
3863 static void
3864 gfc_conv_intrinsic_singlebitop (gfc_se * se, gfc_expr * expr, int set)
3865 {
3866   tree args[2];
3867   tree type;
3868   tree tmp;
3869   enum tree_code op;
3870
3871   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3872   type = TREE_TYPE (args[0]);
3873
3874   tmp = fold_build2_loc (input_location, LSHIFT_EXPR, type,
3875                          build_int_cst (type, 1), args[1]);
3876   if (set)
3877     op = BIT_IOR_EXPR;
3878   else
3879     {
3880       op = BIT_AND_EXPR;
3881       tmp = fold_build1_loc (input_location, BIT_NOT_EXPR, type, tmp);
3882     }
3883   se->expr = fold_build2_loc (input_location, op, type, args[0], tmp);
3884 }
3885
3886 /* Extract a sequence of bits.
3887     IBITS(I, POS, LEN) = (I >> POS) & ~((~0) << LEN).  */
3888 static void
3889 gfc_conv_intrinsic_ibits (gfc_se * se, gfc_expr * expr)
3890 {
3891   tree args[3];
3892   tree type;
3893   tree tmp;
3894   tree mask;
3895
3896   gfc_conv_intrinsic_function_args (se, expr, args, 3);
3897   type = TREE_TYPE (args[0]);
3898
3899   mask = build_int_cst (type, -1);
3900   mask = fold_build2_loc (input_location, LSHIFT_EXPR, type, mask, args[2]);
3901   mask = fold_build1_loc (input_location, BIT_NOT_EXPR, type, mask);
3902
3903   tmp = fold_build2_loc (input_location, RSHIFT_EXPR, type, args[0], args[1]);
3904
3905   se->expr = fold_build2_loc (input_location, BIT_AND_EXPR, type, tmp, mask);
3906 }
3907
3908 static void
3909 gfc_conv_intrinsic_shift (gfc_se * se, gfc_expr * expr, bool right_shift,
3910                           bool arithmetic)
3911 {
3912   tree args[2], type, num_bits, cond;
3913
3914   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3915
3916   args[0] = gfc_evaluate_now (args[0], &se->pre);
3917   args[1] = gfc_evaluate_now (args[1], &se->pre);
3918   type = TREE_TYPE (args[0]);
3919
3920   if (!arithmetic)
3921     args[0] = fold_convert (unsigned_type_for (type), args[0]);
3922   else
3923     gcc_assert (right_shift);
3924
3925   se->expr = fold_build2_loc (input_location,
3926                               right_shift ? RSHIFT_EXPR : LSHIFT_EXPR,
3927                               TREE_TYPE (args[0]), args[0], args[1]);
3928
3929   if (!arithmetic)
3930     se->expr = fold_convert (type, se->expr);
3931
3932   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
3933      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
3934      special case.  */
3935   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
3936   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
3937                           args[1], num_bits);
3938
3939   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
3940                               build_int_cst (type, 0), se->expr);
3941 }
3942
3943 /* ISHFT (I, SHIFT) = (abs (shift) >= BIT_SIZE (i))
3944                         ? 0
3945                         : ((shift >= 0) ? i << shift : i >> -shift)
3946    where all shifts are logical shifts.  */
3947 static void
3948 gfc_conv_intrinsic_ishft (gfc_se * se, gfc_expr * expr)
3949 {
3950   tree args[2];
3951   tree type;
3952   tree utype;
3953   tree tmp;
3954   tree width;
3955   tree num_bits;
3956   tree cond;
3957   tree lshift;
3958   tree rshift;
3959
3960   gfc_conv_intrinsic_function_args (se, expr, args, 2);
3961
3962   args[0] = gfc_evaluate_now (args[0], &se->pre);
3963   args[1] = gfc_evaluate_now (args[1], &se->pre);
3964
3965   type = TREE_TYPE (args[0]);
3966   utype = unsigned_type_for (type);
3967
3968   width = fold_build1_loc (input_location, ABS_EXPR, TREE_TYPE (args[1]),
3969                            args[1]);
3970
3971   /* Left shift if positive.  */
3972   lshift = fold_build2_loc (input_location, LSHIFT_EXPR, type, args[0], width);
3973
3974   /* Right shift if negative.
3975      We convert to an unsigned type because we want a logical shift.
3976      The standard doesn't define the case of shifting negative
3977      numbers, and we try to be compatible with other compilers, most
3978      notably g77, here.  */
3979   rshift = fold_convert (type, fold_build2_loc (input_location, RSHIFT_EXPR,
3980                                     utype, convert (utype, args[0]), width));
3981
3982   tmp = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, args[1],
3983                          build_int_cst (TREE_TYPE (args[1]), 0));
3984   tmp = fold_build3_loc (input_location, COND_EXPR, type, tmp, lshift, rshift);
3985
3986   /* The Fortran standard allows shift widths <= BIT_SIZE(I), whereas
3987      gcc requires a shift width < BIT_SIZE(I), so we have to catch this
3988      special case.  */
3989   num_bits = build_int_cst (TREE_TYPE (args[1]), TYPE_PRECISION (type));
3990   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, width,
3991                           num_bits);
3992   se->expr = fold_build3_loc (input_location, COND_EXPR, type, cond,
3993                               build_int_cst (type, 0), tmp);
3994 }
3995
3996
3997 /* Circular shift.  AKA rotate or barrel shift.  */
3998
3999 static void
4000 gfc_conv_intrinsic_ishftc (gfc_se * se, gfc_expr * expr)
4001 {
4002   tree *args;
4003   tree type;
4004   tree tmp;
4005   tree lrot;
4006   tree rrot;
4007   tree zero;
4008   unsigned int num_args;
4009
4010   num_args = gfc_intrinsic_argument_list_length (expr);
4011   args = XALLOCAVEC (tree, num_args);
4012
4013   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
4014
4015   if (num_args == 3)
4016     {
4017       /* Use a library function for the 3 parameter version.  */
4018       tree int4type = gfc_get_int_type (4);
4019
4020       type = TREE_TYPE (args[0]);
4021       /* We convert the first argument to at least 4 bytes, and
4022          convert back afterwards.  This removes the need for library
4023          functions for all argument sizes, and function will be
4024          aligned to at least 32 bits, so there's no loss.  */
4025       if (expr->ts.kind < 4)
4026         args[0] = convert (int4type, args[0]);
4027
4028       /* Convert the SHIFT and SIZE args to INTEGER*4 otherwise we would
4029          need loads of library  functions.  They cannot have values >
4030          BIT_SIZE (I) so the conversion is safe.  */
4031       args[1] = convert (int4type, args[1]);
4032       args[2] = convert (int4type, args[2]);
4033
4034       switch (expr->ts.kind)
4035         {
4036         case 1:
4037         case 2:
4038         case 4:
4039           tmp = gfor_fndecl_math_ishftc4;
4040           break;
4041         case 8:
4042           tmp = gfor_fndecl_math_ishftc8;
4043           break;
4044         case 16:
4045           tmp = gfor_fndecl_math_ishftc16;
4046           break;
4047         default:
4048           gcc_unreachable ();
4049         }
4050       se->expr = build_call_expr_loc (input_location,
4051                                       tmp, 3, args[0], args[1], args[2]);
4052       /* Convert the result back to the original type, if we extended
4053          the first argument's width above.  */
4054       if (expr->ts.kind < 4)
4055         se->expr = convert (type, se->expr);
4056
4057       return;
4058     }
4059   type = TREE_TYPE (args[0]);
4060
4061   /* Evaluate arguments only once.  */
4062   args[0] = gfc_evaluate_now (args[0], &se->pre);
4063   args[1] = gfc_evaluate_now (args[1], &se->pre);
4064
4065   /* Rotate left if positive.  */
4066   lrot = fold_build2_loc (input_location, LROTATE_EXPR, type, args[0], args[1]);
4067
4068   /* Rotate right if negative.  */
4069   tmp = fold_build1_loc (input_location, NEGATE_EXPR, TREE_TYPE (args[1]),
4070                          args[1]);
4071   rrot = fold_build2_loc (input_location,RROTATE_EXPR, type, args[0], tmp);
4072
4073   zero = build_int_cst (TREE_TYPE (args[1]), 0);
4074   tmp = fold_build2_loc (input_location, GT_EXPR, boolean_type_node, args[1],
4075                          zero);
4076   rrot = fold_build3_loc (input_location, COND_EXPR, type, tmp, lrot, rrot);
4077
4078   /* Do nothing if shift == 0.  */
4079   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, args[1],
4080                          zero);
4081   se->expr = fold_build3_loc (input_location, COND_EXPR, type, tmp, args[0],
4082                               rrot);
4083 }
4084
4085
4086 /* LEADZ (i) = (i == 0) ? BIT_SIZE (i)
4087                         : __builtin_clz(i) - (BIT_SIZE('int') - BIT_SIZE(i))
4088
4089    The conditional expression is necessary because the result of LEADZ(0)
4090    is defined, but the result of __builtin_clz(0) is undefined for most
4091    targets.
4092
4093    For INTEGER kinds smaller than the C 'int' type, we have to subtract the
4094    difference in bit size between the argument of LEADZ and the C int.  */
4095  
4096 static void
4097 gfc_conv_intrinsic_leadz (gfc_se * se, gfc_expr * expr)
4098 {
4099   tree arg;
4100   tree arg_type;
4101   tree cond;
4102   tree result_type;
4103   tree leadz;
4104   tree bit_size;
4105   tree tmp;
4106   tree func;
4107   int s, argsize;
4108
4109   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4110   argsize = TYPE_PRECISION (TREE_TYPE (arg));
4111
4112   /* Which variant of __builtin_clz* should we call?  */
4113   if (argsize <= INT_TYPE_SIZE)
4114     {
4115       arg_type = unsigned_type_node;
4116       func = builtin_decl_explicit (BUILT_IN_CLZ);
4117     }
4118   else if (argsize <= LONG_TYPE_SIZE)
4119     {
4120       arg_type = long_unsigned_type_node;
4121       func = builtin_decl_explicit (BUILT_IN_CLZL);
4122     }
4123   else if (argsize <= LONG_LONG_TYPE_SIZE)
4124     {
4125       arg_type = long_long_unsigned_type_node;
4126       func = builtin_decl_explicit (BUILT_IN_CLZLL);
4127     }
4128   else
4129     {
4130       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
4131       arg_type = gfc_build_uint_type (argsize);
4132       func = NULL_TREE;
4133     }
4134
4135   /* Convert the actual argument twice: first, to the unsigned type of the
4136      same size; then, to the proper argument type for the built-in
4137      function.  But the return type is of the default INTEGER kind.  */
4138   arg = fold_convert (gfc_build_uint_type (argsize), arg);
4139   arg = fold_convert (arg_type, arg);
4140   arg = gfc_evaluate_now (arg, &se->pre);
4141   result_type = gfc_get_int_type (gfc_default_integer_kind);
4142
4143   /* Compute LEADZ for the case i .ne. 0.  */
4144   if (func)
4145     {
4146       s = TYPE_PRECISION (arg_type) - argsize;
4147       tmp = fold_convert (result_type,
4148                           build_call_expr_loc (input_location, func,
4149                                                1, arg));
4150       leadz = fold_build2_loc (input_location, MINUS_EXPR, result_type,
4151                                tmp, build_int_cst (result_type, s));
4152     }
4153   else
4154     {
4155       /* We end up here if the argument type is larger than 'long long'.
4156          We generate this code:
4157   
4158             if (x & (ULL_MAX << ULL_SIZE) != 0)
4159               return clzll ((unsigned long long) (x >> ULLSIZE));
4160             else
4161               return ULL_SIZE + clzll ((unsigned long long) x);
4162          where ULL_MAX is the largest value that a ULL_MAX can hold
4163          (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
4164          is the bit-size of the long long type (64 in this example).  */
4165       tree ullsize, ullmax, tmp1, tmp2, btmp;
4166
4167       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
4168       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
4169                                 long_long_unsigned_type_node,
4170                                 build_int_cst (long_long_unsigned_type_node,
4171                                                0));
4172
4173       cond = fold_build2_loc (input_location, LSHIFT_EXPR, arg_type,
4174                               fold_convert (arg_type, ullmax), ullsize);
4175       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type,
4176                               arg, cond);
4177       cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
4178                               cond, build_int_cst (arg_type, 0));
4179
4180       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
4181                               arg, ullsize);
4182       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
4183       btmp = builtin_decl_explicit (BUILT_IN_CLZLL);
4184       tmp1 = fold_convert (result_type,
4185                            build_call_expr_loc (input_location, btmp, 1, tmp1));
4186
4187       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
4188       btmp = builtin_decl_explicit (BUILT_IN_CLZLL);
4189       tmp2 = fold_convert (result_type,
4190                            build_call_expr_loc (input_location, btmp, 1, tmp2));
4191       tmp2 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
4192                               tmp2, ullsize);
4193
4194       leadz = fold_build3_loc (input_location, COND_EXPR, result_type,
4195                                cond, tmp1, tmp2);
4196     }
4197
4198   /* Build BIT_SIZE.  */
4199   bit_size = build_int_cst (result_type, argsize);
4200
4201   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
4202                           arg, build_int_cst (arg_type, 0));
4203   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
4204                               bit_size, leadz);
4205 }
4206
4207
4208 /* TRAILZ(i) = (i == 0) ? BIT_SIZE (i) : __builtin_ctz(i)
4209
4210    The conditional expression is necessary because the result of TRAILZ(0)
4211    is defined, but the result of __builtin_ctz(0) is undefined for most
4212    targets.  */
4213  
4214 static void
4215 gfc_conv_intrinsic_trailz (gfc_se * se, gfc_expr *expr)
4216 {
4217   tree arg;
4218   tree arg_type;
4219   tree cond;
4220   tree result_type;
4221   tree trailz;
4222   tree bit_size;
4223   tree func;
4224   int argsize;
4225
4226   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4227   argsize = TYPE_PRECISION (TREE_TYPE (arg));
4228
4229   /* Which variant of __builtin_ctz* should we call?  */
4230   if (argsize <= INT_TYPE_SIZE)
4231     {
4232       arg_type = unsigned_type_node;
4233       func = builtin_decl_explicit (BUILT_IN_CTZ);
4234     }
4235   else if (argsize <= LONG_TYPE_SIZE)
4236     {
4237       arg_type = long_unsigned_type_node;
4238       func = builtin_decl_explicit (BUILT_IN_CTZL);
4239     }
4240   else if (argsize <= LONG_LONG_TYPE_SIZE)
4241     {
4242       arg_type = long_long_unsigned_type_node;
4243       func = builtin_decl_explicit (BUILT_IN_CTZLL);
4244     }
4245   else
4246     {
4247       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
4248       arg_type = gfc_build_uint_type (argsize);
4249       func = NULL_TREE;
4250     }
4251
4252   /* Convert the actual argument twice: first, to the unsigned type of the
4253      same size; then, to the proper argument type for the built-in
4254      function.  But the return type is of the default INTEGER kind.  */
4255   arg = fold_convert (gfc_build_uint_type (argsize), arg);
4256   arg = fold_convert (arg_type, arg);
4257   arg = gfc_evaluate_now (arg, &se->pre);
4258   result_type = gfc_get_int_type (gfc_default_integer_kind);
4259
4260   /* Compute TRAILZ for the case i .ne. 0.  */
4261   if (func)
4262     trailz = fold_convert (result_type, build_call_expr_loc (input_location,
4263                                                              func, 1, arg));
4264   else
4265     {
4266       /* We end up here if the argument type is larger than 'long long'.
4267          We generate this code:
4268   
4269             if ((x & ULL_MAX) == 0)
4270               return ULL_SIZE + ctzll ((unsigned long long) (x >> ULLSIZE));
4271             else
4272               return ctzll ((unsigned long long) x);
4273
4274          where ULL_MAX is the largest value that a ULL_MAX can hold
4275          (0xFFFFFFFFFFFFFFFF for a 64-bit long long type), and ULLSIZE
4276          is the bit-size of the long long type (64 in this example).  */
4277       tree ullsize, ullmax, tmp1, tmp2, btmp;
4278
4279       ullsize = build_int_cst (result_type, LONG_LONG_TYPE_SIZE);
4280       ullmax = fold_build1_loc (input_location, BIT_NOT_EXPR,
4281                                 long_long_unsigned_type_node,
4282                                 build_int_cst (long_long_unsigned_type_node, 0));
4283
4284       cond = fold_build2_loc (input_location, BIT_AND_EXPR, arg_type, arg,
4285                               fold_convert (arg_type, ullmax));
4286       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, cond,
4287                               build_int_cst (arg_type, 0));
4288
4289       tmp1 = fold_build2_loc (input_location, RSHIFT_EXPR, arg_type,
4290                               arg, ullsize);
4291       tmp1 = fold_convert (long_long_unsigned_type_node, tmp1);
4292       btmp = builtin_decl_explicit (BUILT_IN_CTZLL);
4293       tmp1 = fold_convert (result_type,
4294                            build_call_expr_loc (input_location, btmp, 1, tmp1));
4295       tmp1 = fold_build2_loc (input_location, PLUS_EXPR, result_type,
4296                               tmp1, ullsize);
4297
4298       tmp2 = fold_convert (long_long_unsigned_type_node, arg);
4299       btmp = builtin_decl_explicit (BUILT_IN_CTZLL);
4300       tmp2 = fold_convert (result_type,
4301                            build_call_expr_loc (input_location, btmp, 1, tmp2));
4302
4303       trailz = fold_build3_loc (input_location, COND_EXPR, result_type,
4304                                 cond, tmp1, tmp2);
4305     }
4306
4307   /* Build BIT_SIZE.  */
4308   bit_size = build_int_cst (result_type, argsize);
4309
4310   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
4311                           arg, build_int_cst (arg_type, 0));
4312   se->expr = fold_build3_loc (input_location, COND_EXPR, result_type, cond,
4313                               bit_size, trailz);
4314 }
4315
4316 /* Using __builtin_popcount for POPCNT and __builtin_parity for POPPAR;
4317    for types larger than "long long", we call the long long built-in for
4318    the lower and higher bits and combine the result.  */
4319  
4320 static void
4321 gfc_conv_intrinsic_popcnt_poppar (gfc_se * se, gfc_expr *expr, int parity)
4322 {
4323   tree arg;
4324   tree arg_type;
4325   tree result_type;
4326   tree func;
4327   int argsize;
4328
4329   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4330   argsize = TYPE_PRECISION (TREE_TYPE (arg));
4331   result_type = gfc_get_int_type (gfc_default_integer_kind);
4332
4333   /* Which variant of the builtin should we call?  */
4334   if (argsize <= INT_TYPE_SIZE)
4335     {
4336       arg_type = unsigned_type_node;
4337       func = builtin_decl_explicit (parity
4338                                     ? BUILT_IN_PARITY
4339                                     : BUILT_IN_POPCOUNT);
4340     }
4341   else if (argsize <= LONG_TYPE_SIZE)
4342     {
4343       arg_type = long_unsigned_type_node;
4344       func = builtin_decl_explicit (parity
4345                                     ? BUILT_IN_PARITYL
4346                                     : BUILT_IN_POPCOUNTL);
4347     }
4348   else if (argsize <= LONG_LONG_TYPE_SIZE)
4349     {
4350       arg_type = long_long_unsigned_type_node;
4351       func = builtin_decl_explicit (parity
4352                                     ? BUILT_IN_PARITYLL
4353                                     : BUILT_IN_POPCOUNTLL);
4354     }
4355   else
4356     {
4357       /* Our argument type is larger than 'long long', which mean none
4358          of the POPCOUNT builtins covers it.  We thus call the 'long long'
4359          variant multiple times, and add the results.  */
4360       tree utype, arg2, call1, call2;
4361
4362       /* For now, we only cover the case where argsize is twice as large
4363          as 'long long'.  */
4364       gcc_assert (argsize == 2 * LONG_LONG_TYPE_SIZE);
4365
4366       func = builtin_decl_explicit (parity
4367                                     ? BUILT_IN_PARITYLL
4368                                     : BUILT_IN_POPCOUNTLL);
4369
4370       /* Convert it to an integer, and store into a variable.  */
4371       utype = gfc_build_uint_type (argsize);
4372       arg = fold_convert (utype, arg);
4373       arg = gfc_evaluate_now (arg, &se->pre);
4374
4375       /* Call the builtin twice.  */
4376       call1 = build_call_expr_loc (input_location, func, 1,
4377                                    fold_convert (long_long_unsigned_type_node,
4378                                                  arg));
4379
4380       arg2 = fold_build2_loc (input_location, RSHIFT_EXPR, utype, arg,
4381                               build_int_cst (utype, LONG_LONG_TYPE_SIZE));
4382       call2 = build_call_expr_loc (input_location, func, 1,
4383                                    fold_convert (long_long_unsigned_type_node,
4384                                                  arg2));
4385                           
4386       /* Combine the results.  */
4387       if (parity)
4388         se->expr = fold_build2_loc (input_location, BIT_XOR_EXPR, result_type,
4389                                     call1, call2);
4390       else
4391         se->expr = fold_build2_loc (input_location, PLUS_EXPR, result_type,
4392                                     call1, call2);
4393
4394       return;
4395     }
4396
4397   /* Convert the actual argument twice: first, to the unsigned type of the
4398      same size; then, to the proper argument type for the built-in
4399      function.  */
4400   arg = fold_convert (gfc_build_uint_type (argsize), arg);
4401   arg = fold_convert (arg_type, arg);
4402
4403   se->expr = fold_convert (result_type,
4404                            build_call_expr_loc (input_location, func, 1, arg));
4405 }
4406
4407
4408 /* Process an intrinsic with unspecified argument-types that has an optional
4409    argument (which could be of type character), e.g. EOSHIFT.  For those, we
4410    need to append the string length of the optional argument if it is not
4411    present and the type is really character.
4412    primary specifies the position (starting at 1) of the non-optional argument
4413    specifying the type and optional gives the position of the optional
4414    argument in the arglist.  */
4415
4416 static void
4417 conv_generic_with_optional_char_arg (gfc_se* se, gfc_expr* expr,
4418                                      unsigned primary, unsigned optional)
4419 {
4420   gfc_actual_arglist* prim_arg;
4421   gfc_actual_arglist* opt_arg;
4422   unsigned cur_pos;
4423   gfc_actual_arglist* arg;
4424   gfc_symbol* sym;
4425   VEC(tree,gc) *append_args;
4426
4427   /* Find the two arguments given as position.  */
4428   cur_pos = 0;
4429   prim_arg = NULL;
4430   opt_arg = NULL;
4431   for (arg = expr->value.function.actual; arg; arg = arg->next)
4432     {
4433       ++cur_pos;
4434
4435       if (cur_pos == primary)
4436         prim_arg = arg;
4437       if (cur_pos == optional)
4438         opt_arg = arg;
4439
4440       if (cur_pos >= primary && cur_pos >= optional)
4441         break;
4442     }
4443   gcc_assert (prim_arg);
4444   gcc_assert (prim_arg->expr);
4445   gcc_assert (opt_arg);
4446
4447   /* If we do have type CHARACTER and the optional argument is really absent,
4448      append a dummy 0 as string length.  */
4449   append_args = NULL;
4450   if (prim_arg->expr->ts.type == BT_CHARACTER && !opt_arg->expr)
4451     {
4452       tree dummy;
4453
4454       dummy = build_int_cst (gfc_charlen_type_node, 0);
4455       append_args = VEC_alloc (tree, gc, 1);
4456       VEC_quick_push (tree, append_args, dummy);
4457     }
4458
4459   /* Build the call itself.  */
4460   sym = gfc_get_symbol_for_expr (expr);
4461   gfc_conv_procedure_call (se, sym, expr->value.function.actual, expr,
4462                           append_args);
4463   free (sym);
4464 }
4465
4466
4467 /* The length of a character string.  */
4468 static void
4469 gfc_conv_intrinsic_len (gfc_se * se, gfc_expr * expr)
4470 {
4471   tree len;
4472   tree type;
4473   tree decl;
4474   gfc_symbol *sym;
4475   gfc_se argse;
4476   gfc_expr *arg;
4477   gfc_ss *ss;
4478
4479   gcc_assert (!se->ss);
4480
4481   arg = expr->value.function.actual->expr;
4482
4483   type = gfc_typenode_for_spec (&expr->ts);
4484   switch (arg->expr_type)
4485     {
4486     case EXPR_CONSTANT:
4487       len = build_int_cst (gfc_charlen_type_node, arg->value.character.length);
4488       break;
4489
4490     case EXPR_ARRAY:
4491       /* Obtain the string length from the function used by
4492          trans-array.c(gfc_trans_array_constructor).  */
4493       len = NULL_TREE;
4494       get_array_ctor_strlen (&se->pre, arg->value.constructor, &len);
4495       break;
4496
4497     case EXPR_VARIABLE:
4498       if (arg->ref == NULL
4499             || (arg->ref->next == NULL && arg->ref->type == REF_ARRAY))
4500         {
4501           /* This doesn't catch all cases.
4502              See http://gcc.gnu.org/ml/fortran/2004-06/msg00165.html
4503              and the surrounding thread.  */
4504           sym = arg->symtree->n.sym;
4505           decl = gfc_get_symbol_decl (sym);
4506           if (decl == current_function_decl && sym->attr.function
4507                 && (sym->result == sym))
4508             decl = gfc_get_fake_result_decl (sym, 0);
4509
4510           len = sym->ts.u.cl->backend_decl;
4511           gcc_assert (len);
4512           break;
4513         }
4514
4515       /* Otherwise fall through.  */
4516
4517     default:
4518       /* Anybody stupid enough to do this deserves inefficient code.  */
4519       ss = gfc_walk_expr (arg);
4520       gfc_init_se (&argse, se);
4521       if (ss == gfc_ss_terminator)
4522         gfc_conv_expr (&argse, arg);
4523       else
4524         gfc_conv_expr_descriptor (&argse, arg, ss);
4525       gfc_add_block_to_block (&se->pre, &argse.pre);
4526       gfc_add_block_to_block (&se->post, &argse.post);
4527       len = argse.string_length;
4528       break;
4529     }
4530   se->expr = convert (type, len);
4531 }
4532
4533 /* The length of a character string not including trailing blanks.  */
4534 static void
4535 gfc_conv_intrinsic_len_trim (gfc_se * se, gfc_expr * expr)
4536 {
4537   int kind = expr->value.function.actual->expr->ts.kind;
4538   tree args[2], type, fndecl;
4539
4540   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4541   type = gfc_typenode_for_spec (&expr->ts);
4542
4543   if (kind == 1)
4544     fndecl = gfor_fndecl_string_len_trim;
4545   else if (kind == 4)
4546     fndecl = gfor_fndecl_string_len_trim_char4;
4547   else
4548     gcc_unreachable ();
4549
4550   se->expr = build_call_expr_loc (input_location,
4551                               fndecl, 2, args[0], args[1]);
4552   se->expr = convert (type, se->expr);
4553 }
4554
4555
4556 /* Returns the starting position of a substring within a string.  */
4557
4558 static void
4559 gfc_conv_intrinsic_index_scan_verify (gfc_se * se, gfc_expr * expr,
4560                                       tree function)
4561 {
4562   tree logical4_type_node = gfc_get_logical_type (4);
4563   tree type;
4564   tree fndecl;
4565   tree *args;
4566   unsigned int num_args;
4567
4568   args = XALLOCAVEC (tree, 5);
4569
4570   /* Get number of arguments; characters count double due to the
4571      string length argument. Kind= is not passed to the library
4572      and thus ignored.  */
4573   if (expr->value.function.actual->next->next->expr == NULL)
4574     num_args = 4;
4575   else
4576     num_args = 5;
4577
4578   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
4579   type = gfc_typenode_for_spec (&expr->ts);
4580
4581   if (num_args == 4)
4582     args[4] = build_int_cst (logical4_type_node, 0);
4583   else
4584     args[4] = convert (logical4_type_node, args[4]);
4585
4586   fndecl = build_addr (function, current_function_decl);
4587   se->expr = build_call_array_loc (input_location,
4588                                TREE_TYPE (TREE_TYPE (function)), fndecl,
4589                                5, args);
4590   se->expr = convert (type, se->expr);
4591
4592 }
4593
4594 /* The ascii value for a single character.  */
4595 static void
4596 gfc_conv_intrinsic_ichar (gfc_se * se, gfc_expr * expr)
4597 {
4598   tree args[2], type, pchartype;
4599
4600   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4601   gcc_assert (POINTER_TYPE_P (TREE_TYPE (args[1])));
4602   pchartype = gfc_get_pchar_type (expr->value.function.actual->expr->ts.kind);
4603   args[1] = fold_build1_loc (input_location, NOP_EXPR, pchartype, args[1]);
4604   type = gfc_typenode_for_spec (&expr->ts);
4605
4606   se->expr = build_fold_indirect_ref_loc (input_location,
4607                                       args[1]);
4608   se->expr = convert (type, se->expr);
4609 }
4610
4611
4612 /* Intrinsic ISNAN calls __builtin_isnan.  */
4613
4614 static void
4615 gfc_conv_intrinsic_isnan (gfc_se * se, gfc_expr * expr)
4616 {
4617   tree arg;
4618
4619   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4620   se->expr = build_call_expr_loc (input_location,
4621                                   builtin_decl_explicit (BUILT_IN_ISNAN),
4622                                   1, arg);
4623   STRIP_TYPE_NOPS (se->expr);
4624   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
4625 }
4626
4627
4628 /* Intrinsics IS_IOSTAT_END and IS_IOSTAT_EOR just need to compare
4629    their argument against a constant integer value.  */
4630
4631 static void
4632 gfc_conv_has_intvalue (gfc_se * se, gfc_expr * expr, const int value)
4633 {
4634   tree arg;
4635
4636   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4637   se->expr = fold_build2_loc (input_location, EQ_EXPR,
4638                               gfc_typenode_for_spec (&expr->ts),
4639                               arg, build_int_cst (TREE_TYPE (arg), value));
4640 }
4641
4642
4643
4644 /* MERGE (tsource, fsource, mask) = mask ? tsource : fsource.  */
4645
4646 static void
4647 gfc_conv_intrinsic_merge (gfc_se * se, gfc_expr * expr)
4648 {
4649   tree tsource;
4650   tree fsource;
4651   tree mask;
4652   tree type;
4653   tree len, len2;
4654   tree *args;
4655   unsigned int num_args;
4656
4657   num_args = gfc_intrinsic_argument_list_length (expr);
4658   args = XALLOCAVEC (tree, num_args);
4659
4660   gfc_conv_intrinsic_function_args (se, expr, args, num_args);
4661   if (expr->ts.type != BT_CHARACTER)
4662     {
4663       tsource = args[0];
4664       fsource = args[1];
4665       mask = args[2];
4666     }
4667   else
4668     {
4669       /* We do the same as in the non-character case, but the argument
4670          list is different because of the string length arguments. We
4671          also have to set the string length for the result.  */
4672       len = args[0];
4673       tsource = args[1];
4674       len2 = args[2];
4675       fsource = args[3];
4676       mask = args[4];
4677
4678       gfc_trans_same_strlen_check ("MERGE intrinsic", &expr->where, len, len2,
4679                                    &se->pre);
4680       se->string_length = len;
4681     }
4682   type = TREE_TYPE (tsource);
4683   se->expr = fold_build3_loc (input_location, COND_EXPR, type, mask, tsource,
4684                               fold_convert (type, fsource));
4685 }
4686
4687
4688 /* MERGE_BITS (I, J, MASK) = (I & MASK) | (I & (~MASK)).  */
4689
4690 static void
4691 gfc_conv_intrinsic_merge_bits (gfc_se * se, gfc_expr * expr)
4692 {
4693   tree args[3], mask, type;
4694
4695   gfc_conv_intrinsic_function_args (se, expr, args, 3);
4696   mask = gfc_evaluate_now (args[2], &se->pre);
4697
4698   type = TREE_TYPE (args[0]);
4699   gcc_assert (TREE_TYPE (args[1]) == type);
4700   gcc_assert (TREE_TYPE (mask) == type);
4701
4702   args[0] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[0], mask);
4703   args[1] = fold_build2_loc (input_location, BIT_AND_EXPR, type, args[1],
4704                              fold_build1_loc (input_location, BIT_NOT_EXPR,
4705                                               type, mask));
4706   se->expr = fold_build2_loc (input_location, BIT_IOR_EXPR, type,
4707                               args[0], args[1]);
4708 }
4709
4710
4711 /* MASKL(n)  =  n == 0 ? 0 : (~0) << (BIT_SIZE - n)
4712    MASKR(n)  =  n == BIT_SIZE ? ~0 : ~((~0) << n)  */
4713
4714 static void
4715 gfc_conv_intrinsic_mask (gfc_se * se, gfc_expr * expr, int left)
4716 {
4717   tree arg, allones, type, utype, res, cond, bitsize;
4718   int i;
4719  
4720   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4721   arg = gfc_evaluate_now (arg, &se->pre);
4722
4723   type = gfc_get_int_type (expr->ts.kind);
4724   utype = unsigned_type_for (type);
4725
4726   i = gfc_validate_kind (BT_INTEGER, expr->ts.kind, false);
4727   bitsize = build_int_cst (TREE_TYPE (arg), gfc_integer_kinds[i].bit_size);
4728
4729   allones = fold_build1_loc (input_location, BIT_NOT_EXPR, utype,
4730                              build_int_cst (utype, 0));
4731
4732   if (left)
4733     {
4734       /* Left-justified mask.  */
4735       res = fold_build2_loc (input_location, MINUS_EXPR, TREE_TYPE (arg),
4736                              bitsize, arg);
4737       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
4738                              fold_convert (utype, res));
4739
4740       /* Special case arg == 0, because SHIFT_EXPR wants a shift strictly
4741          smaller than type width.  */
4742       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, arg,
4743                               build_int_cst (TREE_TYPE (arg), 0));
4744       res = fold_build3_loc (input_location, COND_EXPR, utype, cond,
4745                              build_int_cst (utype, 0), res);
4746     }
4747   else
4748     {
4749       /* Right-justified mask.  */
4750       res = fold_build2_loc (input_location, LSHIFT_EXPR, utype, allones,
4751                              fold_convert (utype, arg));
4752       res = fold_build1_loc (input_location, BIT_NOT_EXPR, utype, res);
4753
4754       /* Special case agr == bit_size, because SHIFT_EXPR wants a shift
4755          strictly smaller than type width.  */
4756       cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
4757                               arg, bitsize);
4758       res = fold_build3_loc (input_location, COND_EXPR, utype,
4759                              cond, allones, res);
4760     }
4761
4762   se->expr = fold_convert (type, res);
4763 }
4764
4765
4766 /* FRACTION (s) is translated into frexp (s, &dummy_int).  */
4767 static void
4768 gfc_conv_intrinsic_fraction (gfc_se * se, gfc_expr * expr)
4769 {
4770   tree arg, type, tmp, frexp;
4771
4772   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4773
4774   type = gfc_typenode_for_spec (&expr->ts);
4775   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4776   tmp = gfc_create_var (integer_type_node, NULL);
4777   se->expr = build_call_expr_loc (input_location, frexp, 2,
4778                                   fold_convert (type, arg),
4779                                   gfc_build_addr_expr (NULL_TREE, tmp));
4780   se->expr = fold_convert (type, se->expr);
4781 }
4782
4783
4784 /* NEAREST (s, dir) is translated into
4785      tmp = copysign (HUGE_VAL, dir);
4786      return nextafter (s, tmp);
4787  */
4788 static void
4789 gfc_conv_intrinsic_nearest (gfc_se * se, gfc_expr * expr)
4790 {
4791   tree args[2], type, tmp, nextafter, copysign, huge_val;
4792
4793   nextafter = gfc_builtin_decl_for_float_kind (BUILT_IN_NEXTAFTER, expr->ts.kind);
4794   copysign = gfc_builtin_decl_for_float_kind (BUILT_IN_COPYSIGN, expr->ts.kind);
4795
4796   type = gfc_typenode_for_spec (&expr->ts);
4797   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4798
4799   huge_val = gfc_build_inf_or_huge (type, expr->ts.kind);
4800   tmp = build_call_expr_loc (input_location, copysign, 2, huge_val,
4801                              fold_convert (type, args[1]));
4802   se->expr = build_call_expr_loc (input_location, nextafter, 2,
4803                                   fold_convert (type, args[0]), tmp);
4804   se->expr = fold_convert (type, se->expr);
4805 }
4806
4807
4808 /* SPACING (s) is translated into
4809     int e;
4810     if (s == 0)
4811       res = tiny;
4812     else
4813     {
4814       frexp (s, &e);
4815       e = e - prec;
4816       e = MAX_EXPR (e, emin);
4817       res = scalbn (1., e);
4818     }
4819     return res;
4820
4821  where prec is the precision of s, gfc_real_kinds[k].digits,
4822        emin is min_exponent - 1, gfc_real_kinds[k].min_exponent - 1,
4823    and tiny is tiny(s), gfc_real_kinds[k].tiny.  */
4824
4825 static void
4826 gfc_conv_intrinsic_spacing (gfc_se * se, gfc_expr * expr)
4827 {
4828   tree arg, type, prec, emin, tiny, res, e;
4829   tree cond, tmp, frexp, scalbn;
4830   int k;
4831   stmtblock_t block;
4832
4833   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
4834   prec = build_int_cst (integer_type_node, gfc_real_kinds[k].digits);
4835   emin = build_int_cst (integer_type_node, gfc_real_kinds[k].min_exponent - 1);
4836   tiny = gfc_conv_mpfr_to_tree (gfc_real_kinds[k].tiny, expr->ts.kind, 0);
4837
4838   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4839   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4840
4841   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4842   arg = gfc_evaluate_now (arg, &se->pre);
4843
4844   type = gfc_typenode_for_spec (&expr->ts);
4845   e = gfc_create_var (integer_type_node, NULL);
4846   res = gfc_create_var (type, NULL);
4847
4848
4849   /* Build the block for s /= 0.  */
4850   gfc_start_block (&block);
4851   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
4852                              gfc_build_addr_expr (NULL_TREE, e));
4853   gfc_add_expr_to_block (&block, tmp);
4854
4855   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node, e,
4856                          prec);
4857   gfc_add_modify (&block, e, fold_build2_loc (input_location, MAX_EXPR,
4858                                               integer_type_node, tmp, emin));
4859
4860   tmp = build_call_expr_loc (input_location, scalbn, 2,
4861                          build_real_from_int_cst (type, integer_one_node), e);
4862   gfc_add_modify (&block, res, tmp);
4863
4864   /* Finish by building the IF statement.  */
4865   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, arg,
4866                           build_real_from_int_cst (type, integer_zero_node));
4867   tmp = build3_v (COND_EXPR, cond, build2_v (MODIFY_EXPR, res, tiny),
4868                   gfc_finish_block (&block));
4869
4870   gfc_add_expr_to_block (&se->pre, tmp);
4871   se->expr = res;
4872 }
4873
4874
4875 /* RRSPACING (s) is translated into
4876       int e;
4877       real x;
4878       x = fabs (s);
4879       if (x != 0)
4880       {
4881         frexp (s, &e);
4882         x = scalbn (x, precision - e);
4883       }
4884       return x;
4885
4886  where precision is gfc_real_kinds[k].digits.  */
4887
4888 static void
4889 gfc_conv_intrinsic_rrspacing (gfc_se * se, gfc_expr * expr)
4890 {
4891   tree arg, type, e, x, cond, stmt, tmp, frexp, scalbn, fabs;
4892   int prec, k;
4893   stmtblock_t block;
4894
4895   k = gfc_validate_kind (BT_REAL, expr->ts.kind, false);
4896   prec = gfc_real_kinds[k].digits;
4897
4898   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4899   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4900   fabs = gfc_builtin_decl_for_float_kind (BUILT_IN_FABS, expr->ts.kind);
4901
4902   type = gfc_typenode_for_spec (&expr->ts);
4903   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
4904   arg = gfc_evaluate_now (arg, &se->pre);
4905
4906   e = gfc_create_var (integer_type_node, NULL);
4907   x = gfc_create_var (type, NULL);
4908   gfc_add_modify (&se->pre, x,
4909                   build_call_expr_loc (input_location, fabs, 1, arg));
4910
4911
4912   gfc_start_block (&block);
4913   tmp = build_call_expr_loc (input_location, frexp, 2, arg,
4914                              gfc_build_addr_expr (NULL_TREE, e));
4915   gfc_add_expr_to_block (&block, tmp);
4916
4917   tmp = fold_build2_loc (input_location, MINUS_EXPR, integer_type_node,
4918                          build_int_cst (integer_type_node, prec), e);
4919   tmp = build_call_expr_loc (input_location, scalbn, 2, x, tmp);
4920   gfc_add_modify (&block, x, tmp);
4921   stmt = gfc_finish_block (&block);
4922
4923   cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, x,
4924                           build_real_from_int_cst (type, integer_zero_node));
4925   tmp = build3_v (COND_EXPR, cond, stmt, build_empty_stmt (input_location));
4926   gfc_add_expr_to_block (&se->pre, tmp);
4927
4928   se->expr = fold_convert (type, x);
4929 }
4930
4931
4932 /* SCALE (s, i) is translated into scalbn (s, i).  */
4933 static void
4934 gfc_conv_intrinsic_scale (gfc_se * se, gfc_expr * expr)
4935 {
4936   tree args[2], type, scalbn;
4937
4938   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4939
4940   type = gfc_typenode_for_spec (&expr->ts);
4941   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4942   se->expr = build_call_expr_loc (input_location, scalbn, 2,
4943                                   fold_convert (type, args[0]),
4944                                   fold_convert (integer_type_node, args[1]));
4945   se->expr = fold_convert (type, se->expr);
4946 }
4947
4948
4949 /* SET_EXPONENT (s, i) is translated into
4950    scalbn (frexp (s, &dummy_int), i).  */
4951 static void
4952 gfc_conv_intrinsic_set_exponent (gfc_se * se, gfc_expr * expr)
4953 {
4954   tree args[2], type, tmp, frexp, scalbn;
4955
4956   frexp = gfc_builtin_decl_for_float_kind (BUILT_IN_FREXP, expr->ts.kind);
4957   scalbn = gfc_builtin_decl_for_float_kind (BUILT_IN_SCALBN, expr->ts.kind);
4958
4959   type = gfc_typenode_for_spec (&expr->ts);
4960   gfc_conv_intrinsic_function_args (se, expr, args, 2);
4961
4962   tmp = gfc_create_var (integer_type_node, NULL);
4963   tmp = build_call_expr_loc (input_location, frexp, 2,
4964                              fold_convert (type, args[0]),
4965                              gfc_build_addr_expr (NULL_TREE, tmp));
4966   se->expr = build_call_expr_loc (input_location, scalbn, 2, tmp,
4967                                   fold_convert (integer_type_node, args[1]));
4968   se->expr = fold_convert (type, se->expr);
4969 }
4970
4971
4972 static void
4973 gfc_conv_intrinsic_size (gfc_se * se, gfc_expr * expr)
4974 {
4975   gfc_actual_arglist *actual;
4976   tree arg1;
4977   tree type;
4978   tree fncall0;
4979   tree fncall1;
4980   gfc_se argse;
4981   gfc_ss *ss;
4982
4983   gfc_init_se (&argse, NULL);
4984   actual = expr->value.function.actual;
4985
4986   ss = gfc_walk_expr (actual->expr);
4987   gcc_assert (ss != gfc_ss_terminator);
4988   argse.want_pointer = 1;
4989   argse.data_not_needed = 1;
4990   gfc_conv_expr_descriptor (&argse, actual->expr, ss);
4991   gfc_add_block_to_block (&se->pre, &argse.pre);
4992   gfc_add_block_to_block (&se->post, &argse.post);
4993   arg1 = gfc_evaluate_now (argse.expr, &se->pre);
4994
4995   /* Build the call to size0.  */
4996   fncall0 = build_call_expr_loc (input_location,
4997                              gfor_fndecl_size0, 1, arg1);
4998
4999   actual = actual->next;
5000
5001   if (actual->expr)
5002     {
5003       gfc_init_se (&argse, NULL);
5004       gfc_conv_expr_type (&argse, actual->expr,
5005                           gfc_array_index_type);
5006       gfc_add_block_to_block (&se->pre, &argse.pre);
5007
5008       /* Unusually, for an intrinsic, size does not exclude
5009          an optional arg2, so we must test for it.  */  
5010       if (actual->expr->expr_type == EXPR_VARIABLE
5011             && actual->expr->symtree->n.sym->attr.dummy
5012             && actual->expr->symtree->n.sym->attr.optional)
5013         {
5014           tree tmp;
5015           /* Build the call to size1.  */
5016           fncall1 = build_call_expr_loc (input_location,
5017                                      gfor_fndecl_size1, 2,
5018                                      arg1, argse.expr);
5019
5020           gfc_init_se (&argse, NULL);
5021           argse.want_pointer = 1;
5022           argse.data_not_needed = 1;
5023           gfc_conv_expr (&argse, actual->expr);
5024           gfc_add_block_to_block (&se->pre, &argse.pre);
5025           tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
5026                                  argse.expr, null_pointer_node);
5027           tmp = gfc_evaluate_now (tmp, &se->pre);
5028           se->expr = fold_build3_loc (input_location, COND_EXPR,
5029                                       pvoid_type_node, tmp, fncall1, fncall0);
5030         }
5031       else
5032         {
5033           se->expr = NULL_TREE;
5034           argse.expr = fold_build2_loc (input_location, MINUS_EXPR,
5035                                         gfc_array_index_type,
5036                                         argse.expr, gfc_index_one_node);
5037         }
5038     }
5039   else if (expr->value.function.actual->expr->rank == 1)
5040     {
5041       argse.expr = gfc_index_zero_node;
5042       se->expr = NULL_TREE;
5043     }
5044   else
5045     se->expr = fncall0;
5046
5047   if (se->expr == NULL_TREE)
5048     {
5049       tree ubound, lbound;
5050
5051       arg1 = build_fold_indirect_ref_loc (input_location,
5052                                       arg1);
5053       ubound = gfc_conv_descriptor_ubound_get (arg1, argse.expr);
5054       lbound = gfc_conv_descriptor_lbound_get (arg1, argse.expr);
5055       se->expr = fold_build2_loc (input_location, MINUS_EXPR,
5056                                   gfc_array_index_type, ubound, lbound);
5057       se->expr = fold_build2_loc (input_location, PLUS_EXPR,
5058                                   gfc_array_index_type,
5059                                   se->expr, gfc_index_one_node);
5060       se->expr = fold_build2_loc (input_location, MAX_EXPR,
5061                                   gfc_array_index_type, se->expr,
5062                                   gfc_index_zero_node);
5063     }
5064
5065   type = gfc_typenode_for_spec (&expr->ts);
5066   se->expr = convert (type, se->expr);
5067 }
5068
5069
5070 /* Helper function to compute the size of a character variable,
5071    excluding the terminating null characters.  The result has
5072    gfc_array_index_type type.  */
5073
5074 static tree
5075 size_of_string_in_bytes (int kind, tree string_length)
5076 {
5077   tree bytesize;
5078   int i = gfc_validate_kind (BT_CHARACTER, kind, false);
5079  
5080   bytesize = build_int_cst (gfc_array_index_type,
5081                             gfc_character_kinds[i].bit_size / 8);
5082
5083   return fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
5084                           bytesize,
5085                           fold_convert (gfc_array_index_type, string_length));
5086 }
5087
5088
5089 static void
5090 gfc_conv_intrinsic_sizeof (gfc_se *se, gfc_expr *expr)
5091 {
5092   gfc_expr *arg;
5093   gfc_ss *ss;
5094   gfc_se argse;
5095   tree source_bytes;
5096   tree type;
5097   tree tmp;
5098   tree lower;
5099   tree upper;
5100   int n;
5101
5102   arg = expr->value.function.actual->expr;
5103
5104   gfc_init_se (&argse, NULL);
5105   ss = gfc_walk_expr (arg);
5106
5107   if (ss == gfc_ss_terminator)
5108     {
5109       if (arg->ts.type == BT_CLASS)
5110         gfc_add_data_component (arg);
5111
5112       gfc_conv_expr_reference (&argse, arg);
5113
5114       type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
5115                                                  argse.expr));
5116
5117       /* Obtain the source word length.  */
5118       if (arg->ts.type == BT_CHARACTER)
5119         se->expr = size_of_string_in_bytes (arg->ts.kind,
5120                                             argse.string_length);
5121       else
5122         se->expr = fold_convert (gfc_array_index_type, size_in_bytes (type)); 
5123     }
5124   else
5125     {
5126       source_bytes = gfc_create_var (gfc_array_index_type, "bytes");
5127       argse.want_pointer = 0;
5128       gfc_conv_expr_descriptor (&argse, arg, ss);
5129       type = gfc_get_element_type (TREE_TYPE (argse.expr));
5130
5131       /* Obtain the argument's word length.  */
5132       if (arg->ts.type == BT_CHARACTER)
5133         tmp = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
5134       else
5135         tmp = fold_convert (gfc_array_index_type,
5136                             size_in_bytes (type)); 
5137       gfc_add_modify (&argse.pre, source_bytes, tmp);
5138
5139       /* Obtain the size of the array in bytes.  */
5140       for (n = 0; n < arg->rank; n++)
5141         {
5142           tree idx;
5143           idx = gfc_rank_cst[n];
5144           lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
5145           upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
5146           tmp = fold_build2_loc (input_location, MINUS_EXPR,
5147                                  gfc_array_index_type, upper, lower);
5148           tmp = fold_build2_loc (input_location, PLUS_EXPR,
5149                                  gfc_array_index_type, tmp, gfc_index_one_node);
5150           tmp = fold_build2_loc (input_location, MULT_EXPR,
5151                                  gfc_array_index_type, tmp, source_bytes);
5152           gfc_add_modify (&argse.pre, source_bytes, tmp);
5153         }
5154       se->expr = source_bytes;
5155     }
5156
5157   gfc_add_block_to_block (&se->pre, &argse.pre);
5158 }
5159
5160
5161 static void
5162 gfc_conv_intrinsic_storage_size (gfc_se *se, gfc_expr *expr)
5163 {
5164   gfc_expr *arg;
5165   gfc_ss *ss;
5166   gfc_se argse,eight;
5167   tree type, result_type, tmp;
5168
5169   arg = expr->value.function.actual->expr;
5170   gfc_init_se (&eight, NULL);
5171   gfc_conv_expr (&eight, gfc_get_int_expr (expr->ts.kind, NULL, 8));
5172   
5173   gfc_init_se (&argse, NULL);
5174   ss = gfc_walk_expr (arg);
5175   result_type = gfc_get_int_type (expr->ts.kind);
5176
5177   if (ss == gfc_ss_terminator)
5178     {
5179       if (arg->ts.type == BT_CLASS)
5180       {
5181         gfc_add_vptr_component (arg);
5182         gfc_add_size_component (arg);
5183         gfc_conv_expr (&argse, arg);
5184         tmp = fold_convert (result_type, argse.expr);
5185         goto done;
5186       }
5187
5188       gfc_conv_expr_reference (&argse, arg);
5189       type = TREE_TYPE (build_fold_indirect_ref_loc (input_location, 
5190                                                      argse.expr));
5191     }
5192   else
5193     {
5194       argse.want_pointer = 0;
5195       gfc_conv_expr_descriptor (&argse, arg, ss);
5196       type = gfc_get_element_type (TREE_TYPE (argse.expr));
5197     }
5198     
5199   /* Obtain the argument's word length.  */
5200   if (arg->ts.type == BT_CHARACTER)
5201     tmp = size_of_string_in_bytes (arg->ts.kind, argse.string_length);
5202   else
5203     tmp = fold_convert (result_type, size_in_bytes (type)); 
5204
5205 done:
5206   se->expr = fold_build2_loc (input_location, MULT_EXPR, result_type, tmp,
5207                               eight.expr);
5208   gfc_add_block_to_block (&se->pre, &argse.pre);
5209 }
5210
5211
5212 /* Intrinsic string comparison functions.  */
5213
5214 static void
5215 gfc_conv_intrinsic_strcmp (gfc_se * se, gfc_expr * expr, enum tree_code op)
5216 {
5217   tree args[4];
5218
5219   gfc_conv_intrinsic_function_args (se, expr, args, 4);
5220
5221   se->expr
5222     = gfc_build_compare_string (args[0], args[1], args[2], args[3],
5223                                 expr->value.function.actual->expr->ts.kind,
5224                                 op);
5225   se->expr = fold_build2_loc (input_location, op,
5226                               gfc_typenode_for_spec (&expr->ts), se->expr,
5227                               build_int_cst (TREE_TYPE (se->expr), 0));
5228 }
5229
5230 /* Generate a call to the adjustl/adjustr library function.  */
5231 static void
5232 gfc_conv_intrinsic_adjust (gfc_se * se, gfc_expr * expr, tree fndecl)
5233 {
5234   tree args[3];
5235   tree len;
5236   tree type;
5237   tree var;
5238   tree tmp;
5239
5240   gfc_conv_intrinsic_function_args (se, expr, &args[1], 2);
5241   len = args[1];
5242
5243   type = TREE_TYPE (args[2]);
5244   var = gfc_conv_string_tmp (se, type, len);
5245   args[0] = var;
5246
5247   tmp = build_call_expr_loc (input_location,
5248                          fndecl, 3, args[0], args[1], args[2]);
5249   gfc_add_expr_to_block (&se->pre, tmp);
5250   se->expr = var;
5251   se->string_length = len;
5252 }
5253
5254
5255 /* Generate code for the TRANSFER intrinsic:
5256         For scalar results:
5257           DEST = TRANSFER (SOURCE, MOLD)
5258         where:
5259           typeof<DEST> = typeof<MOLD>
5260         and:
5261           MOLD is scalar.
5262
5263         For array results:
5264           DEST(1:N) = TRANSFER (SOURCE, MOLD[, SIZE])
5265         where:
5266           typeof<DEST> = typeof<MOLD>
5267         and:
5268           N = min (sizeof (SOURCE(:)), sizeof (DEST(:)),
5269               sizeof (DEST(0) * SIZE).  */
5270 static void
5271 gfc_conv_intrinsic_transfer (gfc_se * se, gfc_expr * expr)
5272 {
5273   tree tmp;
5274   tree tmpdecl;
5275   tree ptr;
5276   tree extent;
5277   tree source;
5278   tree source_type;
5279   tree source_bytes;
5280   tree mold_type;
5281   tree dest_word_len;
5282   tree size_words;
5283   tree size_bytes;
5284   tree upper;
5285   tree lower;
5286   tree stmt;
5287   gfc_actual_arglist *arg;
5288   gfc_se argse;
5289   gfc_ss *ss;
5290   gfc_array_info *info;
5291   stmtblock_t block;
5292   int n;
5293   bool scalar_mold;
5294
5295   info = NULL;
5296   if (se->loop)
5297     info = &se->ss->info->data.array;
5298
5299   /* Convert SOURCE.  The output from this stage is:-
5300         source_bytes = length of the source in bytes
5301         source = pointer to the source data.  */
5302   arg = expr->value.function.actual;
5303
5304   /* Ensure double transfer through LOGICAL preserves all
5305      the needed bits.  */
5306   if (arg->expr->expr_type == EXPR_FUNCTION
5307         && arg->expr->value.function.esym == NULL
5308         && arg->expr->value.function.isym != NULL
5309         && arg->expr->value.function.isym->id == GFC_ISYM_TRANSFER
5310         && arg->expr->ts.type == BT_LOGICAL
5311         && expr->ts.type != arg->expr->ts.type)
5312     arg->expr->value.function.name = "__transfer_in_transfer";
5313
5314   gfc_init_se (&argse, NULL);
5315   ss = gfc_walk_expr (arg->expr);
5316
5317   source_bytes = gfc_create_var (gfc_array_index_type, NULL);
5318
5319   /* Obtain the pointer to source and the length of source in bytes.  */
5320   if (ss == gfc_ss_terminator)
5321     {
5322       gfc_conv_expr_reference (&argse, arg->expr);
5323       source = argse.expr;
5324
5325       source_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
5326                                                         argse.expr));
5327
5328       /* Obtain the source word length.  */
5329       if (arg->expr->ts.type == BT_CHARACTER)
5330         tmp = size_of_string_in_bytes (arg->expr->ts.kind,
5331                                        argse.string_length);
5332       else
5333         tmp = fold_convert (gfc_array_index_type,
5334                             size_in_bytes (source_type)); 
5335     }
5336   else
5337     {
5338       argse.want_pointer = 0;
5339       gfc_conv_expr_descriptor (&argse, arg->expr, ss);
5340       source = gfc_conv_descriptor_data_get (argse.expr);
5341       source_type = gfc_get_element_type (TREE_TYPE (argse.expr));
5342
5343       /* Repack the source if not a full variable array.  */
5344       if (arg->expr->expr_type == EXPR_VARIABLE
5345               && arg->expr->ref->u.ar.type != AR_FULL)
5346         {
5347           tmp = gfc_build_addr_expr (NULL_TREE, argse.expr);
5348
5349           if (gfc_option.warn_array_temp)
5350             gfc_warning ("Creating array temporary at %L", &expr->where);
5351
5352           source = build_call_expr_loc (input_location,
5353                                     gfor_fndecl_in_pack, 1, tmp);
5354           source = gfc_evaluate_now (source, &argse.pre);
5355
5356           /* Free the temporary.  */
5357           gfc_start_block (&block);
5358           tmp = gfc_call_free (convert (pvoid_type_node, source));
5359           gfc_add_expr_to_block (&block, tmp);
5360           stmt = gfc_finish_block (&block);
5361
5362           /* Clean up if it was repacked.  */
5363           gfc_init_block (&block);
5364           tmp = gfc_conv_array_data (argse.expr);
5365           tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
5366                                  source, tmp);
5367           tmp = build3_v (COND_EXPR, tmp, stmt,
5368                           build_empty_stmt (input_location));
5369           gfc_add_expr_to_block (&block, tmp);
5370           gfc_add_block_to_block (&block, &se->post);
5371           gfc_init_block (&se->post);
5372           gfc_add_block_to_block (&se->post, &block);
5373         }
5374
5375       /* Obtain the source word length.  */
5376       if (arg->expr->ts.type == BT_CHARACTER)
5377         tmp = size_of_string_in_bytes (arg->expr->ts.kind,
5378                                        argse.string_length);
5379       else
5380         tmp = fold_convert (gfc_array_index_type,
5381                             size_in_bytes (source_type)); 
5382
5383       /* Obtain the size of the array in bytes.  */
5384       extent = gfc_create_var (gfc_array_index_type, NULL);
5385       for (n = 0; n < arg->expr->rank; n++)
5386         {
5387           tree idx;
5388           idx = gfc_rank_cst[n];
5389           gfc_add_modify (&argse.pre, source_bytes, tmp);
5390           lower = gfc_conv_descriptor_lbound_get (argse.expr, idx);
5391           upper = gfc_conv_descriptor_ubound_get (argse.expr, idx);
5392           tmp = fold_build2_loc (input_location, MINUS_EXPR,
5393                                  gfc_array_index_type, upper, lower);
5394           gfc_add_modify (&argse.pre, extent, tmp);
5395           tmp = fold_build2_loc (input_location, PLUS_EXPR,
5396                                  gfc_array_index_type, extent,
5397                                  gfc_index_one_node);
5398           tmp = fold_build2_loc (input_location, MULT_EXPR,
5399                                  gfc_array_index_type, tmp, source_bytes);
5400         }
5401     }
5402
5403   gfc_add_modify (&argse.pre, source_bytes, tmp);
5404   gfc_add_block_to_block (&se->pre, &argse.pre);
5405   gfc_add_block_to_block (&se->post, &argse.post);
5406
5407   /* Now convert MOLD.  The outputs are:
5408         mold_type = the TREE type of MOLD
5409         dest_word_len = destination word length in bytes.  */
5410   arg = arg->next;
5411
5412   gfc_init_se (&argse, NULL);
5413   ss = gfc_walk_expr (arg->expr);
5414
5415   scalar_mold = arg->expr->rank == 0;
5416
5417   if (ss == gfc_ss_terminator)
5418     {
5419       gfc_conv_expr_reference (&argse, arg->expr);
5420       mold_type = TREE_TYPE (build_fold_indirect_ref_loc (input_location,
5421                                                       argse.expr));
5422     }
5423   else
5424     {
5425       gfc_init_se (&argse, NULL);
5426       argse.want_pointer = 0;
5427       gfc_conv_expr_descriptor (&argse, arg->expr, ss);
5428       mold_type = gfc_get_element_type (TREE_TYPE (argse.expr));
5429     }
5430
5431   gfc_add_block_to_block (&se->pre, &argse.pre);
5432   gfc_add_block_to_block (&se->post, &argse.post);
5433
5434   if (strcmp (expr->value.function.name, "__transfer_in_transfer") == 0)
5435     {
5436       /* If this TRANSFER is nested in another TRANSFER, use a type
5437          that preserves all bits.  */
5438       if (arg->expr->ts.type == BT_LOGICAL)
5439         mold_type = gfc_get_int_type (arg->expr->ts.kind);
5440     }
5441
5442   if (arg->expr->ts.type == BT_CHARACTER)
5443     {
5444       tmp = size_of_string_in_bytes (arg->expr->ts.kind, argse.string_length);
5445       mold_type = gfc_get_character_type_len (arg->expr->ts.kind, tmp);
5446     }
5447   else
5448     tmp = fold_convert (gfc_array_index_type,
5449                         size_in_bytes (mold_type)); 
5450  
5451   dest_word_len = gfc_create_var (gfc_array_index_type, NULL);
5452   gfc_add_modify (&se->pre, dest_word_len, tmp);
5453
5454   /* Finally convert SIZE, if it is present.  */
5455   arg = arg->next;
5456   size_words = gfc_create_var (gfc_array_index_type, NULL);
5457
5458   if (arg->expr)
5459     {
5460       gfc_init_se (&argse, NULL);
5461       gfc_conv_expr_reference (&argse, arg->expr);
5462       tmp = convert (gfc_array_index_type,
5463                      build_fold_indirect_ref_loc (input_location,
5464                                               argse.expr));
5465       gfc_add_block_to_block (&se->pre, &argse.pre);
5466       gfc_add_block_to_block (&se->post, &argse.post);
5467     }
5468   else
5469     tmp = NULL_TREE;
5470
5471   /* Separate array and scalar results.  */
5472   if (scalar_mold && tmp == NULL_TREE)
5473     goto scalar_transfer;
5474
5475   size_bytes = gfc_create_var (gfc_array_index_type, NULL);
5476   if (tmp != NULL_TREE)
5477     tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_array_index_type,
5478                            tmp, dest_word_len);
5479   else
5480     tmp = source_bytes;
5481
5482   gfc_add_modify (&se->pre, size_bytes, tmp);
5483   gfc_add_modify (&se->pre, size_words,
5484                        fold_build2_loc (input_location, CEIL_DIV_EXPR,
5485                                         gfc_array_index_type,
5486                                         size_bytes, dest_word_len));
5487
5488   /* Evaluate the bounds of the result.  If the loop range exists, we have
5489      to check if it is too large.  If so, we modify loop->to be consistent
5490      with min(size, size(source)).  Otherwise, size is made consistent with
5491      the loop range, so that the right number of bytes is transferred.*/
5492   n = se->loop->order[0];
5493   if (se->loop->to[n] != NULL_TREE)
5494     {
5495       tmp = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5496                              se->loop->to[n], se->loop->from[n]);
5497       tmp = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
5498                              tmp, gfc_index_one_node);
5499       tmp = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
5500                          tmp, size_words);
5501       gfc_add_modify (&se->pre, size_words, tmp);
5502       gfc_add_modify (&se->pre, size_bytes,
5503                            fold_build2_loc (input_location, MULT_EXPR,
5504                                             gfc_array_index_type,
5505                                             size_words, dest_word_len));
5506       upper = fold_build2_loc (input_location, PLUS_EXPR, gfc_array_index_type,
5507                                size_words, se->loop->from[n]);
5508       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5509                                upper, gfc_index_one_node);
5510     }
5511   else
5512     {
5513       upper = fold_build2_loc (input_location, MINUS_EXPR, gfc_array_index_type,
5514                                size_words, gfc_index_one_node);
5515       se->loop->from[n] = gfc_index_zero_node;
5516     }
5517
5518   se->loop->to[n] = upper;
5519
5520   /* Build a destination descriptor, using the pointer, source, as the
5521      data field.  */
5522   gfc_trans_create_temp_array (&se->pre, &se->post, se->ss, mold_type,
5523                                NULL_TREE, false, true, false, &expr->where);
5524
5525   /* Cast the pointer to the result.  */
5526   tmp = gfc_conv_descriptor_data_get (info->descriptor);
5527   tmp = fold_convert (pvoid_type_node, tmp);
5528
5529   /* Use memcpy to do the transfer.  */
5530   tmp = build_call_expr_loc (input_location,
5531                          builtin_decl_explicit (BUILT_IN_MEMCPY),
5532                          3,
5533                          tmp,
5534                          fold_convert (pvoid_type_node, source),
5535                          fold_build2_loc (input_location, MIN_EXPR,
5536                                           gfc_array_index_type,
5537                                           size_bytes, source_bytes));
5538   gfc_add_expr_to_block (&se->pre, tmp);
5539
5540   se->expr = info->descriptor;
5541   if (expr->ts.type == BT_CHARACTER)
5542     se->string_length = fold_convert (gfc_charlen_type_node, dest_word_len);
5543
5544   return;
5545
5546 /* Deal with scalar results.  */
5547 scalar_transfer:
5548   extent = fold_build2_loc (input_location, MIN_EXPR, gfc_array_index_type,
5549                             dest_word_len, source_bytes);
5550   extent = fold_build2_loc (input_location, MAX_EXPR, gfc_array_index_type,
5551                             extent, gfc_index_zero_node);
5552
5553   if (expr->ts.type == BT_CHARACTER)
5554     {
5555       tree direct;
5556       tree indirect;
5557
5558       ptr = convert (gfc_get_pchar_type (expr->ts.kind), source);
5559       tmpdecl = gfc_create_var (gfc_get_pchar_type (expr->ts.kind),
5560                                 "transfer");
5561
5562       /* If source is longer than the destination, use a pointer to
5563          the source directly.  */
5564       gfc_init_block (&block);
5565       gfc_add_modify (&block, tmpdecl, ptr);
5566       direct = gfc_finish_block (&block);
5567
5568       /* Otherwise, allocate a string with the length of the destination
5569          and copy the source into it.  */
5570       gfc_init_block (&block);
5571       tmp = gfc_get_pchar_type (expr->ts.kind);
5572       tmp = gfc_call_malloc (&block, tmp, dest_word_len);
5573       gfc_add_modify (&block, tmpdecl,
5574                       fold_convert (TREE_TYPE (ptr), tmp));
5575       tmp = build_call_expr_loc (input_location,
5576                              builtin_decl_explicit (BUILT_IN_MEMCPY), 3,
5577                              fold_convert (pvoid_type_node, tmpdecl),
5578                              fold_convert (pvoid_type_node, ptr),
5579                              extent);
5580       gfc_add_expr_to_block (&block, tmp);
5581       indirect = gfc_finish_block (&block);
5582
5583       /* Wrap it up with the condition.  */
5584       tmp = fold_build2_loc (input_location, LE_EXPR, boolean_type_node,
5585                              dest_word_len, source_bytes);
5586       tmp = build3_v (COND_EXPR, tmp, direct, indirect);
5587       gfc_add_expr_to_block (&se->pre, tmp);
5588
5589       se->expr = tmpdecl;
5590       se->string_length = dest_word_len;
5591     }
5592   else
5593     {
5594       tmpdecl = gfc_create_var (mold_type, "transfer");
5595
5596       ptr = convert (build_pointer_type (mold_type), source);
5597
5598       /* Use memcpy to do the transfer.  */
5599       tmp = gfc_build_addr_expr (NULL_TREE, tmpdecl);
5600       tmp = build_call_expr_loc (input_location,
5601                              builtin_decl_explicit (BUILT_IN_MEMCPY), 3,
5602                              fold_convert (pvoid_type_node, tmp),
5603                              fold_convert (pvoid_type_node, ptr),
5604                              extent);
5605       gfc_add_expr_to_block (&se->pre, tmp);
5606
5607       se->expr = tmpdecl;
5608     }
5609 }
5610
5611
5612 /* Generate code for the ALLOCATED intrinsic.
5613    Generate inline code that directly check the address of the argument.  */
5614
5615 static void
5616 gfc_conv_allocated (gfc_se *se, gfc_expr *expr)
5617 {
5618   gfc_actual_arglist *arg1;
5619   gfc_se arg1se;
5620   gfc_ss *ss1;
5621   tree tmp;
5622
5623   gfc_init_se (&arg1se, NULL);
5624   arg1 = expr->value.function.actual;
5625   ss1 = gfc_walk_expr (arg1->expr);
5626
5627   if (ss1 == gfc_ss_terminator)
5628     {
5629       /* Allocatable scalar.  */
5630       arg1se.want_pointer = 1;
5631       if (arg1->expr->ts.type == BT_CLASS)
5632         gfc_add_data_component (arg1->expr);
5633       gfc_conv_expr (&arg1se, arg1->expr);
5634       tmp = arg1se.expr;
5635     }
5636   else
5637     {
5638       /* Allocatable array.  */
5639       arg1se.descriptor_only = 1;
5640       gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5641       tmp = gfc_conv_descriptor_data_get (arg1se.expr);
5642     }
5643
5644   tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp,
5645                          fold_convert (TREE_TYPE (tmp), null_pointer_node));
5646   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
5647 }
5648
5649
5650 /* Generate code for the ASSOCIATED intrinsic.
5651    If both POINTER and TARGET are arrays, generate a call to library function
5652    _gfor_associated, and pass descriptors of POINTER and TARGET to it.
5653    In other cases, generate inline code that directly compare the address of
5654    POINTER with the address of TARGET.  */
5655
5656 static void
5657 gfc_conv_associated (gfc_se *se, gfc_expr *expr)
5658 {
5659   gfc_actual_arglist *arg1;
5660   gfc_actual_arglist *arg2;
5661   gfc_se arg1se;
5662   gfc_se arg2se;
5663   tree tmp2;
5664   tree tmp;
5665   tree nonzero_charlen;
5666   tree nonzero_arraylen;
5667   gfc_ss *ss1, *ss2;
5668
5669   gfc_init_se (&arg1se, NULL);
5670   gfc_init_se (&arg2se, NULL);
5671   arg1 = expr->value.function.actual;
5672   if (arg1->expr->ts.type == BT_CLASS)
5673     gfc_add_data_component (arg1->expr);
5674   arg2 = arg1->next;
5675   ss1 = gfc_walk_expr (arg1->expr);
5676
5677   if (!arg2->expr)
5678     {
5679       /* No optional target.  */
5680       if (ss1 == gfc_ss_terminator)
5681         {
5682           /* A pointer to a scalar.  */
5683           arg1se.want_pointer = 1;
5684           gfc_conv_expr (&arg1se, arg1->expr);
5685           tmp2 = arg1se.expr;
5686         }
5687       else
5688         {
5689           /* A pointer to an array.  */
5690           gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5691           tmp2 = gfc_conv_descriptor_data_get (arg1se.expr);
5692         }
5693       gfc_add_block_to_block (&se->pre, &arg1se.pre);
5694       gfc_add_block_to_block (&se->post, &arg1se.post);
5695       tmp = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, tmp2,
5696                              fold_convert (TREE_TYPE (tmp2), null_pointer_node));
5697       se->expr = tmp;
5698     }
5699   else
5700     {
5701       /* An optional target.  */
5702       if (arg2->expr->ts.type == BT_CLASS)
5703         gfc_add_data_component (arg2->expr);
5704       ss2 = gfc_walk_expr (arg2->expr);
5705
5706       nonzero_charlen = NULL_TREE;
5707       if (arg1->expr->ts.type == BT_CHARACTER)
5708         nonzero_charlen = fold_build2_loc (input_location, NE_EXPR,
5709                                            boolean_type_node,
5710                                            arg1->expr->ts.u.cl->backend_decl,
5711                                            integer_zero_node);
5712
5713       if (ss1 == gfc_ss_terminator)
5714         {
5715           /* A pointer to a scalar.  */
5716           gcc_assert (ss2 == gfc_ss_terminator);
5717           arg1se.want_pointer = 1;
5718           gfc_conv_expr (&arg1se, arg1->expr);
5719           arg2se.want_pointer = 1;
5720           gfc_conv_expr (&arg2se, arg2->expr);
5721           gfc_add_block_to_block (&se->pre, &arg1se.pre);
5722           gfc_add_block_to_block (&se->post, &arg1se.post);
5723           tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
5724                                  arg1se.expr, arg2se.expr);
5725           tmp2 = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
5726                                   arg1se.expr, null_pointer_node);
5727           se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5728                                       boolean_type_node, tmp, tmp2);
5729         }
5730       else
5731         {
5732           /* An array pointer of zero length is not associated if target is
5733              present.  */
5734           arg1se.descriptor_only = 1;
5735           gfc_conv_expr_lhs (&arg1se, arg1->expr);
5736           tmp = gfc_conv_descriptor_stride_get (arg1se.expr,
5737                                             gfc_rank_cst[arg1->expr->rank - 1]);
5738           nonzero_arraylen = fold_build2_loc (input_location, NE_EXPR,
5739                                               boolean_type_node, tmp,
5740                                               build_int_cst (TREE_TYPE (tmp), 0));
5741
5742           /* A pointer to an array, call library function _gfor_associated.  */
5743           gcc_assert (ss2 != gfc_ss_terminator);
5744           arg1se.want_pointer = 1;
5745           gfc_conv_expr_descriptor (&arg1se, arg1->expr, ss1);
5746
5747           arg2se.want_pointer = 1;
5748           gfc_conv_expr_descriptor (&arg2se, arg2->expr, ss2);
5749           gfc_add_block_to_block (&se->pre, &arg2se.pre);
5750           gfc_add_block_to_block (&se->post, &arg2se.post);
5751           se->expr = build_call_expr_loc (input_location,
5752                                       gfor_fndecl_associated, 2,
5753                                       arg1se.expr, arg2se.expr);
5754           se->expr = convert (boolean_type_node, se->expr);
5755           se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5756                                       boolean_type_node, se->expr,
5757                                       nonzero_arraylen);
5758         }
5759
5760       /* If target is present zero character length pointers cannot
5761          be associated.  */
5762       if (nonzero_charlen != NULL_TREE)
5763         se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
5764                                     boolean_type_node,
5765                                     se->expr, nonzero_charlen);
5766     }
5767
5768   se->expr = convert (gfc_typenode_for_spec (&expr->ts), se->expr);
5769 }
5770
5771
5772 /* Generate code for the SAME_TYPE_AS intrinsic.
5773    Generate inline code that directly checks the vindices.  */
5774
5775 static void
5776 gfc_conv_same_type_as (gfc_se *se, gfc_expr *expr)
5777 {
5778   gfc_expr *a, *b;
5779   gfc_se se1, se2;
5780   tree tmp;
5781
5782   gfc_init_se (&se1, NULL);
5783   gfc_init_se (&se2, NULL);
5784
5785   a = expr->value.function.actual->expr;
5786   b = expr->value.function.actual->next->expr;
5787
5788   if (a->ts.type == BT_CLASS)
5789     {
5790       gfc_add_vptr_component (a);
5791       gfc_add_hash_component (a);
5792     }
5793   else if (a->ts.type == BT_DERIVED)
5794     a = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5795                           a->ts.u.derived->hash_value);
5796
5797   if (b->ts.type == BT_CLASS)
5798     {
5799       gfc_add_vptr_component (b);
5800       gfc_add_hash_component (b);
5801     }
5802   else if (b->ts.type == BT_DERIVED)
5803     b = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5804                           b->ts.u.derived->hash_value);
5805
5806   gfc_conv_expr (&se1, a);
5807   gfc_conv_expr (&se2, b);
5808
5809   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
5810                          se1.expr, fold_convert (TREE_TYPE (se1.expr), se2.expr));
5811   se->expr = convert (gfc_typenode_for_spec (&expr->ts), tmp);
5812 }
5813
5814
5815 /* Generate code for SELECTED_CHAR_KIND (NAME) intrinsic function.  */
5816
5817 static void
5818 gfc_conv_intrinsic_sc_kind (gfc_se *se, gfc_expr *expr)
5819 {
5820   tree args[2];
5821
5822   gfc_conv_intrinsic_function_args (se, expr, args, 2);
5823   se->expr = build_call_expr_loc (input_location,
5824                               gfor_fndecl_sc_kind, 2, args[0], args[1]);
5825   se->expr = fold_convert (gfc_typenode_for_spec (&expr->ts), se->expr);
5826 }
5827
5828
5829 /* Generate code for SELECTED_INT_KIND (R) intrinsic function.  */
5830
5831 static void
5832 gfc_conv_intrinsic_si_kind (gfc_se *se, gfc_expr *expr)
5833 {
5834   tree arg, type;
5835
5836   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);
5837
5838   /* The argument to SELECTED_INT_KIND is INTEGER(4).  */
5839   type = gfc_get_int_type (4); 
5840   arg = gfc_build_addr_expr (NULL_TREE, fold_convert (type, arg));
5841
5842   /* Convert it to the required type.  */
5843   type = gfc_typenode_for_spec (&expr->ts);
5844   se->expr = build_call_expr_loc (input_location,
5845                               gfor_fndecl_si_kind, 1, arg);
5846   se->expr = fold_convert (type, se->expr);
5847 }
5848
5849
5850 /* Generate code for SELECTED_REAL_KIND (P, R) intrinsic function.  */
5851
5852 static void
5853 gfc_conv_intrinsic_sr_kind (gfc_se *se, gfc_expr *expr)
5854 {
5855   gfc_actual_arglist *actual;
5856   tree type;
5857   gfc_se argse;
5858   VEC(tree,gc) *args = NULL;
5859
5860   for (actual = expr->value.function.actual; actual; actual = actual->next)
5861     {
5862       gfc_init_se (&argse, se);
5863
5864       /* Pass a NULL pointer for an absent arg.  */
5865       if (actual->expr == NULL)
5866         argse.expr = null_pointer_node;
5867       else
5868         {
5869           gfc_typespec ts;
5870           gfc_clear_ts (&ts);
5871
5872           if (actual->expr->ts.kind != gfc_c_int_kind)
5873             {
5874               /* The arguments to SELECTED_REAL_KIND are INTEGER(4).  */
5875               ts.type = BT_INTEGER;
5876               ts.kind = gfc_c_int_kind;
5877               gfc_convert_type (actual->expr, &ts, 2);
5878             }
5879           gfc_conv_expr_reference (&argse, actual->expr);
5880         } 
5881
5882       gfc_add_block_to_block (&se->pre, &argse.pre);
5883       gfc_add_block_to_block (&se->post, &argse.post);
5884       VEC_safe_push (tree, gc, args, argse.expr);
5885     }
5886
5887   /* Convert it to the required type.  */
5888   type = gfc_typenode_for_spec (&expr->ts);
5889   se->expr = build_call_expr_loc_vec (input_location,
5890                                       gfor_fndecl_sr_kind, args);
5891   se->expr = fold_convert (type, se->expr);
5892 }
5893
5894
5895 /* Generate code for TRIM (A) intrinsic function.  */
5896
5897 static void
5898 gfc_conv_intrinsic_trim (gfc_se * se, gfc_expr * expr)
5899 {
5900   tree var;
5901   tree len;
5902   tree addr;
5903   tree tmp;
5904   tree cond;
5905   tree fndecl;
5906   tree function;
5907   tree *args;
5908   unsigned int num_args;
5909
5910   num_args = gfc_intrinsic_argument_list_length (expr) + 2;
5911   args = XALLOCAVEC (tree, num_args);
5912
5913   var = gfc_create_var (gfc_get_pchar_type (expr->ts.kind), "pstr");
5914   addr = gfc_build_addr_expr (ppvoid_type_node, var);
5915   len = gfc_create_var (gfc_charlen_type_node, "len");
5916
5917   gfc_conv_intrinsic_function_args (se, expr, &args[2], num_args - 2);
5918   args[0] = gfc_build_addr_expr (NULL_TREE, len);
5919   args[1] = addr;
5920
5921   if (expr->ts.kind == 1)
5922     function = gfor_fndecl_string_trim;
5923   else if (expr->ts.kind == 4)
5924     function = gfor_fndecl_string_trim_char4;
5925   else
5926     gcc_unreachable ();
5927
5928   fndecl = build_addr (function, current_function_decl);
5929   tmp = build_call_array_loc (input_location,
5930                           TREE_TYPE (TREE_TYPE (function)), fndecl,
5931                           num_args, args);
5932   gfc_add_expr_to_block (&se->pre, tmp);
5933
5934   /* Free the temporary afterwards, if necessary.  */
5935   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
5936                           len, build_int_cst (TREE_TYPE (len), 0));
5937   tmp = gfc_call_free (var);
5938   tmp = build3_v (COND_EXPR, cond, tmp, build_empty_stmt (input_location));
5939   gfc_add_expr_to_block (&se->post, tmp);
5940
5941   se->expr = var;
5942   se->string_length = len;
5943 }
5944
5945
5946 /* Generate code for REPEAT (STRING, NCOPIES) intrinsic function.  */
5947
5948 static void
5949 gfc_conv_intrinsic_repeat (gfc_se * se, gfc_expr * expr)
5950 {
5951   tree args[3], ncopies, dest, dlen, src, slen, ncopies_type;
5952   tree type, cond, tmp, count, exit_label, n, max, largest;
5953   tree size;
5954   stmtblock_t block, body;
5955   int i;
5956
5957   /* We store in charsize the size of a character.  */
5958   i = gfc_validate_kind (BT_CHARACTER, expr->ts.kind, false);
5959   size = build_int_cst (size_type_node, gfc_character_kinds[i].bit_size / 8);
5960
5961   /* Get the arguments.  */
5962   gfc_conv_intrinsic_function_args (se, expr, args, 3);
5963   slen = fold_convert (size_type_node, gfc_evaluate_now (args[0], &se->pre));
5964   src = args[1];
5965   ncopies = gfc_evaluate_now (args[2], &se->pre);
5966   ncopies_type = TREE_TYPE (ncopies);
5967
5968   /* Check that NCOPIES is not negative.  */
5969   cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node, ncopies,
5970                           build_int_cst (ncopies_type, 0));
5971   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
5972                            "Argument NCOPIES of REPEAT intrinsic is negative "
5973                            "(its value is %lld)",
5974                            fold_convert (long_integer_type_node, ncopies));
5975
5976   /* If the source length is zero, any non negative value of NCOPIES
5977      is valid, and nothing happens.  */
5978   n = gfc_create_var (ncopies_type, "ncopies");
5979   cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, slen,
5980                           build_int_cst (size_type_node, 0));
5981   tmp = fold_build3_loc (input_location, COND_EXPR, ncopies_type, cond,
5982                          build_int_cst (ncopies_type, 0), ncopies);
5983   gfc_add_modify (&se->pre, n, tmp);
5984   ncopies = n;
5985
5986   /* Check that ncopies is not too large: ncopies should be less than
5987      (or equal to) MAX / slen, where MAX is the maximal integer of
5988      the gfc_charlen_type_node type.  If slen == 0, we need a special
5989      case to avoid the division by zero.  */
5990   i = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
5991   max = gfc_conv_mpz_to_tree (gfc_integer_kinds[i].huge, gfc_charlen_int_kind);
5992   max = fold_build2_loc (input_location, TRUNC_DIV_EXPR, size_type_node,
5993                           fold_convert (size_type_node, max), slen);
5994   largest = TYPE_PRECISION (size_type_node) > TYPE_PRECISION (ncopies_type)
5995               ? size_type_node : ncopies_type;
5996   cond = fold_build2_loc (input_location, GT_EXPR, boolean_type_node,
5997                           fold_convert (largest, ncopies),
5998                           fold_convert (largest, max));
5999   tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, slen,
6000                          build_int_cst (size_type_node, 0));
6001   cond = fold_build3_loc (input_location, COND_EXPR, boolean_type_node, tmp,
6002                           boolean_false_node, cond);
6003   gfc_trans_runtime_check (true, false, cond, &se->pre, &expr->where,
6004                            "Argument NCOPIES of REPEAT intrinsic is too large");
6005
6006   /* Compute the destination length.  */
6007   dlen = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
6008                           fold_convert (gfc_charlen_type_node, slen),
6009                           fold_convert (gfc_charlen_type_node, ncopies));
6010   type = gfc_get_character_type (expr->ts.kind, expr->ts.u.cl);
6011   dest = gfc_conv_string_tmp (se, build_pointer_type (type), dlen);
6012
6013   /* Generate the code to do the repeat operation:
6014        for (i = 0; i < ncopies; i++)
6015          memmove (dest + (i * slen * size), src, slen*size);  */
6016   gfc_start_block (&block);
6017   count = gfc_create_var (ncopies_type, "count");
6018   gfc_add_modify (&block, count, build_int_cst (ncopies_type, 0));
6019   exit_label = gfc_build_label_decl (NULL_TREE);
6020
6021   /* Start the loop body.  */
6022   gfc_start_block (&body);
6023
6024   /* Exit the loop if count >= ncopies.  */
6025   cond = fold_build2_loc (input_location, GE_EXPR, boolean_type_node, count,
6026                           ncopies);
6027   tmp = build1_v (GOTO_EXPR, exit_label);
6028   TREE_USED (exit_label) = 1;
6029   tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, cond, tmp,
6030                          build_empty_stmt (input_location));
6031   gfc_add_expr_to_block (&body, tmp);
6032
6033   /* Call memmove (dest + (i*slen*size), src, slen*size).  */
6034   tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
6035                          fold_convert (gfc_charlen_type_node, slen),
6036                          fold_convert (gfc_charlen_type_node, count));
6037   tmp = fold_build2_loc (input_location, MULT_EXPR, gfc_charlen_type_node,
6038                          tmp, fold_convert (gfc_charlen_type_node, size));
6039   tmp = fold_build_pointer_plus_loc (input_location,
6040                                      fold_convert (pvoid_type_node, dest), tmp);
6041   tmp = build_call_expr_loc (input_location,
6042                              builtin_decl_explicit (BUILT_IN_MEMMOVE),
6043                              3, tmp, src,
6044                              fold_build2_loc (input_location, MULT_EXPR,
6045                                               size_type_node, slen,
6046                                               fold_convert (size_type_node,
6047                                                             size)));
6048   gfc_add_expr_to_block (&body, tmp);
6049
6050   /* Increment count.  */
6051   tmp = fold_build2_loc (input_location, PLUS_EXPR, ncopies_type,
6052                          count, build_int_cst (TREE_TYPE (count), 1));
6053   gfc_add_modify (&body, count, tmp);
6054
6055   /* Build the loop.  */
6056   tmp = build1_v (LOOP_EXPR, gfc_finish_block (&body));
6057   gfc_add_expr_to_block (&block, tmp);
6058
6059   /* Add the exit label.  */
6060   tmp = build1_v (LABEL_EXPR, exit_label);
6061   gfc_add_expr_to_block (&block, tmp);
6062
6063   /* Finish the block.  */
6064   tmp = gfc_finish_block (&block);
6065   gfc_add_expr_to_block (&se->pre, tmp);
6066
6067   /* Set the result value.  */
6068   se->expr = dest;
6069   se->string_length = dlen;
6070 }
6071
6072
6073 /* Generate code for the IARGC intrinsic.  */
6074
6075 static void
6076 gfc_conv_intrinsic_iargc (gfc_se * se, gfc_expr * expr)
6077 {
6078   tree tmp;
6079   tree fndecl;
6080   tree type;
6081
6082   /* Call the library function.  This always returns an INTEGER(4).  */
6083   fndecl = gfor_fndecl_iargc;
6084   tmp = build_call_expr_loc (input_location,
6085                          fndecl, 0);
6086
6087   /* Convert it to the required type.  */
6088   type = gfc_typenode_for_spec (&expr->ts);
6089   tmp = fold_convert (type, tmp);
6090
6091   se->expr = tmp;
6092 }
6093
6094
6095 /* The loc intrinsic returns the address of its argument as
6096    gfc_index_integer_kind integer.  */
6097
6098 static void
6099 gfc_conv_intrinsic_loc (gfc_se * se, gfc_expr * expr)
6100 {
6101   tree temp_var;
6102   gfc_expr *arg_expr;
6103   gfc_ss *ss;
6104
6105   gcc_assert (!se->ss);
6106
6107   arg_expr = expr->value.function.actual->expr;
6108   ss = gfc_walk_expr (arg_expr);
6109   if (ss == gfc_ss_terminator)
6110     gfc_conv_expr_reference (se, arg_expr);
6111   else
6112     gfc_conv_array_parameter (se, arg_expr, ss, true, NULL, NULL, NULL);
6113   se->expr= convert (gfc_get_int_type (gfc_index_integer_kind), se->expr);
6114    
6115   /* Create a temporary variable for loc return value.  Without this, 
6116      we get an error an ICE in gcc/expr.c(expand_expr_addr_expr_1).  */
6117   temp_var = gfc_create_var (gfc_get_int_type (gfc_index_integer_kind), NULL);
6118   gfc_add_modify (&se->pre, temp_var, se->expr);
6119   se->expr = temp_var;
6120 }
6121
6122 /* Generate code for an intrinsic function.  Some map directly to library
6123    calls, others get special handling.  In some cases the name of the function
6124    used depends on the type specifiers.  */
6125
6126 void
6127 gfc_conv_intrinsic_function (gfc_se * se, gfc_expr * expr)
6128 {
6129   const char *name;
6130   int lib, kind;
6131   tree fndecl;
6132
6133   name = &expr->value.function.name[2];
6134
6135   if (expr->rank > 0)
6136     {
6137       lib = gfc_is_intrinsic_libcall (expr);
6138       if (lib != 0)
6139         {
6140           if (lib == 1)
6141             se->ignore_optional = 1;
6142
6143           switch (expr->value.function.isym->id)
6144             {
6145             case GFC_ISYM_EOSHIFT:
6146             case GFC_ISYM_PACK:
6147             case GFC_ISYM_RESHAPE:
6148               /* For all of those the first argument specifies the type and the
6149                  third is optional.  */
6150               conv_generic_with_optional_char_arg (se, expr, 1, 3);
6151               break;
6152
6153             default:
6154               gfc_conv_intrinsic_funcall (se, expr);
6155               break;
6156             }
6157
6158           return;
6159         }
6160     }
6161
6162   switch (expr->value.function.isym->id)
6163     {
6164     case GFC_ISYM_NONE:
6165       gcc_unreachable ();
6166
6167     case GFC_ISYM_REPEAT:
6168       gfc_conv_intrinsic_repeat (se, expr);
6169       break;
6170
6171     case GFC_ISYM_TRIM:
6172       gfc_conv_intrinsic_trim (se, expr);
6173       break;
6174
6175     case GFC_ISYM_SC_KIND:
6176       gfc_conv_intrinsic_sc_kind (se, expr);
6177       break;
6178
6179     case GFC_ISYM_SI_KIND:
6180       gfc_conv_intrinsic_si_kind (se, expr);
6181       break;
6182
6183     case GFC_ISYM_SR_KIND:
6184       gfc_conv_intrinsic_sr_kind (se, expr);
6185       break;
6186
6187     case GFC_ISYM_EXPONENT:
6188       gfc_conv_intrinsic_exponent (se, expr);
6189       break;
6190
6191     case GFC_ISYM_SCAN:
6192       kind = expr->value.function.actual->expr->ts.kind;
6193       if (kind == 1)
6194        fndecl = gfor_fndecl_string_scan;
6195       else if (kind == 4)
6196        fndecl = gfor_fndecl_string_scan_char4;
6197       else
6198        gcc_unreachable ();
6199
6200       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
6201       break;
6202
6203     case GFC_ISYM_VERIFY:
6204       kind = expr->value.function.actual->expr->ts.kind;
6205       if (kind == 1)
6206        fndecl = gfor_fndecl_string_verify;
6207       else if (kind == 4)
6208        fndecl = gfor_fndecl_string_verify_char4;
6209       else
6210        gcc_unreachable ();
6211
6212       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
6213       break;
6214
6215     case GFC_ISYM_ALLOCATED:
6216       gfc_conv_allocated (se, expr);
6217       break;
6218
6219     case GFC_ISYM_ASSOCIATED:
6220       gfc_conv_associated(se, expr);
6221       break;
6222
6223     case GFC_ISYM_SAME_TYPE_AS:
6224       gfc_conv_same_type_as (se, expr);
6225       break;
6226
6227     case GFC_ISYM_ABS:
6228       gfc_conv_intrinsic_abs (se, expr);
6229       break;
6230
6231     case GFC_ISYM_ADJUSTL:
6232       if (expr->ts.kind == 1)
6233        fndecl = gfor_fndecl_adjustl;
6234       else if (expr->ts.kind == 4)
6235        fndecl = gfor_fndecl_adjustl_char4;
6236       else
6237        gcc_unreachable ();
6238
6239       gfc_conv_intrinsic_adjust (se, expr, fndecl);
6240       break;
6241
6242     case GFC_ISYM_ADJUSTR:
6243       if (expr->ts.kind == 1)
6244        fndecl = gfor_fndecl_adjustr;
6245       else if (expr->ts.kind == 4)
6246        fndecl = gfor_fndecl_adjustr_char4;
6247       else
6248        gcc_unreachable ();
6249
6250       gfc_conv_intrinsic_adjust (se, expr, fndecl);
6251       break;
6252
6253     case GFC_ISYM_AIMAG:
6254       gfc_conv_intrinsic_imagpart (se, expr);
6255       break;
6256
6257     case GFC_ISYM_AINT:
6258       gfc_conv_intrinsic_aint (se, expr, RND_TRUNC);
6259       break;
6260
6261     case GFC_ISYM_ALL:
6262       gfc_conv_intrinsic_anyall (se, expr, EQ_EXPR);
6263       break;
6264
6265     case GFC_ISYM_ANINT:
6266       gfc_conv_intrinsic_aint (se, expr, RND_ROUND);
6267       break;
6268
6269     case GFC_ISYM_AND:
6270       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
6271       break;
6272
6273     case GFC_ISYM_ANY:
6274       gfc_conv_intrinsic_anyall (se, expr, NE_EXPR);
6275       break;
6276
6277     case GFC_ISYM_BTEST:
6278       gfc_conv_intrinsic_btest (se, expr);
6279       break;
6280
6281     case GFC_ISYM_BGE:
6282       gfc_conv_intrinsic_bitcomp (se, expr, GE_EXPR);
6283       break;
6284
6285     case GFC_ISYM_BGT:
6286       gfc_conv_intrinsic_bitcomp (se, expr, GT_EXPR);
6287       break;
6288
6289     case GFC_ISYM_BLE:
6290       gfc_conv_intrinsic_bitcomp (se, expr, LE_EXPR);
6291       break;
6292
6293     case GFC_ISYM_BLT:
6294       gfc_conv_intrinsic_bitcomp (se, expr, LT_EXPR);
6295       break;
6296
6297     case GFC_ISYM_ACHAR:
6298     case GFC_ISYM_CHAR:
6299       gfc_conv_intrinsic_char (se, expr);
6300       break;
6301
6302     case GFC_ISYM_CONVERSION:
6303     case GFC_ISYM_REAL:
6304     case GFC_ISYM_LOGICAL:
6305     case GFC_ISYM_DBLE:
6306       gfc_conv_intrinsic_conversion (se, expr);
6307       break;
6308
6309       /* Integer conversions are handled separately to make sure we get the
6310          correct rounding mode.  */
6311     case GFC_ISYM_INT:
6312     case GFC_ISYM_INT2:
6313     case GFC_ISYM_INT8:
6314     case GFC_ISYM_LONG:
6315       gfc_conv_intrinsic_int (se, expr, RND_TRUNC);
6316       break;
6317
6318     case GFC_ISYM_NINT:
6319       gfc_conv_intrinsic_int (se, expr, RND_ROUND);
6320       break;
6321
6322     case GFC_ISYM_CEILING:
6323       gfc_conv_intrinsic_int (se, expr, RND_CEIL);
6324       break;
6325
6326     case GFC_ISYM_FLOOR:
6327       gfc_conv_intrinsic_int (se, expr, RND_FLOOR);
6328       break;
6329
6330     case GFC_ISYM_MOD:
6331       gfc_conv_intrinsic_mod (se, expr, 0);
6332       break;
6333
6334     case GFC_ISYM_MODULO:
6335       gfc_conv_intrinsic_mod (se, expr, 1);
6336       break;
6337
6338     case GFC_ISYM_CMPLX:
6339       gfc_conv_intrinsic_cmplx (se, expr, name[5] == '1');
6340       break;
6341
6342     case GFC_ISYM_COMMAND_ARGUMENT_COUNT:
6343       gfc_conv_intrinsic_iargc (se, expr);
6344       break;
6345
6346     case GFC_ISYM_COMPLEX:
6347       gfc_conv_intrinsic_cmplx (se, expr, 1);
6348       break;
6349
6350     case GFC_ISYM_CONJG:
6351       gfc_conv_intrinsic_conjg (se, expr);
6352       break;
6353
6354     case GFC_ISYM_COUNT:
6355       gfc_conv_intrinsic_count (se, expr);
6356       break;
6357
6358     case GFC_ISYM_CTIME:
6359       gfc_conv_intrinsic_ctime (se, expr);
6360       break;
6361
6362     case GFC_ISYM_DIM:
6363       gfc_conv_intrinsic_dim (se, expr);
6364       break;
6365
6366     case GFC_ISYM_DOT_PRODUCT:
6367       gfc_conv_intrinsic_dot_product (se, expr);
6368       break;
6369
6370     case GFC_ISYM_DPROD:
6371       gfc_conv_intrinsic_dprod (se, expr);
6372       break;
6373
6374     case GFC_ISYM_DSHIFTL:
6375       gfc_conv_intrinsic_dshift (se, expr, true);
6376       break;
6377
6378     case GFC_ISYM_DSHIFTR:
6379       gfc_conv_intrinsic_dshift (se, expr, false);
6380       break;
6381
6382     case GFC_ISYM_FDATE:
6383       gfc_conv_intrinsic_fdate (se, expr);
6384       break;
6385
6386     case GFC_ISYM_FRACTION:
6387       gfc_conv_intrinsic_fraction (se, expr);
6388       break;
6389
6390     case GFC_ISYM_IALL:
6391       gfc_conv_intrinsic_arith (se, expr, BIT_AND_EXPR, false);
6392       break;
6393
6394     case GFC_ISYM_IAND:
6395       gfc_conv_intrinsic_bitop (se, expr, BIT_AND_EXPR);
6396       break;
6397
6398     case GFC_ISYM_IANY:
6399       gfc_conv_intrinsic_arith (se, expr, BIT_IOR_EXPR, false);
6400       break;
6401
6402     case GFC_ISYM_IBCLR:
6403       gfc_conv_intrinsic_singlebitop (se, expr, 0);
6404       break;
6405
6406     case GFC_ISYM_IBITS:
6407       gfc_conv_intrinsic_ibits (se, expr);
6408       break;
6409
6410     case GFC_ISYM_IBSET:
6411       gfc_conv_intrinsic_singlebitop (se, expr, 1);
6412       break;
6413
6414     case GFC_ISYM_IACHAR:
6415     case GFC_ISYM_ICHAR:
6416       /* We assume ASCII character sequence.  */
6417       gfc_conv_intrinsic_ichar (se, expr);
6418       break;
6419
6420     case GFC_ISYM_IARGC:
6421       gfc_conv_intrinsic_iargc (se, expr);
6422       break;
6423
6424     case GFC_ISYM_IEOR:
6425       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
6426       break;
6427
6428     case GFC_ISYM_INDEX:
6429       kind = expr->value.function.actual->expr->ts.kind;
6430       if (kind == 1)
6431        fndecl = gfor_fndecl_string_index;
6432       else if (kind == 4)
6433        fndecl = gfor_fndecl_string_index_char4;
6434       else
6435        gcc_unreachable ();
6436
6437       gfc_conv_intrinsic_index_scan_verify (se, expr, fndecl);
6438       break;
6439
6440     case GFC_ISYM_IOR:
6441       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
6442       break;
6443
6444     case GFC_ISYM_IPARITY:
6445       gfc_conv_intrinsic_arith (se, expr, BIT_XOR_EXPR, false);
6446       break;
6447
6448     case GFC_ISYM_IS_IOSTAT_END:
6449       gfc_conv_has_intvalue (se, expr, LIBERROR_END);
6450       break;
6451
6452     case GFC_ISYM_IS_IOSTAT_EOR:
6453       gfc_conv_has_intvalue (se, expr, LIBERROR_EOR);
6454       break;
6455
6456     case GFC_ISYM_ISNAN:
6457       gfc_conv_intrinsic_isnan (se, expr);
6458       break;
6459
6460     case GFC_ISYM_LSHIFT:
6461       gfc_conv_intrinsic_shift (se, expr, false, false);
6462       break;
6463
6464     case GFC_ISYM_RSHIFT:
6465       gfc_conv_intrinsic_shift (se, expr, true, true);
6466       break;
6467
6468     case GFC_ISYM_SHIFTA:
6469       gfc_conv_intrinsic_shift (se, expr, true, true);
6470       break;
6471
6472     case GFC_ISYM_SHIFTL:
6473       gfc_conv_intrinsic_shift (se, expr, false, false);
6474       break;
6475
6476     case GFC_ISYM_SHIFTR:
6477       gfc_conv_intrinsic_shift (se, expr, true, false);
6478       break;
6479
6480     case GFC_ISYM_ISHFT:
6481       gfc_conv_intrinsic_ishft (se, expr);
6482       break;
6483
6484     case GFC_ISYM_ISHFTC:
6485       gfc_conv_intrinsic_ishftc (se, expr);
6486       break;
6487
6488     case GFC_ISYM_LEADZ:
6489       gfc_conv_intrinsic_leadz (se, expr);
6490       break;
6491
6492     case GFC_ISYM_TRAILZ:
6493       gfc_conv_intrinsic_trailz (se, expr);
6494       break;
6495
6496     case GFC_ISYM_POPCNT:
6497       gfc_conv_intrinsic_popcnt_poppar (se, expr, 0);
6498       break;
6499
6500     case GFC_ISYM_POPPAR:
6501       gfc_conv_intrinsic_popcnt_poppar (se, expr, 1);
6502       break;
6503
6504     case GFC_ISYM_LBOUND:
6505       gfc_conv_intrinsic_bound (se, expr, 0);
6506       break;
6507
6508     case GFC_ISYM_LCOBOUND:
6509       conv_intrinsic_cobound (se, expr);
6510       break;
6511
6512     case GFC_ISYM_TRANSPOSE:
6513       /* The scalarizer has already been set up for reversed dimension access
6514          order ; now we just get the argument value normally.  */
6515       gfc_conv_expr (se, expr->value.function.actual->expr);
6516       break;
6517
6518     case GFC_ISYM_LEN:
6519       gfc_conv_intrinsic_len (se, expr);
6520       break;
6521
6522     case GFC_ISYM_LEN_TRIM:
6523       gfc_conv_intrinsic_len_trim (se, expr);
6524       break;
6525
6526     case GFC_ISYM_LGE:
6527       gfc_conv_intrinsic_strcmp (se, expr, GE_EXPR);
6528       break;
6529
6530     case GFC_ISYM_LGT:
6531       gfc_conv_intrinsic_strcmp (se, expr, GT_EXPR);
6532       break;
6533
6534     case GFC_ISYM_LLE:
6535       gfc_conv_intrinsic_strcmp (se, expr, LE_EXPR);
6536       break;
6537
6538     case GFC_ISYM_LLT:
6539       gfc_conv_intrinsic_strcmp (se, expr, LT_EXPR);
6540       break;
6541
6542     case GFC_ISYM_MASKL:
6543       gfc_conv_intrinsic_mask (se, expr, 1);
6544       break;
6545
6546     case GFC_ISYM_MASKR:
6547       gfc_conv_intrinsic_mask (se, expr, 0);
6548       break;
6549
6550     case GFC_ISYM_MAX:
6551       if (expr->ts.type == BT_CHARACTER)
6552         gfc_conv_intrinsic_minmax_char (se, expr, 1);
6553       else
6554         gfc_conv_intrinsic_minmax (se, expr, GT_EXPR);
6555       break;
6556
6557     case GFC_ISYM_MAXLOC:
6558       gfc_conv_intrinsic_minmaxloc (se, expr, GT_EXPR);
6559       break;
6560
6561     case GFC_ISYM_MAXVAL:
6562       gfc_conv_intrinsic_minmaxval (se, expr, GT_EXPR);
6563       break;
6564
6565     case GFC_ISYM_MERGE:
6566       gfc_conv_intrinsic_merge (se, expr);
6567       break;
6568
6569     case GFC_ISYM_MERGE_BITS:
6570       gfc_conv_intrinsic_merge_bits (se, expr);
6571       break;
6572
6573     case GFC_ISYM_MIN:
6574       if (expr->ts.type == BT_CHARACTER)
6575         gfc_conv_intrinsic_minmax_char (se, expr, -1);
6576       else
6577         gfc_conv_intrinsic_minmax (se, expr, LT_EXPR);
6578       break;
6579
6580     case GFC_ISYM_MINLOC:
6581       gfc_conv_intrinsic_minmaxloc (se, expr, LT_EXPR);
6582       break;
6583
6584     case GFC_ISYM_MINVAL:
6585       gfc_conv_intrinsic_minmaxval (se, expr, LT_EXPR);
6586       break;
6587
6588     case GFC_ISYM_NEAREST:
6589       gfc_conv_intrinsic_nearest (se, expr);
6590       break;
6591
6592     case GFC_ISYM_NORM2:
6593       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, true);
6594       break;
6595
6596     case GFC_ISYM_NOT:
6597       gfc_conv_intrinsic_not (se, expr);
6598       break;
6599
6600     case GFC_ISYM_OR:
6601       gfc_conv_intrinsic_bitop (se, expr, BIT_IOR_EXPR);
6602       break;
6603
6604     case GFC_ISYM_PARITY:
6605       gfc_conv_intrinsic_arith (se, expr, NE_EXPR, false);
6606       break;
6607
6608     case GFC_ISYM_PRESENT:
6609       gfc_conv_intrinsic_present (se, expr);
6610       break;
6611
6612     case GFC_ISYM_PRODUCT:
6613       gfc_conv_intrinsic_arith (se, expr, MULT_EXPR, false);
6614       break;
6615
6616     case GFC_ISYM_RRSPACING:
6617       gfc_conv_intrinsic_rrspacing (se, expr);
6618       break;
6619
6620     case GFC_ISYM_SET_EXPONENT:
6621       gfc_conv_intrinsic_set_exponent (se, expr);
6622       break;
6623
6624     case GFC_ISYM_SCALE:
6625       gfc_conv_intrinsic_scale (se, expr);
6626       break;
6627
6628     case GFC_ISYM_SIGN:
6629       gfc_conv_intrinsic_sign (se, expr);
6630       break;
6631
6632     case GFC_ISYM_SIZE:
6633       gfc_conv_intrinsic_size (se, expr);
6634       break;
6635
6636     case GFC_ISYM_SIZEOF:
6637     case GFC_ISYM_C_SIZEOF:
6638       gfc_conv_intrinsic_sizeof (se, expr);
6639       break;
6640
6641     case GFC_ISYM_STORAGE_SIZE:
6642       gfc_conv_intrinsic_storage_size (se, expr);
6643       break;
6644
6645     case GFC_ISYM_SPACING:
6646       gfc_conv_intrinsic_spacing (se, expr);
6647       break;
6648
6649     case GFC_ISYM_SUM:
6650       gfc_conv_intrinsic_arith (se, expr, PLUS_EXPR, false);
6651       break;
6652
6653     case GFC_ISYM_TRANSFER:
6654       if (se->ss && se->ss->info->useflags)
6655         /* Access the previously obtained result.  */
6656         gfc_conv_tmp_array_ref (se);
6657       else
6658         gfc_conv_intrinsic_transfer (se, expr);
6659       break;
6660
6661     case GFC_ISYM_TTYNAM:
6662       gfc_conv_intrinsic_ttynam (se, expr);
6663       break;
6664
6665     case GFC_ISYM_UBOUND:
6666       gfc_conv_intrinsic_bound (se, expr, 1);
6667       break;
6668
6669     case GFC_ISYM_UCOBOUND:
6670       conv_intrinsic_cobound (se, expr);
6671       break;
6672
6673     case GFC_ISYM_XOR:
6674       gfc_conv_intrinsic_bitop (se, expr, BIT_XOR_EXPR);
6675       break;
6676
6677     case GFC_ISYM_LOC:
6678       gfc_conv_intrinsic_loc (se, expr);
6679       break;
6680
6681     case GFC_ISYM_THIS_IMAGE:
6682       /* For num_images() == 1, handle as LCOBOUND.  */
6683       if (expr->value.function.actual->expr
6684           && gfc_option.coarray == GFC_FCOARRAY_SINGLE)
6685         conv_intrinsic_cobound (se, expr);
6686       else
6687         trans_this_image (se, expr);
6688       break;
6689
6690     case GFC_ISYM_IMAGE_INDEX:
6691       trans_image_index (se, expr);
6692       break;
6693
6694     case GFC_ISYM_NUM_IMAGES:
6695       trans_num_images (se);
6696       break;
6697
6698     case GFC_ISYM_ACCESS:
6699     case GFC_ISYM_CHDIR:
6700     case GFC_ISYM_CHMOD:
6701     case GFC_ISYM_DTIME:
6702     case GFC_ISYM_ETIME:
6703     case GFC_ISYM_EXTENDS_TYPE_OF:
6704     case GFC_ISYM_FGET:
6705     case GFC_ISYM_FGETC:
6706     case GFC_ISYM_FNUM:
6707     case GFC_ISYM_FPUT:
6708     case GFC_ISYM_FPUTC:
6709     case GFC_ISYM_FSTAT:
6710     case GFC_ISYM_FTELL:
6711     case GFC_ISYM_GETCWD:
6712     case GFC_ISYM_GETGID:
6713     case GFC_ISYM_GETPID:
6714     case GFC_ISYM_GETUID:
6715     case GFC_ISYM_HOSTNM:
6716     case GFC_ISYM_KILL:
6717     case GFC_ISYM_IERRNO:
6718     case GFC_ISYM_IRAND:
6719     case GFC_ISYM_ISATTY:
6720     case GFC_ISYM_JN2:
6721     case GFC_ISYM_LINK:
6722     case GFC_ISYM_LSTAT:
6723     case GFC_ISYM_MALLOC:
6724     case GFC_ISYM_MATMUL:
6725     case GFC_ISYM_MCLOCK:
6726     case GFC_ISYM_MCLOCK8:
6727     case GFC_ISYM_RAND:
6728     case GFC_ISYM_RENAME:
6729     case GFC_ISYM_SECOND:
6730     case GFC_ISYM_SECNDS:
6731     case GFC_ISYM_SIGNAL:
6732     case GFC_ISYM_STAT:
6733     case GFC_ISYM_SYMLNK:
6734     case GFC_ISYM_SYSTEM:
6735     case GFC_ISYM_TIME:
6736     case GFC_ISYM_TIME8:
6737     case GFC_ISYM_UMASK:
6738     case GFC_ISYM_UNLINK:
6739     case GFC_ISYM_YN2:
6740       gfc_conv_intrinsic_funcall (se, expr);
6741       break;
6742
6743     case GFC_ISYM_EOSHIFT:
6744     case GFC_ISYM_PACK:
6745     case GFC_ISYM_RESHAPE:
6746       /* For those, expr->rank should always be >0 and thus the if above the
6747          switch should have matched.  */
6748       gcc_unreachable ();
6749       break;
6750
6751     default:
6752       gfc_conv_intrinsic_lib_function (se, expr);
6753       break;
6754     }
6755 }
6756
6757
6758 static gfc_ss *
6759 walk_inline_intrinsic_transpose (gfc_ss *ss, gfc_expr *expr)
6760 {
6761   gfc_ss *arg_ss, *tmp_ss;
6762   gfc_actual_arglist *arg;
6763
6764   arg = expr->value.function.actual;
6765
6766   gcc_assert (arg->expr);
6767
6768   arg_ss = gfc_walk_subexpr (gfc_ss_terminator, arg->expr);
6769   gcc_assert (arg_ss != gfc_ss_terminator);
6770
6771   for (tmp_ss = arg_ss; ; tmp_ss = tmp_ss->next)
6772     {
6773       if (tmp_ss->info->type != GFC_SS_SCALAR
6774           && tmp_ss->info->type != GFC_SS_REFERENCE)
6775         {
6776           int tmp_dim;
6777
6778           gcc_assert (tmp_ss->dimen == 2);
6779
6780           /* We just invert dimensions.  */
6781           tmp_dim = tmp_ss->dim[0];
6782           tmp_ss->dim[0] = tmp_ss->dim[1];
6783           tmp_ss->dim[1] = tmp_dim;
6784         }
6785
6786       /* Stop when tmp_ss points to the last valid element of the chain...  */
6787       if (tmp_ss->next == gfc_ss_terminator)
6788         break;
6789     }
6790
6791   /* ... so that we can attach the rest of the chain to it.  */
6792   tmp_ss->next = ss;
6793
6794   return arg_ss;
6795 }
6796
6797
6798 static gfc_ss *
6799 walk_inline_intrinsic_function (gfc_ss * ss, gfc_expr * expr)
6800 {
6801
6802   switch (expr->value.function.isym->id)
6803     {
6804       case GFC_ISYM_TRANSPOSE:
6805         return walk_inline_intrinsic_transpose (ss, expr);
6806
6807       default:
6808         gcc_unreachable ();
6809     }
6810   gcc_unreachable ();
6811 }
6812
6813
6814 /* This generates code to execute before entering the scalarization loop.
6815    Currently does nothing.  */
6816
6817 void
6818 gfc_add_intrinsic_ss_code (gfc_loopinfo * loop ATTRIBUTE_UNUSED, gfc_ss * ss)
6819 {
6820   switch (ss->info->expr->value.function.isym->id)
6821     {
6822     case GFC_ISYM_UBOUND:
6823     case GFC_ISYM_LBOUND:
6824     case GFC_ISYM_UCOBOUND:
6825     case GFC_ISYM_LCOBOUND:
6826     case GFC_ISYM_THIS_IMAGE:
6827       break;
6828
6829     default:
6830       gcc_unreachable ();
6831     }
6832 }
6833
6834
6835 /* The LBOUND, LCOBOUND, UBOUND and UCOBOUND intrinsics with one parameter
6836    are expanded into code inside the scalarization loop.  */
6837
6838 static gfc_ss *
6839 gfc_walk_intrinsic_bound (gfc_ss * ss, gfc_expr * expr)
6840 {
6841   /* The two argument version returns a scalar.  */
6842   if (expr->value.function.actual->next->expr)
6843     return ss;
6844
6845   return gfc_get_array_ss (ss, expr, 1, GFC_SS_INTRINSIC);
6846 }
6847
6848
6849 /* Walk an intrinsic array libcall.  */
6850
6851 static gfc_ss *
6852 gfc_walk_intrinsic_libfunc (gfc_ss * ss, gfc_expr * expr)
6853 {
6854   gcc_assert (expr->rank > 0);
6855   return gfc_get_array_ss (ss, expr, expr->rank, GFC_SS_FUNCTION);
6856 }
6857
6858
6859 /* Return whether the function call expression EXPR will be expanded
6860    inline by gfc_conv_intrinsic_function.  */
6861
6862 bool
6863 gfc_inline_intrinsic_function_p (gfc_expr *expr)
6864 {
6865   if (!expr->value.function.isym)
6866     return false;
6867
6868   switch (expr->value.function.isym->id)
6869     {
6870     case GFC_ISYM_TRANSPOSE:
6871       return true;
6872
6873     default:
6874       return false;
6875     }
6876 }
6877
6878
6879 /* Returns nonzero if the specified intrinsic function call maps directly to
6880    an external library call.  Should only be used for functions that return
6881    arrays.  */
6882
6883 int
6884 gfc_is_intrinsic_libcall (gfc_expr * expr)
6885 {
6886   gcc_assert (expr->expr_type == EXPR_FUNCTION && expr->value.function.isym);
6887   gcc_assert (expr->rank > 0);
6888
6889   if (gfc_inline_intrinsic_function_p (expr))
6890     return 0;
6891
6892   switch (expr->value.function.isym->id)
6893     {
6894     case GFC_ISYM_ALL:
6895     case GFC_ISYM_ANY:
6896     case GFC_ISYM_COUNT:
6897     case GFC_ISYM_JN2:
6898     case GFC_ISYM_IANY:
6899     case GFC_ISYM_IALL:
6900     case GFC_ISYM_IPARITY:
6901     case GFC_ISYM_MATMUL:
6902     case GFC_ISYM_MAXLOC:
6903     case GFC_ISYM_MAXVAL:
6904     case GFC_ISYM_MINLOC:
6905     case GFC_ISYM_MINVAL:
6906     case GFC_ISYM_NORM2:
6907     case GFC_ISYM_PARITY:
6908     case GFC_ISYM_PRODUCT:
6909     case GFC_ISYM_SUM:
6910     case GFC_ISYM_SHAPE:
6911     case GFC_ISYM_SPREAD:
6912     case GFC_ISYM_YN2:
6913       /* Ignore absent optional parameters.  */
6914       return 1;
6915
6916     case GFC_ISYM_RESHAPE:
6917     case GFC_ISYM_CSHIFT:
6918     case GFC_ISYM_EOSHIFT:
6919     case GFC_ISYM_PACK:
6920     case GFC_ISYM_UNPACK:
6921       /* Pass absent optional parameters.  */
6922       return 2;
6923
6924     default:
6925       return 0;
6926     }
6927 }
6928
6929 /* Walk an intrinsic function.  */
6930 gfc_ss *
6931 gfc_walk_intrinsic_function (gfc_ss * ss, gfc_expr * expr,
6932                              gfc_intrinsic_sym * isym)
6933 {
6934   gcc_assert (isym);
6935
6936   if (isym->elemental)
6937     return gfc_walk_elemental_function_args (ss, expr->value.function.actual,
6938                                              GFC_SS_SCALAR);
6939
6940   if (expr->rank == 0)
6941     return ss;
6942
6943   if (gfc_inline_intrinsic_function_p (expr))
6944     return walk_inline_intrinsic_function (ss, expr);
6945
6946   if (gfc_is_intrinsic_libcall (expr))
6947     return gfc_walk_intrinsic_libfunc (ss, expr);
6948
6949   /* Special cases.  */
6950   switch (isym->id)
6951     {
6952     case GFC_ISYM_LBOUND:
6953     case GFC_ISYM_LCOBOUND:
6954     case GFC_ISYM_UBOUND:
6955     case GFC_ISYM_UCOBOUND:
6956     case GFC_ISYM_THIS_IMAGE:
6957       return gfc_walk_intrinsic_bound (ss, expr);
6958
6959     case GFC_ISYM_TRANSFER:
6960       return gfc_walk_intrinsic_libfunc (ss, expr);
6961
6962     default:
6963       /* This probably meant someone forgot to add an intrinsic to the above
6964          list(s) when they implemented it, or something's gone horribly
6965          wrong.  */
6966       gcc_unreachable ();
6967     }
6968 }
6969
6970
6971 static tree
6972 conv_intrinsic_atomic_def (gfc_code *code)
6973 {
6974   gfc_se atom, value;
6975   stmtblock_t block;
6976
6977   gfc_init_se (&atom, NULL);
6978   gfc_init_se (&value, NULL);
6979   gfc_conv_expr (&atom, code->ext.actual->expr);
6980   gfc_conv_expr (&value, code->ext.actual->next->expr);
6981
6982   gfc_init_block (&block);
6983   gfc_add_modify (&block, atom.expr,
6984                   fold_convert (TREE_TYPE (atom.expr), value.expr));
6985   return gfc_finish_block (&block);
6986 }
6987
6988
6989 static tree
6990 conv_intrinsic_atomic_ref (gfc_code *code)
6991 {
6992   gfc_se atom, value;
6993   stmtblock_t block;
6994
6995   gfc_init_se (&atom, NULL);
6996   gfc_init_se (&value, NULL);
6997   gfc_conv_expr (&value, code->ext.actual->expr);
6998   gfc_conv_expr (&atom, code->ext.actual->next->expr);
6999
7000   gfc_init_block (&block);
7001   gfc_add_modify (&block, value.expr,
7002                   fold_convert (TREE_TYPE (value.expr), atom.expr));
7003   return gfc_finish_block (&block);
7004 }
7005
7006
7007 static tree
7008 conv_intrinsic_move_alloc (gfc_code *code)
7009 {
7010   if (code->ext.actual->expr->rank == 0)
7011     {
7012       /* Scalar arguments: Generate pointer assignments.  */
7013       gfc_expr *from, *to, *deal;
7014       stmtblock_t block;
7015       tree tmp;
7016       gfc_se se;
7017
7018       from = code->ext.actual->expr;
7019       to = code->ext.actual->next->expr;
7020
7021       gfc_start_block (&block);
7022
7023       /* Deallocate 'TO' argument.  */
7024       gfc_init_se (&se, NULL);
7025       se.want_pointer = 1;
7026       deal = gfc_copy_expr (to);
7027       if (deal->ts.type == BT_CLASS)
7028         gfc_add_data_component (deal);
7029       gfc_conv_expr (&se, deal);
7030       tmp = gfc_deallocate_scalar_with_status (se.expr, NULL, true,
7031                                                deal, deal->ts);
7032       gfc_add_expr_to_block (&block, tmp);
7033       gfc_free_expr (deal);
7034
7035       if (to->ts.type == BT_CLASS)
7036         tmp = gfc_trans_class_assign (to, from, EXEC_POINTER_ASSIGN);
7037       else
7038         tmp = gfc_trans_pointer_assignment (to, from);
7039       gfc_add_expr_to_block (&block, tmp);
7040
7041       if (from->ts.type == BT_CLASS)
7042         tmp = gfc_trans_class_assign (from, gfc_get_null_expr (NULL),
7043                                       EXEC_POINTER_ASSIGN);
7044       else
7045         tmp = gfc_trans_pointer_assignment (from,
7046                                             gfc_get_null_expr (NULL));
7047       gfc_add_expr_to_block (&block, tmp);
7048
7049       return gfc_finish_block (&block);
7050     }
7051   else
7052     /* Array arguments: Generate library code.  */
7053     return gfc_trans_call (code, false, NULL_TREE, NULL_TREE, false);
7054 }
7055
7056
7057 tree
7058 gfc_conv_intrinsic_subroutine (gfc_code *code)
7059 {
7060   tree res;
7061
7062   gcc_assert (code->resolved_isym);
7063
7064   switch (code->resolved_isym->id)
7065     {
7066     case GFC_ISYM_MOVE_ALLOC:
7067       res = conv_intrinsic_move_alloc (code);
7068       break;
7069
7070     case GFC_ISYM_ATOMIC_DEF:
7071       res = conv_intrinsic_atomic_def (code);
7072       break;
7073
7074     case GFC_ISYM_ATOMIC_REF:
7075       res = conv_intrinsic_atomic_ref (code);
7076       break;
7077
7078     default:
7079       res = NULL_TREE;
7080       break;
7081     }
7082
7083   return res;
7084 }
7085
7086 #include "gt-fortran-trans-intrinsic.h"