xref: /openbsd-src/gnu/usr.bin/gcc/gcc/convert.c (revision 4e43c760ad4cd5f644ec700462679d05749498d8)
1c87b03e5Sespie /* Utility routines for data type conversion for GNU C.
2c87b03e5Sespie    Copyright (C) 1987, 1988, 1991, 1992, 1993, 1994, 1995, 1997,
3c87b03e5Sespie    1998 Free Software Foundation, Inc.
4c87b03e5Sespie 
5c87b03e5Sespie This file is part of GCC.
6c87b03e5Sespie 
7c87b03e5Sespie GCC is free software; you can redistribute it and/or modify it under
8c87b03e5Sespie the terms of the GNU General Public License as published by the Free
9c87b03e5Sespie Software Foundation; either version 2, or (at your option) any later
10c87b03e5Sespie version.
11c87b03e5Sespie 
12c87b03e5Sespie GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13c87b03e5Sespie WARRANTY; without even the implied warranty of MERCHANTABILITY or
14c87b03e5Sespie FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15c87b03e5Sespie for more details.
16c87b03e5Sespie 
17c87b03e5Sespie You should have received a copy of the GNU General Public License
18c87b03e5Sespie along with GCC; see the file COPYING.  If not, write to the Free
19c87b03e5Sespie Software Foundation, 59 Temple Place - Suite 330, Boston, MA
20c87b03e5Sespie 02111-1307, USA.  */
21c87b03e5Sespie 
22c87b03e5Sespie 
23c87b03e5Sespie /* These routines are somewhat language-independent utility function
24c87b03e5Sespie    intended to be called by the language-specific convert () functions.  */
25c87b03e5Sespie 
26c87b03e5Sespie #include "config.h"
27c87b03e5Sespie #include "system.h"
28c87b03e5Sespie #include "tree.h"
29c87b03e5Sespie #include "flags.h"
30c87b03e5Sespie #include "convert.h"
31c87b03e5Sespie #include "toplev.h"
32c87b03e5Sespie #include "langhooks.h"
33c87b03e5Sespie 
34c87b03e5Sespie /* Convert EXPR to some pointer or reference type TYPE.
35c87b03e5Sespie 
36c87b03e5Sespie    EXPR must be pointer, reference, integer, enumeral, or literal zero;
37c87b03e5Sespie    in other cases error is called.  */
38c87b03e5Sespie 
39c87b03e5Sespie tree
convert_to_pointer(type,expr)40c87b03e5Sespie convert_to_pointer (type, expr)
41c87b03e5Sespie      tree type, expr;
42c87b03e5Sespie {
43c87b03e5Sespie   if (integer_zerop (expr))
44c87b03e5Sespie     {
45c87b03e5Sespie       expr = build_int_2 (0, 0);
46c87b03e5Sespie       TREE_TYPE (expr) = type;
47c87b03e5Sespie       return expr;
48c87b03e5Sespie     }
49c87b03e5Sespie 
50c87b03e5Sespie   switch (TREE_CODE (TREE_TYPE (expr)))
51c87b03e5Sespie     {
52c87b03e5Sespie     case POINTER_TYPE:
53c87b03e5Sespie     case REFERENCE_TYPE:
54c87b03e5Sespie       return build1 (NOP_EXPR, type, expr);
55c87b03e5Sespie 
56c87b03e5Sespie     case INTEGER_TYPE:
57c87b03e5Sespie     case ENUMERAL_TYPE:
58c87b03e5Sespie     case BOOLEAN_TYPE:
59c87b03e5Sespie     case CHAR_TYPE:
60c87b03e5Sespie       if (TYPE_PRECISION (TREE_TYPE (expr)) == POINTER_SIZE)
61c87b03e5Sespie 	return build1 (CONVERT_EXPR, type, expr);
62c87b03e5Sespie 
63c87b03e5Sespie       return
64c87b03e5Sespie 	convert_to_pointer (type,
65c87b03e5Sespie 			    convert ((*lang_hooks.types.type_for_size)
66c87b03e5Sespie 				     (POINTER_SIZE, 0), expr));
67c87b03e5Sespie 
68c87b03e5Sespie     default:
69c87b03e5Sespie       error ("cannot convert to a pointer type");
70c87b03e5Sespie       return convert_to_pointer (type, integer_zero_node);
71c87b03e5Sespie     }
72c87b03e5Sespie }
73c87b03e5Sespie 
74c87b03e5Sespie /* Convert EXPR to some floating-point type TYPE.
75c87b03e5Sespie 
76c87b03e5Sespie    EXPR must be float, integer, or enumeral;
77c87b03e5Sespie    in other cases error is called.  */
78c87b03e5Sespie 
79c87b03e5Sespie tree
convert_to_real(type,expr)80c87b03e5Sespie convert_to_real (type, expr)
81c87b03e5Sespie      tree type, expr;
82c87b03e5Sespie {
83c87b03e5Sespie   switch (TREE_CODE (TREE_TYPE (expr)))
84c87b03e5Sespie     {
85c87b03e5Sespie     case REAL_TYPE:
86c87b03e5Sespie       return build1 (flag_float_store ? CONVERT_EXPR : NOP_EXPR,
87c87b03e5Sespie 		     type, expr);
88c87b03e5Sespie 
89c87b03e5Sespie     case INTEGER_TYPE:
90c87b03e5Sespie     case ENUMERAL_TYPE:
91c87b03e5Sespie     case BOOLEAN_TYPE:
92c87b03e5Sespie     case CHAR_TYPE:
93c87b03e5Sespie       return build1 (FLOAT_EXPR, type, expr);
94c87b03e5Sespie 
95c87b03e5Sespie     case COMPLEX_TYPE:
96c87b03e5Sespie       return convert (type,
97c87b03e5Sespie 		      fold (build1 (REALPART_EXPR,
98c87b03e5Sespie 				    TREE_TYPE (TREE_TYPE (expr)), expr)));
99c87b03e5Sespie 
100c87b03e5Sespie     case POINTER_TYPE:
101c87b03e5Sespie     case REFERENCE_TYPE:
102c87b03e5Sespie       error ("pointer value used where a floating point value was expected");
103c87b03e5Sespie       return convert_to_real (type, integer_zero_node);
104c87b03e5Sespie 
105c87b03e5Sespie     default:
106c87b03e5Sespie       error ("aggregate value used where a float was expected");
107c87b03e5Sespie       return convert_to_real (type, integer_zero_node);
108c87b03e5Sespie     }
109c87b03e5Sespie }
110c87b03e5Sespie 
111c87b03e5Sespie /* Convert EXPR to some integer (or enum) type TYPE.
112c87b03e5Sespie 
113c87b03e5Sespie    EXPR must be pointer, integer, discrete (enum, char, or bool), float, or
114c87b03e5Sespie    vector; in other cases error is called.
115c87b03e5Sespie 
116c87b03e5Sespie    The result of this is always supposed to be a newly created tree node
117c87b03e5Sespie    not in use in any existing structure.  */
118c87b03e5Sespie 
119c87b03e5Sespie tree
convert_to_integer(type,expr)120c87b03e5Sespie convert_to_integer (type, expr)
121c87b03e5Sespie      tree type, expr;
122c87b03e5Sespie {
123c87b03e5Sespie   enum tree_code ex_form = TREE_CODE (expr);
124c87b03e5Sespie   tree intype = TREE_TYPE (expr);
125c87b03e5Sespie   unsigned int inprec = TYPE_PRECISION (intype);
126c87b03e5Sespie   unsigned int outprec = TYPE_PRECISION (type);
127c87b03e5Sespie 
128c87b03e5Sespie   /* An INTEGER_TYPE cannot be incomplete, but an ENUMERAL_TYPE can
129c87b03e5Sespie      be.  Consider `enum E = { a, b = (enum E) 3 };'.  */
130c87b03e5Sespie   if (!COMPLETE_TYPE_P (type))
131c87b03e5Sespie     {
132c87b03e5Sespie       error ("conversion to incomplete type");
133c87b03e5Sespie       return error_mark_node;
134c87b03e5Sespie     }
135c87b03e5Sespie 
136c87b03e5Sespie   switch (TREE_CODE (intype))
137c87b03e5Sespie     {
138c87b03e5Sespie     case POINTER_TYPE:
139c87b03e5Sespie     case REFERENCE_TYPE:
140c87b03e5Sespie       if (integer_zerop (expr))
141c87b03e5Sespie 	expr = integer_zero_node;
142c87b03e5Sespie       else
143c87b03e5Sespie 	expr = fold (build1 (CONVERT_EXPR, (*lang_hooks.types.type_for_size)
144c87b03e5Sespie 			     (POINTER_SIZE, 0), expr));
145c87b03e5Sespie 
146c87b03e5Sespie       return convert_to_integer (type, expr);
147c87b03e5Sespie 
148c87b03e5Sespie     case INTEGER_TYPE:
149c87b03e5Sespie     case ENUMERAL_TYPE:
150c87b03e5Sespie     case BOOLEAN_TYPE:
151c87b03e5Sespie     case CHAR_TYPE:
152c87b03e5Sespie       /* If this is a logical operation, which just returns 0 or 1, we can
153c87b03e5Sespie 	 change the type of the expression.  For some logical operations,
154c87b03e5Sespie 	 we must also change the types of the operands to maintain type
155c87b03e5Sespie 	 correctness.  */
156c87b03e5Sespie 
157c87b03e5Sespie       if (TREE_CODE_CLASS (ex_form) == '<')
158c87b03e5Sespie 	{
159c87b03e5Sespie 	  TREE_TYPE (expr) = type;
160c87b03e5Sespie 	  return expr;
161c87b03e5Sespie 	}
162c87b03e5Sespie 
163c87b03e5Sespie       else if (ex_form == TRUTH_AND_EXPR || ex_form == TRUTH_ANDIF_EXPR
164c87b03e5Sespie 	       || ex_form == TRUTH_OR_EXPR || ex_form == TRUTH_ORIF_EXPR
165c87b03e5Sespie 	       || ex_form == TRUTH_XOR_EXPR)
166c87b03e5Sespie 	{
167c87b03e5Sespie 	  TREE_OPERAND (expr, 0) = convert (type, TREE_OPERAND (expr, 0));
168c87b03e5Sespie 	  TREE_OPERAND (expr, 1) = convert (type, TREE_OPERAND (expr, 1));
169c87b03e5Sespie 	  TREE_TYPE (expr) = type;
170c87b03e5Sespie 	  return expr;
171c87b03e5Sespie 	}
172c87b03e5Sespie 
173c87b03e5Sespie       else if (ex_form == TRUTH_NOT_EXPR)
174c87b03e5Sespie 	{
175c87b03e5Sespie 	  TREE_OPERAND (expr, 0) = convert (type, TREE_OPERAND (expr, 0));
176c87b03e5Sespie 	  TREE_TYPE (expr) = type;
177c87b03e5Sespie 	  return expr;
178c87b03e5Sespie 	}
179c87b03e5Sespie 
180c87b03e5Sespie       /* If we are widening the type, put in an explicit conversion.
181c87b03e5Sespie 	 Similarly if we are not changing the width.  After this, we know
182c87b03e5Sespie 	 we are truncating EXPR.  */
183c87b03e5Sespie 
184c87b03e5Sespie       else if (outprec >= inprec)
185*4e43c760Sespie 	{
186*4e43c760Sespie 	  enum tree_code code;
187*4e43c760Sespie 
188*4e43c760Sespie 	  /* If the precision of the EXPR's type is K bits and the
189*4e43c760Sespie 	     destination mode has more bits, and the sign is changing,
190*4e43c760Sespie 	     it is not safe to use a NOP_EXPR.  For example, suppose
191*4e43c760Sespie 	     that EXPR's type is a 3-bit unsigned integer type, the
192*4e43c760Sespie 	     TYPE is a 3-bit signed integer type, and the machine mode
193*4e43c760Sespie 	     for the types is 8-bit QImode.  In that case, the
194*4e43c760Sespie 	     conversion necessitates an explicit sign-extension.  In
195*4e43c760Sespie 	     the signed-to-unsigned case the high-order bits have to
196*4e43c760Sespie 	     be cleared.  */
197*4e43c760Sespie 	  if (TREE_UNSIGNED (type) != TREE_UNSIGNED (TREE_TYPE (expr))
198*4e43c760Sespie 	      && (TYPE_PRECISION (TREE_TYPE (expr))
199*4e43c760Sespie 		  != GET_MODE_BITSIZE (TYPE_MODE (TREE_TYPE (expr)))))
200*4e43c760Sespie 	    code = CONVERT_EXPR;
201*4e43c760Sespie 	  else
202*4e43c760Sespie 	    code = NOP_EXPR;
203*4e43c760Sespie 
204*4e43c760Sespie 	  return build1 (code, type, expr);
205*4e43c760Sespie 	}
206c87b03e5Sespie 
207c87b03e5Sespie       /* If TYPE is an enumeral type or a type with a precision less
208c87b03e5Sespie 	 than the number of bits in its mode, do the conversion to the
209c87b03e5Sespie 	 type corresponding to its mode, then do a nop conversion
210c87b03e5Sespie 	 to TYPE.  */
211c87b03e5Sespie       else if (TREE_CODE (type) == ENUMERAL_TYPE
212c87b03e5Sespie 	       || outprec != GET_MODE_BITSIZE (TYPE_MODE (type)))
213c87b03e5Sespie 	return build1 (NOP_EXPR, type,
214c87b03e5Sespie 		       convert ((*lang_hooks.types.type_for_mode)
215c87b03e5Sespie 				(TYPE_MODE (type), TREE_UNSIGNED (type)),
216c87b03e5Sespie 				expr));
217c87b03e5Sespie 
218c87b03e5Sespie       /* Here detect when we can distribute the truncation down past some
219c87b03e5Sespie 	 arithmetic.  For example, if adding two longs and converting to an
220c87b03e5Sespie 	 int, we can equally well convert both to ints and then add.
221c87b03e5Sespie 	 For the operations handled here, such truncation distribution
222c87b03e5Sespie 	 is always safe.
223c87b03e5Sespie 	 It is desirable in these cases:
224c87b03e5Sespie 	 1) when truncating down to full-word from a larger size
225c87b03e5Sespie 	 2) when truncating takes no work.
226c87b03e5Sespie 	 3) when at least one operand of the arithmetic has been extended
227c87b03e5Sespie 	 (as by C's default conversions).  In this case we need two conversions
228c87b03e5Sespie 	 if we do the arithmetic as already requested, so we might as well
229c87b03e5Sespie 	 truncate both and then combine.  Perhaps that way we need only one.
230c87b03e5Sespie 
231c87b03e5Sespie 	 Note that in general we cannot do the arithmetic in a type
232c87b03e5Sespie 	 shorter than the desired result of conversion, even if the operands
233c87b03e5Sespie 	 are both extended from a shorter type, because they might overflow
234c87b03e5Sespie 	 if combined in that type.  The exceptions to this--the times when
235c87b03e5Sespie 	 two narrow values can be combined in their narrow type even to
236c87b03e5Sespie 	 make a wider result--are handled by "shorten" in build_binary_op.  */
237c87b03e5Sespie 
238c87b03e5Sespie       switch (ex_form)
239c87b03e5Sespie 	{
240c87b03e5Sespie 	case RSHIFT_EXPR:
241c87b03e5Sespie 	  /* We can pass truncation down through right shifting
242c87b03e5Sespie 	     when the shift count is a nonpositive constant.  */
243c87b03e5Sespie 	  if (TREE_CODE (TREE_OPERAND (expr, 1)) == INTEGER_CST
244c87b03e5Sespie 	      && tree_int_cst_lt (TREE_OPERAND (expr, 1),
245c87b03e5Sespie 				  convert (TREE_TYPE (TREE_OPERAND (expr, 1)),
246c87b03e5Sespie 					   integer_one_node)))
247c87b03e5Sespie 	    goto trunc1;
248c87b03e5Sespie 	  break;
249c87b03e5Sespie 
250c87b03e5Sespie 	case LSHIFT_EXPR:
251c87b03e5Sespie 	  /* We can pass truncation down through left shifting
252c87b03e5Sespie 	     when the shift count is a nonnegative constant and
253c87b03e5Sespie 	     the target type is unsigned.  */
254c87b03e5Sespie 	  if (TREE_CODE (TREE_OPERAND (expr, 1)) == INTEGER_CST
255c87b03e5Sespie 	      && tree_int_cst_sgn (TREE_OPERAND (expr, 1)) >= 0
256c87b03e5Sespie 	      && TREE_UNSIGNED (type)
257c87b03e5Sespie 	      && TREE_CODE (TYPE_SIZE (type)) == INTEGER_CST)
258c87b03e5Sespie 	    {
259c87b03e5Sespie 	      /* If shift count is less than the width of the truncated type,
260c87b03e5Sespie 		 really shift.  */
261c87b03e5Sespie 	      if (tree_int_cst_lt (TREE_OPERAND (expr, 1), TYPE_SIZE (type)))
262c87b03e5Sespie 		/* In this case, shifting is like multiplication.  */
263c87b03e5Sespie 		goto trunc1;
264c87b03e5Sespie 	      else
265c87b03e5Sespie 		{
266c87b03e5Sespie 		  /* If it is >= that width, result is zero.
267c87b03e5Sespie 		     Handling this with trunc1 would give the wrong result:
268c87b03e5Sespie 		     (int) ((long long) a << 32) is well defined (as 0)
269c87b03e5Sespie 		     but (int) a << 32 is undefined and would get a
270c87b03e5Sespie 		     warning.  */
271c87b03e5Sespie 
272c87b03e5Sespie 		  tree t = convert_to_integer (type, integer_zero_node);
273c87b03e5Sespie 
274c87b03e5Sespie 		  /* If the original expression had side-effects, we must
275c87b03e5Sespie 		     preserve it.  */
276c87b03e5Sespie 		  if (TREE_SIDE_EFFECTS (expr))
277c87b03e5Sespie 		    return build (COMPOUND_EXPR, type, expr, t);
278c87b03e5Sespie 		  else
279c87b03e5Sespie 		    return t;
280c87b03e5Sespie 		}
281c87b03e5Sespie 	    }
282c87b03e5Sespie 	  break;
283c87b03e5Sespie 
284c87b03e5Sespie 	case MAX_EXPR:
285c87b03e5Sespie 	case MIN_EXPR:
286c87b03e5Sespie 	case MULT_EXPR:
287c87b03e5Sespie 	  {
288c87b03e5Sespie 	    tree arg0 = get_unwidened (TREE_OPERAND (expr, 0), type);
289c87b03e5Sespie 	    tree arg1 = get_unwidened (TREE_OPERAND (expr, 1), type);
290c87b03e5Sespie 
291c87b03e5Sespie 	    /* Don't distribute unless the output precision is at least as big
292c87b03e5Sespie 	       as the actual inputs.  Otherwise, the comparison of the
293c87b03e5Sespie 	       truncated values will be wrong.  */
294c87b03e5Sespie 	    if (outprec >= TYPE_PRECISION (TREE_TYPE (arg0))
295c87b03e5Sespie 		&& outprec >= TYPE_PRECISION (TREE_TYPE (arg1))
296c87b03e5Sespie 		/* If signedness of arg0 and arg1 don't match,
297c87b03e5Sespie 		   we can't necessarily find a type to compare them in.  */
298c87b03e5Sespie 		&& (TREE_UNSIGNED (TREE_TYPE (arg0))
299c87b03e5Sespie 		    == TREE_UNSIGNED (TREE_TYPE (arg1))))
300c87b03e5Sespie 	      goto trunc1;
301c87b03e5Sespie 	    break;
302c87b03e5Sespie 	  }
303c87b03e5Sespie 
304c87b03e5Sespie 	case PLUS_EXPR:
305c87b03e5Sespie 	case MINUS_EXPR:
306c87b03e5Sespie 	case BIT_AND_EXPR:
307c87b03e5Sespie 	case BIT_IOR_EXPR:
308c87b03e5Sespie 	case BIT_XOR_EXPR:
309c87b03e5Sespie 	case BIT_ANDTC_EXPR:
310c87b03e5Sespie 	trunc1:
311c87b03e5Sespie 	  {
312c87b03e5Sespie 	    tree arg0 = get_unwidened (TREE_OPERAND (expr, 0), type);
313c87b03e5Sespie 	    tree arg1 = get_unwidened (TREE_OPERAND (expr, 1), type);
314c87b03e5Sespie 
315c87b03e5Sespie 	    if (outprec >= BITS_PER_WORD
316c87b03e5Sespie 		|| TRULY_NOOP_TRUNCATION (outprec, inprec)
317c87b03e5Sespie 		|| inprec > TYPE_PRECISION (TREE_TYPE (arg0))
318c87b03e5Sespie 		|| inprec > TYPE_PRECISION (TREE_TYPE (arg1)))
319c87b03e5Sespie 	      {
320c87b03e5Sespie 		/* Do the arithmetic in type TYPEX,
321c87b03e5Sespie 		   then convert result to TYPE.  */
322c87b03e5Sespie 		tree typex = type;
323c87b03e5Sespie 
324c87b03e5Sespie 		/* Can't do arithmetic in enumeral types
325c87b03e5Sespie 		   so use an integer type that will hold the values.  */
326c87b03e5Sespie 		if (TREE_CODE (typex) == ENUMERAL_TYPE)
327c87b03e5Sespie 		  typex = (*lang_hooks.types.type_for_size)
328c87b03e5Sespie 		    (TYPE_PRECISION (typex), TREE_UNSIGNED (typex));
329c87b03e5Sespie 
330c87b03e5Sespie 		/* But now perhaps TYPEX is as wide as INPREC.
331c87b03e5Sespie 		   In that case, do nothing special here.
332c87b03e5Sespie 		   (Otherwise would recurse infinitely in convert.  */
333c87b03e5Sespie 		if (TYPE_PRECISION (typex) != inprec)
334c87b03e5Sespie 		  {
335c87b03e5Sespie 		    /* Don't do unsigned arithmetic where signed was wanted,
336c87b03e5Sespie 		       or vice versa.
337c87b03e5Sespie 		       Exception: if both of the original operands were
338c87b03e5Sespie  		       unsigned then we can safely do the work as unsigned.
339c87b03e5Sespie 		       Exception: shift operations take their type solely
340c87b03e5Sespie 		       from the first argument.
341c87b03e5Sespie 		       Exception: the LSHIFT_EXPR case above requires that
342c87b03e5Sespie 		       we perform this operation unsigned lest we produce
343c87b03e5Sespie 		       signed-overflow undefinedness.
344c87b03e5Sespie 		       And we may need to do it as unsigned
345c87b03e5Sespie 		       if we truncate to the original size.  */
346c87b03e5Sespie 		    if (TREE_UNSIGNED (TREE_TYPE (expr))
347c87b03e5Sespie 			|| (TREE_UNSIGNED (TREE_TYPE (arg0))
348c87b03e5Sespie 			    && (TREE_UNSIGNED (TREE_TYPE (arg1))
349c87b03e5Sespie 				|| ex_form == LSHIFT_EXPR
350c87b03e5Sespie 				|| ex_form == RSHIFT_EXPR
351c87b03e5Sespie 				|| ex_form == LROTATE_EXPR
352c87b03e5Sespie 				|| ex_form == RROTATE_EXPR))
353c87b03e5Sespie 			|| ex_form == LSHIFT_EXPR)
354c87b03e5Sespie 		      typex = (*lang_hooks.types.unsigned_type) (typex);
355c87b03e5Sespie 		    else
356c87b03e5Sespie 		      typex = (*lang_hooks.types.signed_type) (typex);
357c87b03e5Sespie 		    return convert (type,
358c87b03e5Sespie 				    fold (build (ex_form, typex,
359c87b03e5Sespie 						 convert (typex, arg0),
360c87b03e5Sespie 						 convert (typex, arg1),
361c87b03e5Sespie 						 0)));
362c87b03e5Sespie 		  }
363c87b03e5Sespie 	      }
364c87b03e5Sespie 	  }
365c87b03e5Sespie 	  break;
366c87b03e5Sespie 
367c87b03e5Sespie 	case NEGATE_EXPR:
368c87b03e5Sespie 	case BIT_NOT_EXPR:
369c87b03e5Sespie 	  /* This is not correct for ABS_EXPR,
370c87b03e5Sespie 	     since we must test the sign before truncation.  */
371c87b03e5Sespie 	  {
372c87b03e5Sespie 	    tree typex = type;
373c87b03e5Sespie 
374c87b03e5Sespie 	    /* Can't do arithmetic in enumeral types
375c87b03e5Sespie 	       so use an integer type that will hold the values.  */
376c87b03e5Sespie 	    if (TREE_CODE (typex) == ENUMERAL_TYPE)
377c87b03e5Sespie 	      typex = (*lang_hooks.types.type_for_size)
378c87b03e5Sespie 		(TYPE_PRECISION (typex), TREE_UNSIGNED (typex));
379c87b03e5Sespie 
380c87b03e5Sespie 	    /* But now perhaps TYPEX is as wide as INPREC.
381c87b03e5Sespie 	       In that case, do nothing special here.
382c87b03e5Sespie 	       (Otherwise would recurse infinitely in convert.  */
383c87b03e5Sespie 	    if (TYPE_PRECISION (typex) != inprec)
384c87b03e5Sespie 	      {
385c87b03e5Sespie 		/* Don't do unsigned arithmetic where signed was wanted,
386c87b03e5Sespie 		   or vice versa.  */
387c87b03e5Sespie 		if (TREE_UNSIGNED (TREE_TYPE (expr)))
388c87b03e5Sespie 		  typex = (*lang_hooks.types.unsigned_type) (typex);
389c87b03e5Sespie 		else
390c87b03e5Sespie 		  typex = (*lang_hooks.types.signed_type) (typex);
391c87b03e5Sespie 		return convert (type,
392c87b03e5Sespie 				fold (build1 (ex_form, typex,
393c87b03e5Sespie 					      convert (typex,
394c87b03e5Sespie 						       TREE_OPERAND (expr, 0)))));
395c87b03e5Sespie 	      }
396c87b03e5Sespie 	  }
397c87b03e5Sespie 
398c87b03e5Sespie 	case NOP_EXPR:
399c87b03e5Sespie 	  /* Don't introduce a
400c87b03e5Sespie 	     "can't convert between vector values of different size" error.  */
401c87b03e5Sespie 	  if (TREE_CODE (TREE_TYPE (TREE_OPERAND (expr, 0))) == VECTOR_TYPE
402c87b03e5Sespie 	      && (GET_MODE_SIZE (TYPE_MODE (TREE_TYPE (TREE_OPERAND (expr, 0))))
403c87b03e5Sespie 		  != GET_MODE_SIZE (TYPE_MODE (type))))
404c87b03e5Sespie 	    break;
405c87b03e5Sespie 	  /* If truncating after truncating, might as well do all at once.
406c87b03e5Sespie 	     If truncating after extending, we may get rid of wasted work.  */
407c87b03e5Sespie 	  return convert (type, get_unwidened (TREE_OPERAND (expr, 0), type));
408c87b03e5Sespie 
409c87b03e5Sespie 	case COND_EXPR:
410c87b03e5Sespie 	  /* It is sometimes worthwhile to push the narrowing down through
411c87b03e5Sespie 	     the conditional and never loses.  */
412c87b03e5Sespie 	  return fold (build (COND_EXPR, type, TREE_OPERAND (expr, 0),
413c87b03e5Sespie 			      convert (type, TREE_OPERAND (expr, 1)),
414c87b03e5Sespie 			      convert (type, TREE_OPERAND (expr, 2))));
415c87b03e5Sespie 
416c87b03e5Sespie 	default:
417c87b03e5Sespie 	  break;
418c87b03e5Sespie 	}
419c87b03e5Sespie 
420c87b03e5Sespie       return build1 (NOP_EXPR, type, expr);
421c87b03e5Sespie 
422c87b03e5Sespie     case REAL_TYPE:
423c87b03e5Sespie       return build1 (FIX_TRUNC_EXPR, type, expr);
424c87b03e5Sespie 
425c87b03e5Sespie     case COMPLEX_TYPE:
426c87b03e5Sespie       return convert (type,
427c87b03e5Sespie 		      fold (build1 (REALPART_EXPR,
428c87b03e5Sespie 				    TREE_TYPE (TREE_TYPE (expr)), expr)));
429c87b03e5Sespie 
430c87b03e5Sespie     case VECTOR_TYPE:
431c87b03e5Sespie       if (GET_MODE_SIZE (TYPE_MODE (type))
432c87b03e5Sespie 	  != GET_MODE_SIZE (TYPE_MODE (TREE_TYPE (expr))))
433c87b03e5Sespie 	{
434c87b03e5Sespie 	  error ("can't convert between vector values of different size");
435c87b03e5Sespie 	  return error_mark_node;
436c87b03e5Sespie 	}
437c87b03e5Sespie       return build1 (NOP_EXPR, type, expr);
438c87b03e5Sespie 
439c87b03e5Sespie     default:
440c87b03e5Sespie       error ("aggregate value used where an integer was expected");
441c87b03e5Sespie       return convert (type, integer_zero_node);
442c87b03e5Sespie     }
443c87b03e5Sespie }
444c87b03e5Sespie 
445c87b03e5Sespie /* Convert EXPR to the complex type TYPE in the usual ways.  */
446c87b03e5Sespie 
447c87b03e5Sespie tree
convert_to_complex(type,expr)448c87b03e5Sespie convert_to_complex (type, expr)
449c87b03e5Sespie      tree type, expr;
450c87b03e5Sespie {
451c87b03e5Sespie   tree subtype = TREE_TYPE (type);
452c87b03e5Sespie 
453c87b03e5Sespie   switch (TREE_CODE (TREE_TYPE (expr)))
454c87b03e5Sespie     {
455c87b03e5Sespie     case REAL_TYPE:
456c87b03e5Sespie     case INTEGER_TYPE:
457c87b03e5Sespie     case ENUMERAL_TYPE:
458c87b03e5Sespie     case BOOLEAN_TYPE:
459c87b03e5Sespie     case CHAR_TYPE:
460c87b03e5Sespie       return build (COMPLEX_EXPR, type, convert (subtype, expr),
461c87b03e5Sespie 		    convert (subtype, integer_zero_node));
462c87b03e5Sespie 
463c87b03e5Sespie     case COMPLEX_TYPE:
464c87b03e5Sespie       {
465c87b03e5Sespie 	tree elt_type = TREE_TYPE (TREE_TYPE (expr));
466c87b03e5Sespie 
467c87b03e5Sespie 	if (TYPE_MAIN_VARIANT (elt_type) == TYPE_MAIN_VARIANT (subtype))
468c87b03e5Sespie 	  return expr;
469c87b03e5Sespie 	else if (TREE_CODE (expr) == COMPLEX_EXPR)
470c87b03e5Sespie 	  return fold (build (COMPLEX_EXPR,
471c87b03e5Sespie 			      type,
472c87b03e5Sespie 			      convert (subtype, TREE_OPERAND (expr, 0)),
473c87b03e5Sespie 			      convert (subtype, TREE_OPERAND (expr, 1))));
474c87b03e5Sespie 	else
475c87b03e5Sespie 	  {
476c87b03e5Sespie 	    expr = save_expr (expr);
477c87b03e5Sespie 	    return
478c87b03e5Sespie 	      fold (build (COMPLEX_EXPR,
479c87b03e5Sespie 			   type, convert (subtype,
480c87b03e5Sespie 					  fold (build1 (REALPART_EXPR,
481c87b03e5Sespie 							TREE_TYPE (TREE_TYPE (expr)),
482c87b03e5Sespie 							expr))),
483c87b03e5Sespie 			   convert (subtype,
484c87b03e5Sespie 				    fold (build1 (IMAGPART_EXPR,
485c87b03e5Sespie 						  TREE_TYPE (TREE_TYPE (expr)),
486c87b03e5Sespie 						  expr)))));
487c87b03e5Sespie 	  }
488c87b03e5Sespie       }
489c87b03e5Sespie 
490c87b03e5Sespie     case POINTER_TYPE:
491c87b03e5Sespie     case REFERENCE_TYPE:
492c87b03e5Sespie       error ("pointer value used where a complex was expected");
493c87b03e5Sespie       return convert_to_complex (type, integer_zero_node);
494c87b03e5Sespie 
495c87b03e5Sespie     default:
496c87b03e5Sespie       error ("aggregate value used where a complex was expected");
497c87b03e5Sespie       return convert_to_complex (type, integer_zero_node);
498c87b03e5Sespie     }
499c87b03e5Sespie }
500c87b03e5Sespie 
501c87b03e5Sespie /* Convert EXPR to the vector type TYPE in the usual ways.  */
502c87b03e5Sespie 
503c87b03e5Sespie tree
convert_to_vector(type,expr)504c87b03e5Sespie convert_to_vector (type, expr)
505c87b03e5Sespie      tree type, expr;
506c87b03e5Sespie {
507c87b03e5Sespie   switch (TREE_CODE (TREE_TYPE (expr)))
508c87b03e5Sespie     {
509c87b03e5Sespie     case INTEGER_TYPE:
510c87b03e5Sespie     case VECTOR_TYPE:
511c87b03e5Sespie       if (GET_MODE_SIZE (TYPE_MODE (type))
512c87b03e5Sespie 	  != GET_MODE_SIZE (TYPE_MODE (TREE_TYPE (expr))))
513c87b03e5Sespie 	{
514c87b03e5Sespie 	  error ("can't convert between vector values of different size");
515c87b03e5Sespie 	  return error_mark_node;
516c87b03e5Sespie 	}
517c87b03e5Sespie       return build1 (NOP_EXPR, type, expr);
518c87b03e5Sespie 
519c87b03e5Sespie     default:
520c87b03e5Sespie       error ("can't convert value to a vector");
521c87b03e5Sespie       return convert_to_vector (type, integer_zero_node);
522c87b03e5Sespie     }
523c87b03e5Sespie }
524