OSDN Git Service

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