diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 48c0d01f8cb405f3dfa87ad6e4bcdd8929b45ce4..e91f89564cb8a0e63874efe32118b0fa9b7b9e0b 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,21 @@
+2013-11-18  Richard Sandiford  <rdsandiford@googlemail.com>
+
+	* builtins.c, config/alpha/alpha.c, config/iq2000/iq2000.c,
+	config/mips/mips.c, dbxout.c, dwarf2out.c, expr.c, fold-const.c,
+	gimple-fold.c, godump.c, omp-low.c, predict.c, sdbout.c, stor-layout.c,
+	tree-dfa.c, tree-sra.c, tree-ssa-forwprop.c, tree-ssa-loop-prefetch.c,
+	tree-ssa-phiopt.c, tree-ssa-sccvn.c, tree-ssa-strlen.c,
+	tree-ssa-structalias.c, tree-vect-data-refs.c, tree-vect-patterns.c,
+	tree.c, varasm.c, alias.c, cfgexpand.c, config/aarch64/aarch64.c,
+	config/arm/arm.c, config/epiphany/epiphany.c, config/i386/i386.c,
+	config/m32c/m32c-pragma.c, config/mep/mep-pragma.c,
+	config/rs6000/rs6000.c, config/sparc/sparc.c, emit-rtl.c, function.c,
+	gimplify.c, ipa-prop.c, stmt.c, trans-mem.c, tree-cfg.c,
+	tree-object-size.c, tree-ssa-ccp.c, tree-ssa-loop-ivcanon.c,
+	tree-stdarg.c, tree-switch-conversion.c, tree-vect-generic.c,
+	tree-vrp.c, tsan.c, ubsan.c: Replace host_integerp (..., 1) with
+	tree_fits_uhwi_p throughout.
+
 2013-11-18  Richard Sandiford  <rdsandiford@googlemail.com>
 
 	* builtins.c, config/alpha/alpha.c, config/c6x/predicates.md,
diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index facd5d61ef86f41a348e4c703bcabeacd88e8c0f..3b9af6edfacbb577287d66fc882a87014b77d21d 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,8 @@
+2013-11-18  Richard Sandiford  <rdsandiford@googlemail.com>
+
+	* gcc-interface/decl.c, gcc-interface/misc.c, gcc-interface/utils.c:
+	Replace host_integerp (..., 1) with tree_fits_uhwi_p throughout.
+
 2013-11-18  Richard Sandiford  <rdsandiford@googlemail.com>
 
 	* gcc-interface/cuintp.c: Replace host_integerp (..., 0) with
diff --git a/gcc/ada/gcc-interface/decl.c b/gcc/ada/gcc-interface/decl.c
index d3cc5466514c2d113e6908bc7bc761341ac51298..3ad53c4120d88de321a91cd621d488b6bb517be2 100644
--- a/gcc/ada/gcc-interface/decl.c
+++ b/gcc/ada/gcc-interface/decl.c
@@ -837,7 +837,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		align_cap = get_mode_alignment (ptr_mode);
 	      }
 
-	    if (!host_integerp (TYPE_SIZE (gnu_type), 1)
+	    if (!tree_fits_uhwi_p (TYPE_SIZE (gnu_type))
 		|| compare_tree_int (TYPE_SIZE (gnu_type), size_cap) > 0)
 	      align = 0;
 	    else if (compare_tree_int (TYPE_SIZE (gnu_type), align_cap) > 0)
@@ -1482,7 +1482,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 	    && const_flag
 	    && gnu_expr && TREE_CONSTANT (gnu_expr)
 	    && AGGREGATE_TYPE_P (gnu_type)
-	    && host_integerp (TYPE_SIZE_UNIT (gnu_type), 1)
+	    && tree_fits_uhwi_p (TYPE_SIZE_UNIT (gnu_type))
 	    && !(TYPE_IS_PADDING_P (gnu_type)
 		 && !host_integerp (TYPE_SIZE_UNIT
 				    (TREE_TYPE (TYPE_FIELDS (gnu_type))), 1)))
@@ -3497,7 +3497,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 			gnu_size = DECL_SIZE (gnu_old_field);
 			if (RECORD_OR_UNION_TYPE_P (gnu_field_type)
 			    && !TYPE_FAT_POINTER_P (gnu_field_type)
-			    && host_integerp (TYPE_SIZE (gnu_field_type), 1))
+			    && tree_fits_uhwi_p (TYPE_SIZE (gnu_field_type)))
 			  gnu_field_type
 			    = make_packable_type (gnu_field_type, true);
 		      }
@@ -4922,7 +4922,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 
 	      /* Consider an alignment as suspicious if the alignment/size
 		 ratio is greater or equal to the byte/bit ratio.  */
-	      if (host_integerp (size, 1)
+	      if (tree_fits_uhwi_p (size)
 		  && align >= TREE_INT_CST_LOW (size) * BITS_PER_UNIT)
 		post_error_ne ("?suspiciously large alignment specified for&",
 			       Expression (Alignment_Clause (gnat_entity)),
@@ -4930,12 +4930,12 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 	    }
 	}
       else if (Is_Atomic (gnat_entity) && !gnu_size
-	       && host_integerp (TYPE_SIZE (gnu_type), 1)
+	       && tree_fits_uhwi_p (TYPE_SIZE (gnu_type))
 	       && integer_pow2p (TYPE_SIZE (gnu_type)))
 	align = MIN (BIGGEST_ALIGNMENT,
 		     tree_low_cst (TYPE_SIZE (gnu_type), 1));
       else if (Is_Atomic (gnat_entity) && gnu_size
-	       && host_integerp (gnu_size, 1)
+	       && tree_fits_uhwi_p (gnu_size)
 	       && integer_pow2p (gnu_size))
 	align = MIN (BIGGEST_ALIGNMENT, tree_low_cst (gnu_size, 1));
 
@@ -5583,7 +5583,7 @@ gnat_to_gnu_component_type (Entity_Id gnat_array, bool definition,
       && !Strict_Alignment (gnat_type)
       && RECORD_OR_UNION_TYPE_P (gnu_type)
       && !TYPE_FAT_POINTER_P (gnu_type)
-      && host_integerp (TYPE_SIZE (gnu_type), 1))
+      && tree_fits_uhwi_p (TYPE_SIZE (gnu_type)))
     gnu_type = make_packable_type (gnu_type, false);
 
   if (Has_Atomic_Components (gnat_array))
@@ -6507,7 +6507,7 @@ gnat_to_gnu_field (Entity_Id gnat_field, tree gnu_record_type, int packed,
   if (!needs_strict_alignment
       && RECORD_OR_UNION_TYPE_P (gnu_field_type)
       && !TYPE_FAT_POINTER_P (gnu_field_type)
-      && host_integerp (TYPE_SIZE (gnu_field_type), 1)
+      && tree_fits_uhwi_p (TYPE_SIZE (gnu_field_type))
       && (packed == 1
 	  || (gnu_size
 	      && (tree_int_cst_lt (gnu_size, TYPE_SIZE (gnu_field_type))
diff --git a/gcc/ada/gcc-interface/misc.c b/gcc/ada/gcc-interface/misc.c
index 3abe57b6bd97b58b38dee44389b6cfe8d4624931..a82f6fd8f82cf68352938bfa44e8a295429c3b6c 100644
--- a/gcc/ada/gcc-interface/misc.c
+++ b/gcc/ada/gcc-interface/misc.c
@@ -591,7 +591,7 @@ gnat_type_max_size (const_tree gnu_type)
 
   /* If we don't have a constant, see what we can get from TYPE_ADA_SIZE,
      which should stay untouched.  */
-  if (!host_integerp (max_unitsize, 1)
+  if (!tree_fits_uhwi_p (max_unitsize)
       && RECORD_OR_UNION_TYPE_P (gnu_type)
       && !TYPE_FAT_POINTER_P (gnu_type)
       && TYPE_ADA_SIZE (gnu_type))
@@ -600,7 +600,7 @@ gnat_type_max_size (const_tree gnu_type)
 
       /* If we have succeeded in finding a constant, round it up to the
 	 type's alignment and return the result in units.  */
-      if (host_integerp (max_adasize, 1))
+      if (tree_fits_uhwi_p (max_adasize))
 	max_unitsize
 	  = size_binop (CEIL_DIV_EXPR,
 			round_up (max_adasize, TYPE_ALIGN (gnu_type)),
diff --git a/gcc/ada/gcc-interface/utils.c b/gcc/ada/gcc-interface/utils.c
index 01a60280e630948f9886b37988ffb0e050fcd687..4588c52cf19fa1db3ff5907d15838c6eae6f3b78 100644
--- a/gcc/ada/gcc-interface/utils.c
+++ b/gcc/ada/gcc-interface/utils.c
@@ -806,7 +806,7 @@ make_packable_type (tree type, bool in_record)
 
       /* Do not try to shrink the size if the RM size is not constant.  */
       if (TYPE_CONTAINS_TEMPLATE_P (type)
-	  || !host_integerp (TYPE_ADA_SIZE (type), 1))
+	  || !tree_fits_uhwi_p (TYPE_ADA_SIZE (type)))
 	return type;
 
       /* Round the RM size up to a unit boundary to get the minimal size
@@ -832,7 +832,7 @@ make_packable_type (tree type, bool in_record)
 
       if (RECORD_OR_UNION_TYPE_P (new_field_type)
 	  && !TYPE_FAT_POINTER_P (new_field_type)
-	  && host_integerp (TYPE_SIZE (new_field_type), 1))
+	  && tree_fits_uhwi_p (TYPE_SIZE (new_field_type)))
 	new_field_type = make_packable_type (new_field_type, true);
 
       /* However, for the last field in a not already packed record type
@@ -915,7 +915,7 @@ make_type_from_size (tree type, tree size_tree, bool for_biased)
 
   /* If size indicates an error, just return TYPE to avoid propagating
      the error.  Likewise if it's too large to represent.  */
-  if (!size_tree || !host_integerp (size_tree, 1))
+  if (!size_tree || !tree_fits_uhwi_p (size_tree))
     return type;
 
   size = tree_low_cst (size_tree, 1);
@@ -1741,7 +1741,7 @@ rest_of_record_type_compilation (tree record_type)
 
 	  if (!pos
 	      && TREE_CODE (curpos) == MULT_EXPR
-	      && host_integerp (TREE_OPERAND (curpos, 1), 1))
+	      && tree_fits_uhwi_p (TREE_OPERAND (curpos, 1)))
 	    {
 	      tree offset = TREE_OPERAND (curpos, 0);
 	      align = tree_low_cst (TREE_OPERAND (curpos, 1), 1);
@@ -1751,7 +1751,7 @@ rest_of_record_type_compilation (tree record_type)
 	    }
 	  else if (!pos
 		   && TREE_CODE (curpos) == PLUS_EXPR
-		   && host_integerp (TREE_OPERAND (curpos, 1), 1)
+		   && tree_fits_uhwi_p (TREE_OPERAND (curpos, 1))
 		   && TREE_CODE (TREE_OPERAND (curpos, 0)) == MULT_EXPR
 		   && host_integerp
 		      (TREE_OPERAND (TREE_OPERAND (curpos, 0), 1), 1))
@@ -2377,7 +2377,7 @@ create_field_decl (tree field_name, tree field_type, tree record_type,
 	 that an alignment of 0 is taken as infinite.  */
       unsigned int known_align;
 
-      if (host_integerp (pos, 1))
+      if (tree_fits_uhwi_p (pos))
 	known_align = tree_low_cst (pos, 1) & - tree_low_cst (pos, 1);
       else
 	known_align = BITS_PER_UNIT;
@@ -2388,7 +2388,7 @@ create_field_decl (tree field_name, tree field_type, tree record_type,
 
       layout_decl (field_decl, known_align);
       SET_DECL_OFFSET_ALIGN (field_decl,
-			     host_integerp (pos, 1) ? BIGGEST_ALIGNMENT
+			     tree_fits_uhwi_p (pos) ? BIGGEST_ALIGNMENT
 			     : BITS_PER_UNIT);
       pos_from_bit (&DECL_FIELD_OFFSET (field_decl),
 		    &DECL_FIELD_BIT_OFFSET (field_decl),
@@ -2548,7 +2548,7 @@ invalidate_global_renaming_pointers (void)
 bool
 value_factor_p (tree value, HOST_WIDE_INT factor)
 {
-  if (host_integerp (value, 1))
+  if (tree_fits_uhwi_p (value))
     return tree_low_cst (value, 1) % factor == 0;
 
   if (TREE_CODE (value) == MULT_EXPR)
@@ -2608,14 +2608,14 @@ potential_alignment_gap (tree prev_field, tree curr_field, tree offset)
   /* If the distance between the end of prev_field and the beginning of
      curr_field is constant, then there is a gap if the value of this
      constant is not null. */
-  if (offset && host_integerp (offset, 1))
+  if (offset && tree_fits_uhwi_p (offset))
     return !integer_zerop (offset);
 
   /* If the size and position of the previous field are constant,
      then check the sum of this size and position. There will be a gap
      iff it is not multiple of the current field alignment. */
-  if (host_integerp (DECL_SIZE (prev_field), 1)
-      && host_integerp (bit_position (prev_field), 1))
+  if (tree_fits_uhwi_p (DECL_SIZE (prev_field))
+      && tree_fits_uhwi_p (bit_position (prev_field)))
     return ((tree_low_cst (bit_position (prev_field), 1)
 	     + tree_low_cst (DECL_SIZE (prev_field), 1))
 	    % DECL_ALIGN (curr_field) != 0);
@@ -6302,7 +6302,7 @@ handle_vector_size_attribute (tree *node, tree name, tree args,
 
   size = TREE_VALUE (args);
 
-  if (!host_integerp (size, 1))
+  if (!tree_fits_uhwi_p (size))
     {
       warning (OPT_Wattributes, "%qs attribute ignored",
 	       IDENTIFIER_POINTER (name));
@@ -6334,7 +6334,7 @@ handle_vector_size_attribute (tree *node, tree name, tree args,
       || (!SCALAR_FLOAT_MODE_P (orig_mode)
 	  && GET_MODE_CLASS (orig_mode) != MODE_INT
 	  && !ALL_SCALAR_FIXED_POINT_MODE_P (orig_mode))
-      || !host_integerp (TYPE_SIZE_UNIT (type), 1)
+      || !tree_fits_uhwi_p (TYPE_SIZE_UNIT (type))
       || TREE_CODE (type) == BOOLEAN_TYPE)
     {
       error ("invalid vector type for attribute %qs",
@@ -6403,7 +6403,7 @@ handle_vector_type_attribute (tree *node, tree name, tree ARG_UNUSED (args),
      bases, and this attribute is for binding implementors, not end-users, so
      we should never get there from legitimate explicit uses.  */
 
-  if (!host_integerp (rep_size, 1))
+  if (!tree_fits_uhwi_p (rep_size))
     return NULL_TREE;
 
   /* Get the element type/mode and check this is something we know
@@ -6418,7 +6418,7 @@ handle_vector_type_attribute (tree *node, tree name, tree ARG_UNUSED (args),
       || (!SCALAR_FLOAT_MODE_P (elem_mode)
 	  && GET_MODE_CLASS (elem_mode) != MODE_INT
 	  && !ALL_SCALAR_FIXED_POINT_MODE_P (elem_mode))
-      || !host_integerp (TYPE_SIZE_UNIT (elem_type), 1))
+      || !tree_fits_uhwi_p (TYPE_SIZE_UNIT (elem_type)))
     {
       error ("invalid element type for attribute %qs",
 	     IDENTIFIER_POINTER (name));
diff --git a/gcc/alias.c b/gcc/alias.c
index 1736169b476f0c9052fc587851d1ed5ec81e0479..b874a045efa222a1bc2a98a49dacf00ff911c476 100644
--- a/gcc/alias.c
+++ b/gcc/alias.c
@@ -338,7 +338,7 @@ ao_ref_from_mem (ao_ref *ref, const_rtx mem)
   if (MEM_EXPR (mem) != get_spill_slot_decl (false)
       && (ref->offset < 0
 	  || (DECL_P (ref->base)
-	      && (!host_integerp (DECL_SIZE (ref->base), 1)
+	      && (!tree_fits_uhwi_p (DECL_SIZE (ref->base))
 		  || (TREE_INT_CST_LOW (DECL_SIZE ((ref->base)))
 		      < (unsigned HOST_WIDE_INT)(ref->offset + ref->size))))))
     return false;
@@ -2347,7 +2347,7 @@ adjust_offset_for_component_ref (tree x, bool *known_p,
       tree xoffset = component_ref_field_offset (x);
       tree field = TREE_OPERAND (x, 1);
 
-      if (! host_integerp (xoffset, 1))
+      if (! tree_fits_uhwi_p (xoffset))
 	{
 	  *known_p = false;
 	  return;
diff --git a/gcc/builtins.c b/gcc/builtins.c
index 7807b60e53963eec011eeb82a7de951075ca6cc1..32812002502fb90da721b956f2bde91e4eff7ada 100644
--- a/gcc/builtins.c
+++ b/gcc/builtins.c
@@ -658,7 +658,7 @@ c_getstr (tree src)
 
   if (offset_node == 0)
     return TREE_STRING_POINTER (src);
-  else if (!host_integerp (offset_node, 1)
+  else if (!tree_fits_uhwi_p (offset_node)
 	   || compare_tree_int (offset_node, TREE_STRING_LENGTH (src) - 1) > 0)
     return 0;
 
@@ -3125,11 +3125,11 @@ determine_block_size (tree len, rtx len_rtx,
 	}
       else
 	{
-	  if (host_integerp (TYPE_MIN_VALUE (TREE_TYPE (len)), 1))
+	  if (tree_fits_uhwi_p (TYPE_MIN_VALUE (TREE_TYPE (len))))
 	    *min_size = tree_low_cst (TYPE_MIN_VALUE (TREE_TYPE (len)), 1);
 	  else
 	    *min_size = 0;
-	  if (host_integerp (TYPE_MAX_VALUE (TREE_TYPE (len)), 1))
+	  if (tree_fits_uhwi_p (TYPE_MAX_VALUE (TREE_TYPE (len))))
 	    *max_size = tree_low_cst (TYPE_MAX_VALUE (TREE_TYPE (len)), 1);
 	  else
 	    *max_size = GET_MODE_MASK (GET_MODE (len_rtx));
@@ -3279,7 +3279,7 @@ expand_builtin_mempcpy_args (tree dest, tree src, tree len,
 	return NULL_RTX;
 
       /* If LEN is not constant, call the normal function.  */
-      if (! host_integerp (len, 1))
+      if (! tree_fits_uhwi_p (len))
 	return NULL_RTX;
 
       len_rtx = expand_normal (len);
@@ -3514,7 +3514,7 @@ expand_builtin_strncpy (tree exp, rtx target)
       tree slen = c_strlen (src, 1);
 
       /* We must be passed a constant len and src parameter.  */
-      if (!host_integerp (len, 1) || !slen || !host_integerp (slen, 1))
+      if (!tree_fits_uhwi_p (len) || !slen || !tree_fits_uhwi_p (slen))
 	return NULL_RTX;
 
       slen = size_binop_loc (loc, PLUS_EXPR, slen, ssize_int (1));
@@ -3528,7 +3528,7 @@ expand_builtin_strncpy (tree exp, rtx target)
 	  const char *p = c_getstr (src);
 	  rtx dest_mem;
 
-	  if (!p || dest_align == 0 || !host_integerp (len, 1)
+	  if (!p || dest_align == 0 || !tree_fits_uhwi_p (len)
 	      || !can_store_by_pieces (tree_low_cst (len, 1),
 				       builtin_strncpy_read_str,
 				       CONST_CAST (char *, p),
@@ -3672,7 +3672,7 @@ expand_builtin_memset_args (tree dest, tree val, tree len,
        * the coefficients by pieces (in the required modes).
        * We can't pass builtin_memset_gen_str as that emits RTL.  */
       c = 1;
-      if (host_integerp (len, 1)
+      if (tree_fits_uhwi_p (len)
 	  && can_store_by_pieces (tree_low_cst (len, 1),
 				  builtin_memset_read_str, &c, dest_align,
 				  true))
@@ -3697,7 +3697,7 @@ expand_builtin_memset_args (tree dest, tree val, tree len,
 
   if (c)
     {
-      if (host_integerp (len, 1)
+      if (tree_fits_uhwi_p (len)
 	  && can_store_by_pieces (tree_low_cst (len, 1),
 				  builtin_memset_read_str, &c, dest_align,
 				  true))
@@ -4394,7 +4394,7 @@ expand_builtin_frame_address (tree fndecl, tree exp)
   if (call_expr_nargs (exp) == 0)
     /* Warning about missing arg was already issued.  */
     return const0_rtx;
-  else if (! host_integerp (CALL_EXPR_ARG (exp, 0), 1))
+  else if (! tree_fits_uhwi_p (CALL_EXPR_ARG (exp, 0)))
     {
       if (DECL_FUNCTION_CODE (fndecl) == BUILT_IN_FRAME_ADDRESS)
 	error ("invalid argument to %<__builtin_frame_address%>");
@@ -8646,7 +8646,7 @@ fold_builtin_memset (location_t loc, tree dest, tree c, tree len,
       || ! validate_arg (len, INTEGER_TYPE))
     return NULL_TREE;
 
-  if (! host_integerp (len, 1))
+  if (! tree_fits_uhwi_p (len))
     return NULL_TREE;
 
   /* If the LEN parameter is zero, return DEST.  */
@@ -8779,7 +8779,7 @@ fold_builtin_memory_op (location_t loc, tree dest, tree src,
 	  if (!dest_align || !src_align)
 	    return NULL_TREE;
 	  if (readonly_data_expr (src)
-	      || (host_integerp (len, 1)
+	      || (tree_fits_uhwi_p (len)
 		  && (MIN (src_align, dest_align) / BITS_PER_UNIT
 		      >= (unsigned HOST_WIDE_INT) tree_low_cst (len, 1))))
 	    {
@@ -8804,7 +8804,7 @@ fold_builtin_memory_op (location_t loc, tree dest, tree src,
 	      destvar = TREE_OPERAND (dest, 0);
 	      dest_base = get_ref_base_and_extent (destvar, &dest_offset,
 						   &size, &maxsize);
-	      if (host_integerp (len, 1))
+	      if (tree_fits_uhwi_p (len))
 		maxsize = tree_low_cst (len, 1);
 	      else
 		maxsize = -1;
@@ -9159,7 +9159,7 @@ fold_builtin_memchr (location_t loc, tree arg1, tree arg2, tree len, tree type)
       const char *p1;
 
       if (TREE_CODE (arg2) != INTEGER_CST
-	  || !host_integerp (len, 1))
+	  || !tree_fits_uhwi_p (len))
 	return NULL_TREE;
 
       p1 = c_getstr (arg1);
@@ -9211,7 +9211,7 @@ fold_builtin_memcmp (location_t loc, tree arg1, tree arg2, tree len)
 
   /* If all arguments are constant, and the value of len is not greater
      than the lengths of arg1 and arg2, evaluate at compile-time.  */
-  if (host_integerp (len, 1) && p1 && p2
+  if (tree_fits_uhwi_p (len) && p1 && p2
       && compare_tree_int (len, strlen (p1) + 1) <= 0
       && compare_tree_int (len, strlen (p2) + 1) <= 0)
     {
@@ -9227,7 +9227,7 @@ fold_builtin_memcmp (location_t loc, tree arg1, tree arg2, tree len)
 
   /* If len parameter is one, return an expression corresponding to
      (*(const unsigned char*)arg1 - (const unsigned char*)arg2).  */
-  if (host_integerp (len, 1) && tree_low_cst (len, 1) == 1)
+  if (tree_fits_uhwi_p (len) && tree_low_cst (len, 1) == 1)
     {
       tree cst_uchar_node = build_type_variant (unsigned_char_type_node, 1, 0);
       tree cst_uchar_ptr_node
@@ -9339,7 +9339,7 @@ fold_builtin_strncmp (location_t loc, tree arg1, tree arg2, tree len)
   p1 = c_getstr (arg1);
   p2 = c_getstr (arg2);
 
-  if (host_integerp (len, 1) && p1 && p2)
+  if (tree_fits_uhwi_p (len) && p1 && p2)
     {
       const int i = strncmp (p1, p2, tree_low_cst (len, 1));
       if (i > 0)
@@ -9387,7 +9387,7 @@ fold_builtin_strncmp (location_t loc, tree arg1, tree arg2, tree len)
 
   /* If len parameter is one, return an expression corresponding to
      (*(const unsigned char*)arg1 - (const unsigned char*)arg2).  */
-  if (host_integerp (len, 1) && tree_low_cst (len, 1) == 1)
+  if (tree_fits_uhwi_p (len) && tree_low_cst (len, 1) == 1)
     {
       tree cst_uchar_node = build_type_variant (unsigned_char_type_node, 1, 0);
       tree cst_uchar_ptr_node
@@ -12242,7 +12242,7 @@ fold_builtin_snprintf (location_t loc, tree dest, tree destsize, tree fmt,
   if (orig && !validate_arg (orig, POINTER_TYPE))
     return NULL_TREE;
 
-  if (!host_integerp (destsize, 1))
+  if (!tree_fits_uhwi_p (destsize))
     return NULL_TREE;
 
   /* Check whether the format is a literal string constant.  */
@@ -12301,7 +12301,7 @@ fold_builtin_snprintf (location_t loc, tree dest, tree destsize, tree fmt,
 	return NULL_TREE;
 
       retval = c_strlen (orig, 1);
-      if (!retval || !host_integerp (retval, 1))  
+      if (!retval || !tree_fits_uhwi_p (retval))
 	return NULL_TREE;
 
       origlen = tree_low_cst (retval, 1);
@@ -12395,10 +12395,10 @@ expand_builtin_memory_chk (tree exp, rtx target, enum machine_mode mode,
   len = CALL_EXPR_ARG (exp, 2);
   size = CALL_EXPR_ARG (exp, 3);
 
-  if (! host_integerp (size, 1))
+  if (! tree_fits_uhwi_p (size))
     return NULL_RTX;
 
-  if (host_integerp (len, 1) || integer_all_onesp (size))
+  if (tree_fits_uhwi_p (len) || integer_all_onesp (size))
     {
       tree fn;
 
@@ -12529,22 +12529,22 @@ maybe_emit_chk_warning (tree exp, enum built_in_function fcode)
   if (!len || !size)
     return;
 
-  if (! host_integerp (size, 1) || integer_all_onesp (size))
+  if (! tree_fits_uhwi_p (size) || integer_all_onesp (size))
     return;
 
   if (is_strlen)
     {
       len = c_strlen (len, 1);
-      if (! len || ! host_integerp (len, 1) || tree_int_cst_lt (len, size))
+      if (! len || ! tree_fits_uhwi_p (len) || tree_int_cst_lt (len, size))
 	return;
     }
   else if (fcode == BUILT_IN_STRNCAT_CHK)
     {
       tree src = CALL_EXPR_ARG (exp, 1);
-      if (! src || ! host_integerp (len, 1) || tree_int_cst_lt (len, size))
+      if (! src || ! tree_fits_uhwi_p (len) || tree_int_cst_lt (len, size))
 	return;
       src = c_strlen (src, 1);
-      if (! src || ! host_integerp (src, 1))
+      if (! src || ! tree_fits_uhwi_p (src))
 	{
 	  warning_at (loc, 0, "%Kcall to %D might overflow destination buffer",
 		      exp, get_callee_fndecl (exp));
@@ -12553,7 +12553,7 @@ maybe_emit_chk_warning (tree exp, enum built_in_function fcode)
       else if (tree_int_cst_lt (src, size))
 	return;
     }
-  else if (! host_integerp (len, 1) || ! tree_int_cst_lt (size, len))
+  else if (! tree_fits_uhwi_p (len) || ! tree_int_cst_lt (size, len))
     return;
 
   warning_at (loc, 0, "%Kcall to %D will always overflow destination buffer",
@@ -12577,7 +12577,7 @@ maybe_emit_sprintf_chk_warning (tree exp, enum built_in_function fcode)
   size = CALL_EXPR_ARG (exp, 2);
   fmt = CALL_EXPR_ARG (exp, 3);
 
-  if (! host_integerp (size, 1) || integer_all_onesp (size))
+  if (! tree_fits_uhwi_p (size) || integer_all_onesp (size))
     return;
 
   /* Check whether the format is a literal string constant.  */
@@ -12605,7 +12605,7 @@ maybe_emit_sprintf_chk_warning (tree exp, enum built_in_function fcode)
 	return;
 
       len = c_strlen (arg, 1);
-      if (!len || ! host_integerp (len, 1))
+      if (!len || ! tree_fits_uhwi_p (len))
 	return;
     }
   else
@@ -12726,17 +12726,17 @@ fold_builtin_memory_chk (location_t loc, tree fndecl,
 	}
     }
 
-  if (! host_integerp (size, 1))
+  if (! tree_fits_uhwi_p (size))
     return NULL_TREE;
 
   if (! integer_all_onesp (size))
     {
-      if (! host_integerp (len, 1))
+      if (! tree_fits_uhwi_p (len))
 	{
 	  /* If LEN is not constant, try MAXLEN too.
 	     For MAXLEN only allow optimizing into non-_ocs function
 	     if SIZE is >= MAXLEN, never convert to __ocs_fail ().  */
-	  if (maxlen == NULL_TREE || ! host_integerp (maxlen, 1))
+	  if (maxlen == NULL_TREE || ! tree_fits_uhwi_p (maxlen))
 	    {
 	      if (fcode == BUILT_IN_MEMPCPY_CHK && ignore)
 		{
@@ -12808,18 +12808,18 @@ fold_builtin_stxcpy_chk (location_t loc, tree fndecl, tree dest,
   if (fcode == BUILT_IN_STRCPY_CHK && operand_equal_p (src, dest, 0))
     return fold_convert_loc (loc, TREE_TYPE (TREE_TYPE (fndecl)), dest);
 
-  if (! host_integerp (size, 1))
+  if (! tree_fits_uhwi_p (size))
     return NULL_TREE;
 
   if (! integer_all_onesp (size))
     {
       len = c_strlen (src, 1);
-      if (! len || ! host_integerp (len, 1))
+      if (! len || ! tree_fits_uhwi_p (len))
 	{
 	  /* If LEN is not constant, try MAXLEN too.
 	     For MAXLEN only allow optimizing into non-_ocs function
 	     if SIZE is >= MAXLEN, never convert to __ocs_fail ().  */
-	  if (maxlen == NULL_TREE || ! host_integerp (maxlen, 1))
+	  if (maxlen == NULL_TREE || ! tree_fits_uhwi_p (maxlen))
 	    {
 	      if (fcode == BUILT_IN_STPCPY_CHK)
 		{
@@ -12895,17 +12895,17 @@ fold_builtin_stxncpy_chk (location_t loc, tree dest, tree src,
          return build_call_expr_loc (loc, fn, 4, dest, src, len, size);
     }
 
-  if (! host_integerp (size, 1))
+  if (! tree_fits_uhwi_p (size))
     return NULL_TREE;
 
   if (! integer_all_onesp (size))
     {
-      if (! host_integerp (len, 1))
+      if (! tree_fits_uhwi_p (len))
 	{
 	  /* If LEN is not constant, try MAXLEN too.
 	     For MAXLEN only allow optimizing into non-_ocs function
 	     if SIZE is >= MAXLEN, never convert to __ocs_fail ().  */
-	  if (maxlen == NULL_TREE || ! host_integerp (maxlen, 1))
+	  if (maxlen == NULL_TREE || ! tree_fits_uhwi_p (maxlen))
 	    return NULL_TREE;
 	}
       else
@@ -12944,7 +12944,7 @@ fold_builtin_strcat_chk (location_t loc, tree fndecl, tree dest,
   if (p && *p == '\0')
     return omit_one_operand_loc (loc, TREE_TYPE (TREE_TYPE (fndecl)), dest, src);
 
-  if (! host_integerp (size, 1) || ! integer_all_onesp (size))
+  if (! tree_fits_uhwi_p (size) || ! integer_all_onesp (size))
     return NULL_TREE;
 
   /* If __builtin_strcat_chk is used, assume strcat is available.  */
@@ -12978,15 +12978,15 @@ fold_builtin_strncat_chk (location_t loc, tree fndecl,
   else if (integer_zerop (len))
     return omit_one_operand_loc (loc, TREE_TYPE (TREE_TYPE (fndecl)), dest, src);
 
-  if (! host_integerp (size, 1))
+  if (! tree_fits_uhwi_p (size))
     return NULL_TREE;
 
   if (! integer_all_onesp (size))
     {
       tree src_len = c_strlen (src, 1);
       if (src_len
-	  && host_integerp (src_len, 1)
-	  && host_integerp (len, 1)
+	  && tree_fits_uhwi_p (src_len)
+	  && tree_fits_uhwi_p (len)
 	  && ! tree_int_cst_lt (len, src_len))
 	{
 	  /* If LEN >= strlen (SRC), optimize into __strcat_chk.  */
@@ -13035,7 +13035,7 @@ fold_builtin_sprintf_chk_1 (location_t loc, int nargs, tree *args,
   if (!validate_arg (fmt, POINTER_TYPE))
     return NULL_TREE;
 
-  if (! host_integerp (size, 1))
+  if (! tree_fits_uhwi_p (size))
     return NULL_TREE;
 
   len = NULL_TREE;
@@ -13066,7 +13066,7 @@ fold_builtin_sprintf_chk_1 (location_t loc, int nargs, tree *args,
 	      if (validate_arg (arg, POINTER_TYPE))
 		{
 		  len = c_strlen (arg, 1);
-		  if (! len || ! host_integerp (len, 1))
+		  if (! len || ! tree_fits_uhwi_p (len))
 		    len = NULL_TREE;
 		}
 	    }
@@ -13143,17 +13143,17 @@ fold_builtin_snprintf_chk_1 (location_t loc, int nargs, tree *args,
   if (!validate_arg (fmt, POINTER_TYPE))
     return NULL_TREE;
 
-  if (! host_integerp (size, 1))
+  if (! tree_fits_uhwi_p (size))
     return NULL_TREE;
 
   if (! integer_all_onesp (size))
     {
-      if (! host_integerp (len, 1))
+      if (! tree_fits_uhwi_p (len))
 	{
 	  /* If LEN is not constant, try MAXLEN too.
 	     For MAXLEN only allow optimizing into non-_ocs function
 	     if SIZE is >= MAXLEN, never convert to __ocs_fail ().  */
-	  if (maxlen == NULL_TREE || ! host_integerp (maxlen, 1))
+	  if (maxlen == NULL_TREE || ! tree_fits_uhwi_p (maxlen))
 	    return NULL_TREE;
 	}
       else
diff --git a/gcc/c-family/ChangeLog b/gcc/c-family/ChangeLog
index fde985328cd31dffc799b77f8843777bfa1cade0..2f7d02f52b9a0d6a26080dbf47f284f62ec8d41c 100644
--- a/gcc/c-family/ChangeLog
+++ b/gcc/c-family/ChangeLog
@@ -1,3 +1,8 @@
+2013-11-18  Richard Sandiford  <rdsandiford@googlemail.com>
+
+	* c-ada-spec.c, c-common.c, c-pretty-print.c: Replace
+	host_integerp (..., 1) with tree_fits_uhwi_p throughout.
+
 2013-11-18  Richard Sandiford  <rdsandiford@googlemail.com>
 
 	* c-ada-spec.c, c-common.c, c-format.c, c-pretty-print.c: Replace
diff --git a/gcc/c-family/c-ada-spec.c b/gcc/c-family/c-ada-spec.c
index 6a5826b0a761feed643e9e23f0d5e7f65972cd8a..731993337894319e73f256327ca13e6b67ff4e5c 100644
--- a/gcc/c-family/c-ada-spec.c
+++ b/gcc/c-family/c-ada-spec.c
@@ -2207,7 +2207,7 @@ dump_generic_ada_node (pretty_printer *buffer, tree node, tree type, int spc,
 	node = fold_convert (ssizetype, node);
       if (tree_fits_shwi_p (node))
 	pp_wide_integer (buffer, TREE_INT_CST_LOW (node));
-      else if (host_integerp (node, 1))
+      else if (tree_fits_uhwi_p (node))
 	pp_unsigned_wide_integer (buffer, TREE_INT_CST_LOW (node));
       else
 	{
diff --git a/gcc/c-family/c-common.c b/gcc/c-family/c-common.c
index d0fc1aafd6b514f24dbba311557db2bff2b895b6..3ffefec9a2acf896b9d56460ad5255285f534455 100644
--- a/gcc/c-family/c-common.c
+++ b/gcc/c-family/c-common.c
@@ -8477,7 +8477,7 @@ handle_vector_size_attribute (tree *node, tree name, tree args,
 
   size = TREE_VALUE (args);
 
-  if (!host_integerp (size, 1))
+  if (!tree_fits_uhwi_p (size))
     {
       warning (OPT_Wattributes, "%qE attribute ignored", name);
       return NULL_TREE;
@@ -8510,7 +8510,7 @@ handle_vector_size_attribute (tree *node, tree name, tree args,
       || (!SCALAR_FLOAT_MODE_P (orig_mode)
 	  && GET_MODE_CLASS (orig_mode) != MODE_INT
 	  && !ALL_SCALAR_FIXED_POINT_MODE_P (orig_mode))
-      || !host_integerp (TYPE_SIZE_UNIT (type), 1)
+      || !tree_fits_uhwi_p (TYPE_SIZE_UNIT (type))
       || TREE_CODE (type) == BOOLEAN_TYPE)
     {
       error ("invalid vector type for attribute %qE", name);
@@ -11702,7 +11702,7 @@ convert_vector_to_pointer_for_subscript (location_t loc,
       tree type1;
 
       if (TREE_CODE (index) == INTEGER_CST)
-        if (!host_integerp (index, 1)
+        if (!tree_fits_uhwi_p (index)
             || ((unsigned HOST_WIDE_INT) tree_low_cst (index, 1)
                >= TYPE_VECTOR_SUBPARTS (type)))
           warning_at (loc, OPT_Warray_bounds, "index value is out of bound");
diff --git a/gcc/c-family/c-pretty-print.c b/gcc/c-family/c-pretty-print.c
index fd4b8579959ed58aa7dd60e75b3ce36d516bad7b..5f538c559f901d189d972431e4e4f6657484f738 100644
--- a/gcc/c-family/c-pretty-print.c
+++ b/gcc/c-family/c-pretty-print.c
@@ -917,7 +917,7 @@ pp_c_integer_constant (c_pretty_printer *pp, tree i)
 
   if (tree_fits_shwi_p (i))
     pp_wide_integer (pp, TREE_INT_CST_LOW (i));
-  else if (host_integerp (i, 1))
+  else if (tree_fits_uhwi_p (i))
     pp_unsigned_wide_integer (pp, TREE_INT_CST_LOW (i));
   else
     {
diff --git a/gcc/cfgexpand.c b/gcc/cfgexpand.c
index 124a4b89dfba4b56dc38060d51f046aab03f499b..ab4c444fd6efc80a8d2eedd2aff31afd6c38dd56 100644
--- a/gcc/cfgexpand.c
+++ b/gcc/cfgexpand.c
@@ -1358,7 +1358,7 @@ stack_protect_classify_type (tree type)
 	  unsigned HOST_WIDE_INT len;
 
 	  if (!TYPE_SIZE_UNIT (type)
-	      || !host_integerp (TYPE_SIZE_UNIT (type), 1))
+	      || !tree_fits_uhwi_p (TYPE_SIZE_UNIT (type)))
 	    len = max;
 	  else
 	    len = tree_low_cst (TYPE_SIZE_UNIT (type), 1);
diff --git a/gcc/config/aarch64/aarch64.c b/gcc/config/aarch64/aarch64.c
index cfda95e04916dddfce966fcd93b8304e01bc00fe..290ed6c851a292a89b23624e9b29a1eb3686ac90 100644
--- a/gcc/config/aarch64/aarch64.c
+++ b/gcc/config/aarch64/aarch64.c
@@ -6030,9 +6030,9 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 	if (count == -1
 	    || !index
 	    || !TYPE_MAX_VALUE (index)
-	    || !host_integerp (TYPE_MAX_VALUE (index), 1)
+	    || !tree_fits_uhwi_p (TYPE_MAX_VALUE (index))
 	    || !TYPE_MIN_VALUE (index)
-	    || !host_integerp (TYPE_MIN_VALUE (index), 1)
+	    || !tree_fits_uhwi_p (TYPE_MIN_VALUE (index))
 	    || count < 0)
 	  return -1;
 
@@ -6040,7 +6040,7 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 		      - tree_low_cst (TYPE_MIN_VALUE (index), 1));
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
@@ -6070,7 +6070,7 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 	  }
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
@@ -6102,7 +6102,7 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 	  }
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
diff --git a/gcc/config/alpha/alpha.c b/gcc/config/alpha/alpha.c
index dbfcd01874cb0b6e7effc47b916415e037a37d6d..855be32d1035f22b79a24c6ff611a87db25231d4 100644
--- a/gcc/config/alpha/alpha.c
+++ b/gcc/config/alpha/alpha.c
@@ -5860,7 +5860,7 @@ va_list_skip_additions (tree lhs)
       if (!CONVERT_EXPR_CODE_P (code)
 	  && ((code != PLUS_EXPR && code != POINTER_PLUS_EXPR)
 	      || TREE_CODE (gimple_assign_rhs2 (stmt)) != INTEGER_CST
-	      || !host_integerp (gimple_assign_rhs2 (stmt), 1)))
+	      || !tree_fits_uhwi_p (gimple_assign_rhs2 (stmt))))
 	return stmt;
 
       lhs = gimple_assign_rhs1 (stmt);
diff --git a/gcc/config/arm/arm.c b/gcc/config/arm/arm.c
index 948070d6274a1494fcb994b7b5f6332ae9408dfe..4d8a39f2e0760ce9021058dd260b78806c11cbf4 100644
--- a/gcc/config/arm/arm.c
+++ b/gcc/config/arm/arm.c
@@ -4728,9 +4728,9 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 	if (count == -1
 	    || !index
 	    || !TYPE_MAX_VALUE (index)
-	    || !host_integerp (TYPE_MAX_VALUE (index), 1)
+	    || !tree_fits_uhwi_p (TYPE_MAX_VALUE (index))
 	    || !TYPE_MIN_VALUE (index)
-	    || !host_integerp (TYPE_MIN_VALUE (index), 1)
+	    || !tree_fits_uhwi_p (TYPE_MIN_VALUE (index))
 	    || count < 0)
 	  return -1;
 
@@ -4738,7 +4738,7 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 		      - tree_low_cst (TYPE_MIN_VALUE (index), 1));
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
@@ -4768,7 +4768,7 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 	  }
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
@@ -4800,7 +4800,7 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 	  }
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
diff --git a/gcc/config/epiphany/epiphany.c b/gcc/config/epiphany/epiphany.c
index fd4c01c49a4f970c83d12d8113840316184be19e..ea692fa9eea977a14ed06add6d2a2000f009135e 100644
--- a/gcc/config/epiphany/epiphany.c
+++ b/gcc/config/epiphany/epiphany.c
@@ -2758,7 +2758,7 @@ epiphany_special_round_type_align (tree type, unsigned computed,
 	continue;
       offset = bit_position (field);
       size = DECL_SIZE (field);
-      if (!host_integerp (offset, 1) || !host_integerp (size, 1)
+      if (!tree_fits_uhwi_p (offset) || !tree_fits_uhwi_p (size)
 	  || TREE_INT_CST_LOW (offset) >= try_align
 	  || TREE_INT_CST_LOW (size) >= try_align)
 	return try_align;
@@ -2785,7 +2785,7 @@ epiphany_adjust_field_align (tree field, unsigned computed)
     {
       tree elmsz = TYPE_SIZE (TREE_TYPE (TREE_TYPE (field)));
 
-      if (!host_integerp (elmsz, 1) || tree_low_cst (elmsz, 1) >= 32)
+      if (!tree_fits_uhwi_p (elmsz) || tree_low_cst (elmsz, 1) >= 32)
 	return 64;
     }
   return computed;
diff --git a/gcc/config/i386/i386.c b/gcc/config/i386/i386.c
index bb6d15a2b2acf9231defc58b8623331c9340274b..96cf77025fa0be67213a105bf3c89fb5fc27f9ea 100644
--- a/gcc/config/i386/i386.c
+++ b/gcc/config/i386/i386.c
@@ -32657,7 +32657,7 @@ get_element_number (tree vec_type, tree arg)
 {
   unsigned HOST_WIDE_INT elt, max = TYPE_VECTOR_SUBPARTS (vec_type) - 1;
 
-  if (!host_integerp (arg, 1)
+  if (!tree_fits_uhwi_p (arg)
       || (elt = tree_low_cst (arg, 1), elt > max))
     {
       error ("selector must be an integer constant in the range 0..%wi", max);
diff --git a/gcc/config/iq2000/iq2000.c b/gcc/config/iq2000/iq2000.c
index 71987c6112343a53023aa7f5e91da3173fecc5b8..759229a1b2be6ea0e6953290ab6a035397120568 100644
--- a/gcc/config/iq2000/iq2000.c
+++ b/gcc/config/iq2000/iq2000.c
@@ -1279,7 +1279,7 @@ iq2000_function_arg (cumulative_args_t cum_v, enum machine_mode mode,
 
       if (! type || TREE_CODE (type) != RECORD_TYPE
 	  || ! named  || ! TYPE_SIZE_UNIT (type)
-	  || ! host_integerp (TYPE_SIZE_UNIT (type), 1))
+	  || ! tree_fits_uhwi_p (TYPE_SIZE_UNIT (type)))
 	ret = gen_rtx_REG (mode, regbase + *arg_words + bias);
       else
 	{
diff --git a/gcc/config/m32c/m32c-pragma.c b/gcc/config/m32c/m32c-pragma.c
index 6b0d05a8aafcd0bd0a16ad275d60404cc33a4cbc..aca78318600d3394a6af3bc4559b1e32409eed40 100644
--- a/gcc/config/m32c/m32c-pragma.c
+++ b/gcc/config/m32c/m32c-pragma.c
@@ -46,7 +46,7 @@ m32c_pragma_memregs (cpp_reader * reader ATTRIBUTE_UNUSED)
   type = pragma_lex (&val);
   if (type == CPP_NUMBER)
     {
-      if (host_integerp (val, 1))
+      if (tree_fits_uhwi_p (val))
 	{
 	  i = tree_low_cst (val, 1);
 
diff --git a/gcc/config/mep/mep-pragma.c b/gcc/config/mep/mep-pragma.c
index 8a9c577f5a904a524e14425166381a754aa38421..1a4cfee8909bf965ecb728936792cc329fe91135 100644
--- a/gcc/config/mep/mep-pragma.c
+++ b/gcc/config/mep/mep-pragma.c
@@ -232,7 +232,7 @@ mep_pragma_coprocessor_width (void)
   switch (type)
     {
     case CPP_NUMBER:
-      if (! host_integerp (val, 1))
+      if (! tree_fits_uhwi_p (val))
 	break;
       i = tree_low_cst (val, 1);
       /* This pragma no longer has any effect.  */
diff --git a/gcc/config/mips/mips.c b/gcc/config/mips/mips.c
index 055e36afa244af8fcf7e1392a110b245b43fbc73..a99d76c23c2e27834f33e0178cb36350ca94ca48 100644
--- a/gcc/config/mips/mips.c
+++ b/gcc/config/mips/mips.c
@@ -5149,7 +5149,7 @@ mips_function_arg (cumulative_args_t cum_v, enum machine_mode mode,
       && type != 0
       && TREE_CODE (type) == RECORD_TYPE
       && TYPE_SIZE_UNIT (type)
-      && host_integerp (TYPE_SIZE_UNIT (type), 1))
+      && tree_fits_uhwi_p (TYPE_SIZE_UNIT (type)))
     {
       tree field;
 
diff --git a/gcc/config/rs6000/rs6000.c b/gcc/config/rs6000/rs6000.c
index fa9d56929a620226c3699089fb4357e36d40c98b..8188ba370fcaec9a84be0aeac91182482d21ffb7 100644
--- a/gcc/config/rs6000/rs6000.c
+++ b/gcc/config/rs6000/rs6000.c
@@ -6125,7 +6125,7 @@ offsettable_ok_by_alignment (rtx op, HOST_WIDE_INT offset,
 	  if (!DECL_SIZE_UNIT (decl))
 	    return false;
 
-	  if (!host_integerp (DECL_SIZE_UNIT (decl), 1))
+	  if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (decl)))
 	    return false;
 
 	  dsize = tree_low_cst (DECL_SIZE_UNIT (decl), 1);
@@ -6151,7 +6151,7 @@ offsettable_ok_by_alignment (rtx op, HOST_WIDE_INT offset,
 	  if (TREE_CODE (decl) == STRING_CST)
 	    dsize = TREE_STRING_LENGTH (decl);
 	  else if (TYPE_SIZE_UNIT (type)
-		   && host_integerp (TYPE_SIZE_UNIT (type), 1))
+		   && tree_fits_uhwi_p (TYPE_SIZE_UNIT (type)))
 	    dsize = tree_low_cst (TYPE_SIZE_UNIT (type), 1);
 	  else
 	    return false;
@@ -8553,9 +8553,9 @@ rs6000_aggregate_candidate (const_tree type, enum machine_mode *modep)
 	if (count == -1
 	    || !index
 	    || !TYPE_MAX_VALUE (index)
-	    || !host_integerp (TYPE_MAX_VALUE (index), 1)
+	    || !tree_fits_uhwi_p (TYPE_MAX_VALUE (index))
 	    || !TYPE_MIN_VALUE (index)
-	    || !host_integerp (TYPE_MIN_VALUE (index), 1)
+	    || !tree_fits_uhwi_p (TYPE_MIN_VALUE (index))
 	    || count < 0)
 	  return -1;
 
@@ -8563,7 +8563,7 @@ rs6000_aggregate_candidate (const_tree type, enum machine_mode *modep)
 		      - tree_low_cst (TYPE_MIN_VALUE (index), 1));
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
@@ -8593,7 +8593,7 @@ rs6000_aggregate_candidate (const_tree type, enum machine_mode *modep)
 	  }
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
@@ -8625,7 +8625,7 @@ rs6000_aggregate_candidate (const_tree type, enum machine_mode *modep)
 	  }
 
 	/* There must be no padding.  */
-	if (!host_integerp (TYPE_SIZE (type), 1)
+	if (!tree_fits_uhwi_p (TYPE_SIZE (type))
 	    || (tree_low_cst (TYPE_SIZE (type), 1)
 		!= count * GET_MODE_BITSIZE (*modep)))
 	  return -1;
@@ -9159,7 +9159,7 @@ rs6000_darwin64_record_arg_advance_recurse (CUMULATIVE_ARGS *cum,
 	mode = TYPE_MODE (ftype);
 
 	if (DECL_SIZE (f) != 0
-	    && host_integerp (bit_position (f), 1))
+	    && tree_fits_uhwi_p (bit_position (f)))
 	  bitpos += int_bit_position (f);
 
 	/* ??? FIXME: else assume zero offset.  */
@@ -9641,7 +9641,7 @@ rs6000_darwin64_record_arg_recurse (CUMULATIVE_ARGS *cum, const_tree type,
 	mode = TYPE_MODE (ftype);
 
 	if (DECL_SIZE (f) != 0
-	    && host_integerp (bit_position (f), 1))
+	    && tree_fits_uhwi_p (bit_position (f)))
 	  bitpos += int_bit_position (f);
 
 	/* ??? FIXME: else assume zero offset.  */
@@ -12386,7 +12386,7 @@ get_element_number (tree vec_type, tree arg)
 {
   unsigned HOST_WIDE_INT elt, max = TYPE_VECTOR_SUBPARTS (vec_type) - 1;
 
-  if (!host_integerp (arg, 1)
+  if (!tree_fits_uhwi_p (arg)
       || (elt = tree_low_cst (arg, 1), elt > max))
     {
       error ("selector must be an integer constant in the range 0..%wi", max);
diff --git a/gcc/config/sparc/sparc.c b/gcc/config/sparc/sparc.c
index e72ee3f6b671c30799cc1c8e6b470e4c11b754f5..1d6aa942ef6854e60bf91056b3a762933c3d5a73 100644
--- a/gcc/config/sparc/sparc.c
+++ b/gcc/config/sparc/sparc.c
@@ -6332,7 +6332,7 @@ function_arg_record_value_1 (const_tree type, HOST_WIDE_INT startbitpos,
 	      if (integer_zerop (DECL_SIZE (field)))
 		continue;
 
-	      if (host_integerp (bit_position (field), 1))
+	      if (tree_fits_uhwi_p (bit_position (field)))
 		bitpos += int_bit_position (field);
 	    }
 
@@ -6480,7 +6480,7 @@ function_arg_record_value_2 (const_tree type, HOST_WIDE_INT startbitpos,
 	      if (integer_zerop (DECL_SIZE (field)))
 		continue;
 
-	      if (host_integerp (bit_position (field), 1))
+	      if (tree_fits_uhwi_p (bit_position (field)))
 		bitpos += int_bit_position (field);
 	    }
 
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index a131d4b258b56d475c127f3e36c392b23145a173..e7a2014a9f9ab0bb3e4fe2ca95415a9f251badb8 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,8 @@
+2013-11-18  Richard Sandiford  <rdsandiford@googlemail.com>
+
+	* decl.c: Replace host_integerp (..., 1) with tree_fits_uhwi_p
+	throughout.
+
 2013-11-18  Richard Sandiford  <rdsandiford@googlemail.com>
 
 	* error.c, init.c, parser.c, semantics.c: Replace
diff --git a/gcc/cp/decl.c b/gcc/cp/decl.c
index 34d73be3e78cad1cc0c4374b2c56241bfdafbb44..770167cacbf98703d3ce0b891e32d2a4658c7577 100644
--- a/gcc/cp/decl.c
+++ b/gcc/cp/decl.c
@@ -5093,7 +5093,7 @@ reshape_init_array_1 (tree elt_type, tree max_index, reshape_iter *d,
       if (integer_all_onesp (max_index))
 	return new_init;
 
-      if (host_integerp (max_index, 1))
+      if (tree_fits_uhwi_p (max_index))
 	max_index_cst = tree_low_cst (max_index, 1);
       /* sizetype is sign extended, not zero extended.  */
       else
diff --git a/gcc/dbxout.c b/gcc/dbxout.c
index c486a3d00d5384f5340f24262eceaba24682f1a1..ddeb87bf5061acac725d970621ab5537627fbd71 100644
--- a/gcc/dbxout.c
+++ b/gcc/dbxout.c
@@ -1521,7 +1521,7 @@ dbxout_type_fields (tree type)
 	  || (TREE_CODE (tem) == FIELD_DECL
 	      && (! tree_fits_shwi_p (bit_position (tem))
 		  || ! DECL_SIZE (tem)
-		  || ! host_integerp (DECL_SIZE (tem), 1))))
+		  || ! tree_fits_uhwi_p (DECL_SIZE (tem)))))
 	continue;
 
       else if (TREE_CODE (tem) != CONST_DECL)
@@ -1864,7 +1864,7 @@ dbxout_type (tree type, int full)
 	 Sun dbx crashes if we do.  */
       if (! full || !COMPLETE_TYPE_P (type)
 	  /* No way in DBX fmt to describe a variable size.  */
-	  || ! host_integerp (TYPE_SIZE (type), 1))
+	  || ! tree_fits_uhwi_p (TYPE_SIZE (type)))
 	return;
       break;
     case TYPE_DEFINED:
@@ -1889,7 +1889,7 @@ dbxout_type (tree type, int full)
 	 && !full)
 	|| !COMPLETE_TYPE_P (type)
 	/* No way in DBX fmt to describe a variable size.  */
-	|| ! host_integerp (TYPE_SIZE (type), 1))
+	|| ! tree_fits_uhwi_p (TYPE_SIZE (type)))
       {
 	typevec[TYPE_SYMTAB_ADDRESS (type)].status = TYPE_XREF;
 	return;
@@ -2147,7 +2147,7 @@ dbxout_type (tree type, int full)
 	     && !full)
 	    || !COMPLETE_TYPE_P (type)
 	    /* No way in DBX fmt to describe a variable size.  */
-	    || ! host_integerp (TYPE_SIZE (type), 1))
+	    || ! tree_fits_uhwi_p (TYPE_SIZE (type)))
 	  {
 	    /* If the type is just a cross reference, output one
 	       and mark the type as partially described.
@@ -2796,7 +2796,7 @@ dbxout_symbol (tree decl, int local ATTRIBUTE_UNUSED)
 		/* Do not generate a tag for records of variable size,
 		   since this type can not be properly described in the
 		   DBX format, and it confuses some tools such as objdump.  */
-		&& host_integerp (TYPE_SIZE (type), 1))
+		&& tree_fits_uhwi_p (TYPE_SIZE (type)))
 	      {
 		tree name = TYPE_NAME (type);
 		if (TREE_CODE (name) == TYPE_DECL)
diff --git a/gcc/dwarf2out.c b/gcc/dwarf2out.c
index bcfaddadae330f49c56b7fe925e8c25641814fcf..73b44ada3efd09024d7ac1b87923e985331692bf 100644
--- a/gcc/dwarf2out.c
+++ b/gcc/dwarf2out.c
@@ -10261,7 +10261,7 @@ simple_type_size_in_bits (const_tree type)
     return BITS_PER_WORD;
   else if (TYPE_SIZE (type) == NULL_TREE)
     return 0;
-  else if (host_integerp (TYPE_SIZE (type), 1))
+  else if (tree_fits_uhwi_p (TYPE_SIZE (type)))
     return tree_low_cst (TYPE_SIZE (type), 1);
   else
     return TYPE_ALIGN (type);
@@ -13540,7 +13540,7 @@ dw_sra_loc_expr (tree decl, rtx loc)
   enum var_init_status initialized;
 
   if (DECL_SIZE (decl) == NULL
-      || !host_integerp (DECL_SIZE (decl), 1))
+      || !tree_fits_uhwi_p (DECL_SIZE (decl)))
     return NULL;
 
   decl_size = tree_low_cst (DECL_SIZE (decl), 1);
@@ -16395,7 +16395,7 @@ add_bit_offset_attribute (dw_die_ref die, tree decl)
      encounter such things, just return without generating any attribute
      whatsoever.  Likewise for variable or too large size.  */
   if (! tree_fits_shwi_p (bit_position (decl))
-      || ! host_integerp (DECL_SIZE (decl), 1))
+      || ! tree_fits_uhwi_p (DECL_SIZE (decl)))
     return;
 
   bitpos_int = int_bit_position (decl);
@@ -16435,7 +16435,7 @@ add_bit_size_attribute (dw_die_ref die, tree decl)
   gcc_assert (TREE_CODE (decl) == FIELD_DECL
 	      && DECL_BIT_FIELD_TYPE (decl));
 
-  if (host_integerp (DECL_SIZE (decl), 1))
+  if (tree_fits_uhwi_p (DECL_SIZE (decl)))
     add_AT_unsigned (die, DW_AT_bit_size, tree_low_cst (DECL_SIZE (decl), 1));
 }
 
@@ -17072,7 +17072,7 @@ descr_info_loc (tree val, tree base_decl)
       return loc;
     case POINTER_PLUS_EXPR:
     case PLUS_EXPR:
-      if (host_integerp (TREE_OPERAND (val, 1), 1)
+      if (tree_fits_uhwi_p (TREE_OPERAND (val, 1))
 	  && (unsigned HOST_WIDE_INT) tree_low_cst (TREE_OPERAND (val, 1), 1)
 	     < 16384)
 	{
diff --git a/gcc/emit-rtl.c b/gcc/emit-rtl.c
index b0fc846226842fd9f33c787b104379f992a60ecb..385f44a45b990089d04abf2121b071cb9fe27c0f 100644
--- a/gcc/emit-rtl.c
+++ b/gcc/emit-rtl.c
@@ -1541,8 +1541,8 @@ get_mem_align_offset (rtx mem, unsigned int align)
 	  tree bit_offset = DECL_FIELD_BIT_OFFSET (field);
 
 	  if (!byte_offset
-	      || !host_integerp (byte_offset, 1)
-	      || !host_integerp (bit_offset, 1))
+	      || !tree_fits_uhwi_p (byte_offset)
+	      || !tree_fits_uhwi_p (bit_offset))
 	    return -1;
 
 	  offset += tree_low_cst (byte_offset, 1);
@@ -1770,7 +1770,7 @@ set_mem_attributes_minus_bitpos (rtx ref, tree t, int objectp,
 	    {
 	      attrs.expr = t2;
 	      attrs.offset_known_p = false;
-	      if (host_integerp (off_tree, 1))
+	      if (tree_fits_uhwi_p (off_tree))
 		{
 		  attrs.offset_known_p = true;
 		  attrs.offset = tree_low_cst (off_tree, 1);
@@ -1800,7 +1800,7 @@ set_mem_attributes_minus_bitpos (rtx ref, tree t, int objectp,
       attrs.align = MAX (attrs.align, obj_align);
     }
 
-  if (host_integerp (new_size, 1))
+  if (tree_fits_uhwi_p (new_size))
     {
       attrs.size_known_p = true;
       attrs.size = tree_low_cst (new_size, 1);
@@ -2273,7 +2273,7 @@ widen_memory_access (rtx memref, enum machine_mode mode, HOST_WIDE_INT offset)
 	      && attrs.offset >= 0)
 	    break;
 
-	  if (! host_integerp (offset, 1))
+	  if (! tree_fits_uhwi_p (offset))
 	    {
 	      attrs.expr = NULL_TREE;
 	      break;
diff --git a/gcc/expr.c b/gcc/expr.c
index 5fbba60706a75fc06223b19d249d621ff7de69dd..da5c05ea051d7336c20447d464a7686258d1f228 100644
--- a/gcc/expr.c
+++ b/gcc/expr.c
@@ -4628,8 +4628,8 @@ get_bit_range (unsigned HOST_WIDE_INT *bitstart,
      relative to the representative.  DECL_FIELD_OFFSET of field and
      repr are the same by construction if they are not constants,
      see finish_bitfield_layout.  */
-  if (host_integerp (DECL_FIELD_OFFSET (field), 1)
-      && host_integerp (DECL_FIELD_OFFSET (repr), 1))
+  if (tree_fits_uhwi_p (DECL_FIELD_OFFSET (field))
+      && tree_fits_uhwi_p (DECL_FIELD_OFFSET (repr)))
     bitoffset = (tree_low_cst (DECL_FIELD_OFFSET (field), 1)
 		 - tree_low_cst (DECL_FIELD_OFFSET (repr), 1)) * BITS_PER_UNIT;
   else
@@ -5470,7 +5470,7 @@ count_type_elements (const_tree type, bool for_ctor_p)
 	tree nelts;
 
 	nelts = array_type_nelts (type);
-	if (nelts && host_integerp (nelts, 1))
+	if (nelts && tree_fits_uhwi_p (nelts))
 	  {
 	    unsigned HOST_WIDE_INT n;
 
@@ -5589,7 +5589,7 @@ categorize_ctor_elements_1 (const_tree ctor, HOST_WIDE_INT *p_nz_elts,
 	  tree lo_index = TREE_OPERAND (purpose, 0);
 	  tree hi_index = TREE_OPERAND (purpose, 1);
 
-	  if (host_integerp (lo_index, 1) && host_integerp (hi_index, 1))
+	  if (tree_fits_uhwi_p (lo_index) && tree_fits_uhwi_p (hi_index))
 	    mult = (tree_low_cst (hi_index, 1)
 		    - tree_low_cst (lo_index, 1) + 1);
 	}
@@ -5908,7 +5908,7 @@ store_constructor (tree exp, rtx target, int cleared, HOST_WIDE_INT size)
 	    if (cleared && initializer_zerop (value))
 	      continue;
 
-	    if (host_integerp (DECL_SIZE (field), 1))
+	    if (tree_fits_uhwi_p (DECL_SIZE (field)))
 	      bitsize = tree_low_cst (DECL_SIZE (field), 1);
 	    else
 	      bitsize = -1;
@@ -6047,8 +6047,8 @@ store_constructor (tree exp, rtx target, int cleared, HOST_WIDE_INT size)
 		    tree lo_index = TREE_OPERAND (index, 0);
 		    tree hi_index = TREE_OPERAND (index, 1);
 
-		    if (! host_integerp (lo_index, 1)
-			|| ! host_integerp (hi_index, 1))
+		    if (! tree_fits_uhwi_p (lo_index)
+			|| ! tree_fits_uhwi_p (hi_index))
 		      {
 			need_to_clear = 1;
 			break;
@@ -6102,7 +6102,7 @@ store_constructor (tree exp, rtx target, int cleared, HOST_WIDE_INT size)
 
 	    mode = TYPE_MODE (elttype);
 	    if (mode == BLKmode)
-	      bitsize = (host_integerp (TYPE_SIZE (elttype), 1)
+	      bitsize = (tree_fits_uhwi_p (TYPE_SIZE (elttype))
 			 ? tree_low_cst (TYPE_SIZE (elttype), 1)
 			 : -1);
 	    else
@@ -6125,7 +6125,7 @@ store_constructor (tree exp, rtx target, int cleared, HOST_WIDE_INT size)
 			count = hi - lo + 1,
 			(!MEM_P (target)
 			 || count <= 2
-			 || (host_integerp (TYPE_SIZE (elttype), 1)
+			 || (tree_fits_uhwi_p (TYPE_SIZE (elttype))
 			     && (tree_low_cst (TYPE_SIZE (elttype), 1) * count
 				 <= 40 * 8)))))
 		  {
@@ -6208,7 +6208,7 @@ store_constructor (tree exp, rtx target, int cleared, HOST_WIDE_INT size)
 		  }
 	      }
 	    else if ((index != 0 && ! tree_fits_shwi_p (index))
-		     || ! host_integerp (TYPE_SIZE (elttype), 1))
+		     || ! tree_fits_uhwi_p (TYPE_SIZE (elttype)))
 	      {
 		tree position;
 
@@ -6676,7 +6676,7 @@ get_inner_reference (tree exp, HOST_WIDE_INT *pbitsize,
 
   if (size_tree != 0)
     {
-      if (! host_integerp (size_tree, 1))
+      if (! tree_fits_uhwi_p (size_tree))
 	mode = BLKmode, *pbitsize = -1;
       else
 	*pbitsize = tree_low_cst (size_tree, 1);
@@ -7756,7 +7756,7 @@ expand_constructor (tree exp, rtx target, enum expand_modifier modifier,
        && ((mode == BLKmode
 	    && ! (target != 0 && safe_from_p (target, exp, 1)))
 		  || TREE_ADDRESSABLE (exp)
-		  || (host_integerp (TYPE_SIZE_UNIT (type), 1)
+		  || (tree_fits_uhwi_p (TYPE_SIZE_UNIT (type))
 		      && (! MOVE_BY_PIECES_P
 				     (tree_low_cst (TYPE_SIZE_UNIT (type), 1),
 				      TYPE_ALIGN (type)))
@@ -9633,7 +9633,7 @@ expand_expr_real_1 (tree exp, rtx target, enum machine_mode tmode,
 	    HOST_WIDE_INT offset = mem_ref_offset (exp).low;
 	    base = TREE_OPERAND (base, 0);
 	    if (offset == 0
-		&& host_integerp (TYPE_SIZE (type), 1)
+		&& tree_fits_uhwi_p (TYPE_SIZE (type))
 		&& (GET_MODE_BITSIZE (DECL_MODE (base))
 		    == TREE_INT_CST_LOW (TYPE_SIZE (type))))
 	      return expand_expr (build1 (VIEW_CONVERT_EXPR, type, base),
@@ -10558,7 +10558,7 @@ is_aligning_offset (const_tree offset, const_tree exp)
   /* We must now have a BIT_AND_EXPR with a constant that is one less than
      power of 2 and which is larger than BIGGEST_ALIGNMENT.  */
   if (TREE_CODE (offset) != BIT_AND_EXPR
-      || !host_integerp (TREE_OPERAND (offset, 1), 1)
+      || !tree_fits_uhwi_p (TREE_OPERAND (offset, 1))
       || compare_tree_int (TREE_OPERAND (offset, 1),
 			   BIGGEST_ALIGNMENT / BITS_PER_UNIT) <= 0
       || !exact_log2 (tree_low_cst (TREE_OPERAND (offset, 1), 1) + 1) < 0)
@@ -10696,7 +10696,7 @@ string_constant (tree arg, tree *ptr_offset)
 	 and inside of the bounds of the string literal.  */
       offset = fold_convert (sizetype, offset);
       if (compare_tree_int (DECL_SIZE_UNIT (array), length) > 0
-	  && (! host_integerp (offset, 1)
+	  && (! tree_fits_uhwi_p (offset)
 	      || compare_tree_int (offset, length) >= 0))
 	return 0;
 
diff --git a/gcc/fold-const.c b/gcc/fold-const.c
index d6187bf4997d9dfc1b76bec4a00bd03b3ac365d8..e51b2f99b9906bf2988cb371913d67faecd4b958 100644
--- a/gcc/fold-const.c
+++ b/gcc/fold-const.c
@@ -1430,7 +1430,7 @@ const_binop (enum tree_code code, tree arg1, tree arg2)
       if (code == VEC_LSHIFT_EXPR
 	  || code == VEC_RSHIFT_EXPR)
 	{
-	  if (!host_integerp (arg2, 1))
+	  if (!tree_fits_uhwi_p (arg2))
 	    return NULL_TREE;
 
 	  unsigned HOST_WIDE_INT shiftc = tree_low_cst (arg2, 1);
@@ -6643,7 +6643,7 @@ fold_single_bit_test (location_t loc, enum tree_code code,
 	 not overflow, adjust BITNUM and INNER.  */
       if (TREE_CODE (inner) == RSHIFT_EXPR
 	  && TREE_CODE (TREE_OPERAND (inner, 1)) == INTEGER_CST
-	  && host_integerp (TREE_OPERAND (inner, 1), 1)
+	  && tree_fits_uhwi_p (TREE_OPERAND (inner, 1))
 	  && bitnum < TYPE_PRECISION (type)
 	  && (TREE_INT_CST_LOW (TREE_OPERAND (inner, 1))
 	      < (unsigned) (TYPE_PRECISION (type) - bitnum)))
@@ -8098,7 +8098,7 @@ fold_unary_loc (location_t loc, enum tree_code code, tree type, tree op0)
 	    change = 1;
 	  else if (TYPE_PRECISION (TREE_TYPE (and1))
 		   <= HOST_BITS_PER_WIDE_INT
-		   && host_integerp (and1, 1))
+		   && tree_fits_uhwi_p (and1))
 	    {
 	      unsigned HOST_WIDE_INT cst;
 
@@ -11864,7 +11864,7 @@ fold_binary_loc (location_t loc,
 	 and for - instead of + (or unary - instead of +)
 	 and/or ^ instead of |.
 	 If B is constant and (B & M) == 0, fold into A & M.  */
-      if (host_integerp (arg1, 1))
+      if (tree_fits_uhwi_p (arg1))
 	{
 	  unsigned HOST_WIDE_INT cst1 = tree_low_cst (arg1, 1);
 	  if (~cst1 && (cst1 & (cst1 + 1)) == 0
@@ -11890,7 +11890,7 @@ fold_binary_loc (location_t loc,
 		  which = 1;
 		}
 
-	      if (!host_integerp (TYPE_MAX_VALUE (TREE_TYPE (arg0)), 1)
+	      if (!tree_fits_uhwi_p (TYPE_MAX_VALUE (TREE_TYPE (arg0)))
 		  || (tree_low_cst (TYPE_MAX_VALUE (TREE_TYPE (arg0)), 1)
 		      & cst1) != cst1)
 		which = -1;
@@ -12013,7 +12013,7 @@ fold_binary_loc (location_t loc,
       /* If arg0 is derived from the address of an object or function, we may
 	 be able to fold this expression using the object or function's
 	 alignment.  */
-      if (POINTER_TYPE_P (TREE_TYPE (arg0)) && host_integerp (arg1, 1))
+      if (POINTER_TYPE_P (TREE_TYPE (arg0)) && tree_fits_uhwi_p (arg1))
 	{
 	  unsigned HOST_WIDE_INT modulus, residue;
 	  unsigned HOST_WIDE_INT low = TREE_INT_CST_LOW (arg1);
@@ -12035,7 +12035,7 @@ fold_binary_loc (location_t loc,
 	   || TREE_CODE (arg0) == RSHIFT_EXPR)
 	  && TYPE_PRECISION (TREE_TYPE (arg0)) <= HOST_BITS_PER_WIDE_INT
 	  && TREE_CODE (arg1) == INTEGER_CST
-	  && host_integerp (TREE_OPERAND (arg0, 1), 1)
+	  && tree_fits_uhwi_p (TREE_OPERAND (arg0, 1))
 	  && tree_low_cst (TREE_OPERAND (arg0, 1), 1) > 0
 	  && (tree_low_cst (TREE_OPERAND (arg0, 1), 1)
 	      < TYPE_PRECISION (TREE_TYPE (arg0))))
@@ -12646,9 +12646,9 @@ fold_binary_loc (location_t loc,
       prec = element_precision (type);
 
       /* Turn (a OP c1) OP c2 into a OP (c1+c2).  */
-      if (TREE_CODE (op0) == code && host_integerp (arg1, true)
+      if (TREE_CODE (op0) == code && tree_fits_uhwi_p (arg1)
 	  && TREE_INT_CST_LOW (arg1) < prec
-	  && host_integerp (TREE_OPERAND (arg0, 1), true)
+	  && tree_fits_uhwi_p (TREE_OPERAND (arg0, 1))
 	  && TREE_INT_CST_LOW (TREE_OPERAND (arg0, 1)) < prec)
 	{
 	  unsigned int low = (TREE_INT_CST_LOW (TREE_OPERAND (arg0, 1))
@@ -14584,7 +14584,7 @@ fold_ternary_loc (location_t loc, enum tree_code code, tree type,
          fold (nearly) all BIT_FIELD_REFs.  */
       if (CONSTANT_CLASS_P (arg0)
 	  && can_native_interpret_type_p (type)
-	  && host_integerp (TYPE_SIZE_UNIT (TREE_TYPE (arg0)), 1)
+	  && tree_fits_uhwi_p (TYPE_SIZE_UNIT (TREE_TYPE (arg0)))
 	  /* This limitation should not be necessary, we just need to
 	     round this up to mode size.  */
 	  && tree_low_cst (op1, 1) % BITS_PER_UNIT == 0
diff --git a/gcc/function.c b/gcc/function.c
index eddffdbb9555de7ed119295e8812cb11845af0cb..3ae4b38dceffb72e3b53ca4ab098dd9591cb9ef6 100644
--- a/gcc/function.c
+++ b/gcc/function.c
@@ -3813,7 +3813,7 @@ locate_and_pad_parm (enum machine_mode passed_mode, tree type, int in_regs,
   {
     tree s2 = sizetree;
     if (where_pad != none
-	&& (!host_integerp (sizetree, 1)
+	&& (!tree_fits_uhwi_p (sizetree)
 	    || (tree_low_cst (sizetree, 1) * BITS_PER_UNIT) % round_boundary))
       s2 = round_up (s2, round_boundary / BITS_PER_UNIT);
     SUB_PARM_SIZE (locate->slot_offset, s2);
@@ -3858,7 +3858,7 @@ locate_and_pad_parm (enum machine_mode passed_mode, tree type, int in_regs,
     pad_below (&locate->offset, passed_mode, sizetree);
 
   if (where_pad != none
-      && (!host_integerp (sizetree, 1)
+      && (!tree_fits_uhwi_p (sizetree)
 	  || (tree_low_cst (sizetree, 1) * BITS_PER_UNIT) % round_boundary))
     sizetree = round_up (sizetree, round_boundary / BITS_PER_UNIT);
 
diff --git a/gcc/gimple-fold.c b/gcc/gimple-fold.c
index 88761bb42e1ca506859859640912c8189d1e99a9..c842dec5d1ee612c4c92c4ce7558304bcf7493a4 100644
--- a/gcc/gimple-fold.c
+++ b/gcc/gimple-fold.c
@@ -3057,7 +3057,7 @@ fold_const_aggregate_ref_1 (tree t, tree (*valueize) (tree))
 	  if ((low_bound = array_ref_low_bound (t),
 	       TREE_CODE (low_bound) == INTEGER_CST)
 	      && (unit_size = array_ref_element_size (t),
-		  host_integerp (unit_size, 1))
+		  tree_fits_uhwi_p (unit_size))
 	      && (doffset = (TREE_INT_CST (idx) - TREE_INT_CST (low_bound))
 			    .sext (TYPE_PRECISION (TREE_TYPE (idx))),
 		  doffset.fits_shwi ()))
@@ -3401,7 +3401,7 @@ gimple_fold_indirect_ref (tree t)
       if (TREE_CODE (addr) == ADDR_EXPR
 	  && TREE_CODE (TREE_TYPE (addrtype)) == VECTOR_TYPE
 	  && useless_type_conversion_p (type, TREE_TYPE (TREE_TYPE (addrtype)))
-	  && host_integerp (off, 1))
+	  && tree_fits_uhwi_p (off))
 	{
           unsigned HOST_WIDE_INT offset = tree_low_cst (off, 1);
           tree part_width = TYPE_SIZE (type);
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index bb50e250213f71031d4c0711198cdf2faca8ca4d..a65d3d1ced6a4a13bba3f6258f50985b572b7bbd 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -538,7 +538,7 @@ gimple_add_tmp_var (tree tmp)
   /* Later processing assumes that the object size is constant, which might
      not be true at this point.  Force the use of a constant upper bound in
      this case.  */
-  if (!host_integerp (DECL_SIZE_UNIT (tmp), 1))
+  if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (tmp)))
     force_constant_size (tmp);
 
   DECL_CONTEXT (tmp) = current_function_decl;
diff --git a/gcc/godump.c b/gcc/godump.c
index 8ae38e5f12404f5a1ec9f30b5c345e57a4986c10..9699559c15131b21d5aac4356c37cd3222cf90eb 100644
--- a/gcc/godump.c
+++ b/gcc/godump.c
@@ -984,7 +984,7 @@ go_output_typedef (struct godump_container *container, tree decl)
 	  if (tree_fits_shwi_p (TREE_VALUE (element)))
 	    snprintf (buf, sizeof buf, HOST_WIDE_INT_PRINT_DEC,
 		     tree_low_cst (TREE_VALUE (element), 0));
-	  else if (host_integerp (TREE_VALUE (element), 1))
+	  else if (tree_fits_uhwi_p (TREE_VALUE (element)))
 	    snprintf (buf, sizeof buf, HOST_WIDE_INT_PRINT_UNSIGNED,
 		     ((unsigned HOST_WIDE_INT)
 		      tree_low_cst (TREE_VALUE (element), 1)));
diff --git a/gcc/ipa-prop.c b/gcc/ipa-prop.c
index d673381b06291aec68ff05f830f87209e3dbb5d1..5857f1a3f0f90c850d9807907a9bf57580dd1f2b 100644
--- a/gcc/ipa-prop.c
+++ b/gcc/ipa-prop.c
@@ -1264,7 +1264,7 @@ type_like_member_ptr_p (tree type, tree *method_ptr, tree *delta)
   fld = TYPE_FIELDS (type);
   if (!fld || !POINTER_TYPE_P (TREE_TYPE (fld))
       || TREE_CODE (TREE_TYPE (TREE_TYPE (fld))) != METHOD_TYPE
-      || !host_integerp (DECL_FIELD_OFFSET (fld), 1))
+      || !tree_fits_uhwi_p (DECL_FIELD_OFFSET (fld)))
     return false;
 
   if (method_ptr)
@@ -1272,7 +1272,7 @@ type_like_member_ptr_p (tree type, tree *method_ptr, tree *delta)
 
   fld = DECL_CHAIN (fld);
   if (!fld || INTEGRAL_TYPE_P (fld)
-      || !host_integerp (DECL_FIELD_OFFSET (fld), 1))
+      || !tree_fits_uhwi_p (DECL_FIELD_OFFSET (fld)))
     return false;
   if (delta)
     *delta = fld;
@@ -1342,7 +1342,7 @@ determine_known_aggregate_parts (gimple call, tree arg,
       if (TREE_CODE (arg) == SSA_NAME)
 	{
 	  tree type_size;
-          if (!host_integerp (TYPE_SIZE (TREE_TYPE (TREE_TYPE (arg))), 1))
+          if (!tree_fits_uhwi_p (TYPE_SIZE (TREE_TYPE (TREE_TYPE (arg)))))
             return;
 	  check_ref = true;
 	  arg_base = arg;
diff --git a/gcc/omp-low.c b/gcc/omp-low.c
index f67494b47af99d289dcee800fff9c2cefe094a37..9bb5b0b13bdd36c67f43d97a4fc70923db3a9874 100644
--- a/gcc/omp-low.c
+++ b/gcc/omp-low.c
@@ -6769,7 +6769,7 @@ expand_omp_simd (struct omp_region *region, struct omp_for_data *fd)
       else
 	{
 	  safelen = OMP_CLAUSE_SAFELEN_EXPR (safelen);
-	  if (!host_integerp (safelen, 1)
+	  if (!tree_fits_uhwi_p (safelen)
 	      || (unsigned HOST_WIDE_INT) tree_low_cst (safelen, 1)
 		 > INT_MAX)
 	    loop->safelen = INT_MAX;
diff --git a/gcc/predict.c b/gcc/predict.c
index 25367825ce928395131cf463ba108b4fe88e8f8f..251faa872923774c134f384c461bbb8d3576e837 100644
--- a/gcc/predict.c
+++ b/gcc/predict.c
@@ -1557,7 +1557,7 @@ predict_loops (void)
 
 	  if (TREE_CODE (niter) == INTEGER_CST)
 	    {
-	      if (host_integerp (niter, 1)
+	      if (tree_fits_uhwi_p (niter)
 		  && max
 		  && compare_tree_int (niter, max - 1) == -1)
 		nitercst = tree_low_cst (niter, 1) + 1;
diff --git a/gcc/sdbout.c b/gcc/sdbout.c
index 66682a3c21ec9c25514458ebc96b2f78d187ce14..26ed6aa974e7f0dafb4c484cedb26379ee0d1119 100644
--- a/gcc/sdbout.c
+++ b/gcc/sdbout.c
@@ -994,7 +994,7 @@ sdbout_field_types (tree type)
     if (TREE_CODE (tail) == FIELD_DECL
 	&& DECL_NAME (tail)
 	&& DECL_SIZE (tail)
-	&& host_integerp (DECL_SIZE (tail), 1)
+	&& tree_fits_uhwi_p (DECL_SIZE (tail))
 	&& tree_fits_shwi_p (bit_position (tail)))
       {
 	if (POINTER_TYPE_P (TREE_TYPE (tail)))
@@ -1173,7 +1173,7 @@ sdbout_one_type (tree type)
 	    if (TREE_CODE (tem) == FIELD_DECL
 		&& DECL_NAME (tem)
 		&& DECL_SIZE (tem)
-		&& host_integerp (DECL_SIZE (tem), 1)
+		&& tree_fits_uhwi_p (DECL_SIZE (tem))
 		&& tree_fits_shwi_p (bit_position (tem)))
 	      {
 		const char *name;
diff --git a/gcc/stmt.c b/gcc/stmt.c
index 947dca9e8b89d42c6e2823aeabaeb288d7d4f3d7..ef4791b446d2393e23018271ab2369b5f2daf55b 100644
--- a/gcc/stmt.c
+++ b/gcc/stmt.c
@@ -854,7 +854,7 @@ expand_switch_as_decision_tree_p (tree range,
      who knows...  */
   max_ratio = optimize_insn_for_size_p () ? 3 : 10;
   if (count < case_values_threshold ()
-      || ! host_integerp (range, /*pos=*/1)
+      || ! tree_fits_uhwi_p (range)
       || compare_tree_int (range, max_ratio * count) > 0)
     return true;
 
diff --git a/gcc/stor-layout.c b/gcc/stor-layout.c
index d6a8687bddef5ba4872b8bcc906b836f0a027bde..44a5f2bf8e1db0151ea7234e20bd35ef4f4e91b7 100644
--- a/gcc/stor-layout.c
+++ b/gcc/stor-layout.c
@@ -332,7 +332,7 @@ mode_for_size_tree (const_tree size, enum mode_class mclass, int limit)
   unsigned HOST_WIDE_INT uhwi;
   unsigned int ui;
 
-  if (!host_integerp (size, 1))
+  if (!tree_fits_uhwi_p (size))
     return BLKmode;
   uhwi = tree_low_cst (size, 1);
   ui = uhwi;
@@ -483,7 +483,7 @@ mode_for_array (tree elem_type, tree size)
     return TYPE_MODE (elem_type);
 
   limit_p = true;
-  if (host_integerp (size, 1) && host_integerp (elem_size, 1))
+  if (tree_fits_uhwi_p (size) && tree_fits_uhwi_p (elem_size))
     {
       int_size = tree_low_cst (size, 1);
       int_elem_size = tree_low_cst (elem_size, 1);
@@ -1117,7 +1117,7 @@ place_field (record_layout_info rli, tree field)
 		   & - tree_low_cst (rli->bitpos, 1));
   else if (integer_zerop (rli->offset))
     known_align = 0;
-  else if (host_integerp (rli->offset, 1))
+  else if (tree_fits_uhwi_p (rli->offset))
     known_align = (BITS_PER_UNIT
 		   * (tree_low_cst (rli->offset, 1)
 		      & - tree_low_cst (rli->offset, 1)));
@@ -1194,9 +1194,9 @@ place_field (record_layout_info rli, tree field)
 	  || TYPE_ALIGN (type) <= BITS_PER_UNIT)
       && maximum_field_alignment == 0
       && ! integer_zerop (DECL_SIZE (field))
-      && host_integerp (DECL_SIZE (field), 1)
-      && host_integerp (rli->offset, 1)
-      && host_integerp (TYPE_SIZE (type), 1))
+      && tree_fits_uhwi_p (DECL_SIZE (field))
+      && tree_fits_uhwi_p (rli->offset)
+      && tree_fits_uhwi_p (TYPE_SIZE (type)))
     {
       unsigned int type_align = TYPE_ALIGN (type);
       tree dsize = DECL_SIZE (field);
@@ -1238,9 +1238,9 @@ place_field (record_layout_info rli, tree field)
       && DECL_BIT_FIELD_TYPE (field)
       && ! DECL_PACKED (field)
       && ! integer_zerop (DECL_SIZE (field))
-      && host_integerp (DECL_SIZE (field), 1)
-      && host_integerp (rli->offset, 1)
-      && host_integerp (TYPE_SIZE (type), 1))
+      && tree_fits_uhwi_p (DECL_SIZE (field))
+      && tree_fits_uhwi_p (rli->offset)
+      && tree_fits_uhwi_p (TYPE_SIZE (type)))
     {
       unsigned int type_align = TYPE_ALIGN (type);
       tree dsize = DECL_SIZE (field);
@@ -1383,8 +1383,8 @@ place_field (record_layout_info rli, tree field)
 	     until we see a bitfield (and come by here again) we just skip
 	     calculating it.  */
 	  if (DECL_SIZE (field) != NULL
-	      && host_integerp (TYPE_SIZE (TREE_TYPE (field)), 1)
-	      && host_integerp (DECL_SIZE (field), 1))
+	      && tree_fits_uhwi_p (TYPE_SIZE (TREE_TYPE (field)))
+	      && tree_fits_uhwi_p (DECL_SIZE (field)))
 	    {
 	      unsigned HOST_WIDE_INT bitsize
 		= tree_low_cst (DECL_SIZE (field), 1);
@@ -1425,7 +1425,7 @@ place_field (record_layout_info rli, tree field)
 		    & - tree_low_cst (DECL_FIELD_BIT_OFFSET (field), 1));
   else if (integer_zerop (DECL_FIELD_OFFSET (field)))
     actual_align = MAX (BIGGEST_ALIGNMENT, rli->record_align);
-  else if (host_integerp (DECL_FIELD_OFFSET (field), 1))
+  else if (tree_fits_uhwi_p (DECL_FIELD_OFFSET (field)))
     actual_align = (BITS_PER_UNIT
 		   * (tree_low_cst (DECL_FIELD_OFFSET (field), 1)
 		      & - tree_low_cst (DECL_FIELD_OFFSET (field), 1)));
@@ -1584,7 +1584,7 @@ compute_record_mode (tree type)
      line.  */
   SET_TYPE_MODE (type, BLKmode);
 
-  if (! host_integerp (TYPE_SIZE (type), 1))
+  if (! tree_fits_uhwi_p (TYPE_SIZE (type)))
     return;
 
   /* A record which has any BLKmode members must itself be
@@ -1600,9 +1600,9 @@ compute_record_mode (tree type)
 	      && ! TYPE_NO_FORCE_BLK (TREE_TYPE (field))
 	      && !(TYPE_SIZE (TREE_TYPE (field)) != 0
 		   && integer_zerop (TYPE_SIZE (TREE_TYPE (field)))))
-	  || ! host_integerp (bit_position (field), 1)
+	  || ! tree_fits_uhwi_p (bit_position (field))
 	  || DECL_SIZE (field) == 0
-	  || ! host_integerp (DECL_SIZE (field), 1))
+	  || ! tree_fits_uhwi_p (DECL_SIZE (field)))
 	return;
 
       /* If this field is the whole struct, remember its mode so
@@ -1621,7 +1621,7 @@ compute_record_mode (tree type)
      matches the type's size.  This only applies to RECORD_TYPE.  This
      does not apply to unions.  */
   if (TREE_CODE (type) == RECORD_TYPE && mode != VOIDmode
-      && host_integerp (TYPE_SIZE (type), 1)
+      && tree_fits_uhwi_p (TYPE_SIZE (type))
       && GET_MODE_BITSIZE (mode) == TREE_INT_CST_LOW (TYPE_SIZE (type)))
     SET_TYPE_MODE (type, mode);
   else
@@ -1763,7 +1763,7 @@ finish_bitfield_representative (tree repr, tree field)
 
   size = size_diffop (DECL_FIELD_OFFSET (field),
 		      DECL_FIELD_OFFSET (repr));
-  gcc_assert (host_integerp (size, 1));
+  gcc_assert (tree_fits_uhwi_p (size));
   bitsize = (tree_low_cst (size, 1) * BITS_PER_UNIT
 	     + tree_low_cst (DECL_FIELD_BIT_OFFSET (field), 1)
 	     - tree_low_cst (DECL_FIELD_BIT_OFFSET (repr), 1)
@@ -1785,7 +1785,7 @@ finish_bitfield_representative (tree repr, tree field)
 	return;
       maxsize = size_diffop (DECL_FIELD_OFFSET (nextf),
 			     DECL_FIELD_OFFSET (repr));
-      if (host_integerp (maxsize, 1))
+      if (tree_fits_uhwi_p (maxsize))
 	{
 	  maxbitsize = (tree_low_cst (maxsize, 1) * BITS_PER_UNIT
 			+ tree_low_cst (DECL_FIELD_BIT_OFFSET (nextf), 1)
@@ -1806,7 +1806,7 @@ finish_bitfield_representative (tree repr, tree field)
 	 use bitsize as fallback for this case.  */
       tree maxsize = size_diffop (TYPE_SIZE_UNIT (DECL_CONTEXT (field)),
 				  DECL_FIELD_OFFSET (repr));
-      if (host_integerp (maxsize, 1))
+      if (tree_fits_uhwi_p (maxsize))
 	maxbitsize = (tree_low_cst (maxsize, 1) * BITS_PER_UNIT
 		      - tree_low_cst (DECL_FIELD_BIT_OFFSET (repr), 1));
       else
@@ -1919,8 +1919,8 @@ finish_bitfield_layout (record_layout_info rli)
 	     representative to be generated.  That will at most
 	     generate worse code but still maintain correctness with
 	     respect to the C++ memory model.  */
-	  else if (!((host_integerp (DECL_FIELD_OFFSET (repr), 1)
-		      && host_integerp (DECL_FIELD_OFFSET (field), 1))
+	  else if (!((tree_fits_uhwi_p (DECL_FIELD_OFFSET (repr))
+		      && tree_fits_uhwi_p (DECL_FIELD_OFFSET (field)))
 		     || operand_equal_p (DECL_FIELD_OFFSET (repr),
 					 DECL_FIELD_OFFSET (field), 0)))
 	    {
diff --git a/gcc/trans-mem.c b/gcc/trans-mem.c
index b56ff73508130b1fc18f5614de9fc139ed0215e0..1a22838ee04faa6e8c5d54335010a90d18aa9337 100644
--- a/gcc/trans-mem.c
+++ b/gcc/trans-mem.c
@@ -1103,7 +1103,7 @@ tm_log_add (basic_block entry_block, tree addr, gimple stmt)
       if (entry_block
 	  && transaction_invariant_address_p (lp->addr, entry_block)
 	  && TYPE_SIZE_UNIT (type) != NULL
-	  && host_integerp (TYPE_SIZE_UNIT (type), 1)
+	  && tree_fits_uhwi_p (TYPE_SIZE_UNIT (type))
 	  && (tree_low_cst (TYPE_SIZE_UNIT (type), 1)
 	      < PARAM_VALUE (PARAM_TM_MAX_AGGREGATE_SIZE))
 	  /* We must be able to copy this type normally.  I.e., no
@@ -1187,7 +1187,7 @@ tm_log_emit_stmt (tree addr, gimple stmt)
     code = BUILT_IN_TM_LOG_DOUBLE;
   else if (type == long_double_type_node)
     code = BUILT_IN_TM_LOG_LDOUBLE;
-  else if (host_integerp (size, 1))
+  else if (tree_fits_uhwi_p (size))
     {
       unsigned int n = tree_low_cst (size, 1);
       switch (n)
@@ -2105,7 +2105,7 @@ build_tm_load (location_t loc, tree lhs, tree rhs, gimple_stmt_iterator *gsi)
   else if (type == long_double_type_node)
     code = BUILT_IN_TM_LOAD_LDOUBLE;
   else if (TYPE_SIZE_UNIT (type) != NULL
-	   && host_integerp (TYPE_SIZE_UNIT (type), 1))
+	   && tree_fits_uhwi_p (TYPE_SIZE_UNIT (type)))
     {
       switch (tree_low_cst (TYPE_SIZE_UNIT (type), 1))
 	{
@@ -2177,7 +2177,7 @@ build_tm_store (location_t loc, tree lhs, tree rhs, gimple_stmt_iterator *gsi)
   else if (type == long_double_type_node)
     code = BUILT_IN_TM_STORE_LDOUBLE;
   else if (TYPE_SIZE_UNIT (type) != NULL
-	   && host_integerp (TYPE_SIZE_UNIT (type), 1))
+	   && tree_fits_uhwi_p (TYPE_SIZE_UNIT (type)))
     {
       switch (tree_low_cst (TYPE_SIZE_UNIT (type), 1))
 	{
diff --git a/gcc/tree-cfg.c b/gcc/tree-cfg.c
index d7f62125e4a5f42886dcc0d4fa767735ccb460ef..e8a06ccea67152d7eab97509e9a8691357c2a565 100644
--- a/gcc/tree-cfg.c
+++ b/gcc/tree-cfg.c
@@ -2701,8 +2701,8 @@ verify_expr (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
 
       if (TREE_CODE (t) == BIT_FIELD_REF)
 	{
-	  if (!host_integerp (TREE_OPERAND (t, 1), 1)
-	      || !host_integerp (TREE_OPERAND (t, 2), 1))
+	  if (!tree_fits_uhwi_p (TREE_OPERAND (t, 1))
+	      || !tree_fits_uhwi_p (TREE_OPERAND (t, 2)))
 	    {
 	      error ("invalid position or size operand to BIT_FIELD_REF");
 	      return t;
diff --git a/gcc/tree-dfa.c b/gcc/tree-dfa.c
index 83fe0d81100197a6b23a23c537756d471b64d949..678bbb9c4e3228fab26a910b2a49422311b261aa 100644
--- a/gcc/tree-dfa.c
+++ b/gcc/tree-dfa.c
@@ -407,7 +407,7 @@ get_ref_base_and_extent (tree exp, HOST_WIDE_INT *poffset,
     }
   if (size_tree != NULL_TREE)
     {
-      if (! host_integerp (size_tree, 1))
+      if (! tree_fits_uhwi_p (size_tree))
 	bitsize = -1;
       else
 	bitsize = TREE_INT_CST_LOW (size_tree);
@@ -475,7 +475,7 @@ get_ref_base_and_extent (tree exp, HOST_WIDE_INT *poffset,
 		   because that would get us out of the structure otherwise.  */
 		if (maxsize != -1
 		    && csize
-		    && host_integerp (csize, 1)
+		    && tree_fits_uhwi_p (csize)
 		    && bit_offset.fits_shwi ())
 		  maxsize = TREE_INT_CST_LOW (csize)
 			    - bit_offset.to_shwi ();
@@ -519,7 +519,7 @@ get_ref_base_and_extent (tree exp, HOST_WIDE_INT *poffset,
 		   because that would get us outside of the array otherwise.  */
 		if (maxsize != -1
 		    && asize
-		    && host_integerp (asize, 1)
+		    && tree_fits_uhwi_p (asize)
 		    && bit_offset.fits_shwi ())
 		  maxsize = TREE_INT_CST_LOW (asize)
 			    - bit_offset.to_shwi ();
@@ -569,7 +569,7 @@ get_ref_base_and_extent (tree exp, HOST_WIDE_INT *poffset,
 	  if (seen_variable_array_ref
 	      && maxsize != -1
 	      && (!bit_offset.fits_shwi ()
-		  || !host_integerp (TYPE_SIZE (TREE_TYPE (exp)), 1)
+		  || !tree_fits_uhwi_p (TYPE_SIZE (TREE_TYPE (exp)))
 		  || (bit_offset.to_shwi () + maxsize
 		      == (HOST_WIDE_INT) TREE_INT_CST_LOW
 		            (TYPE_SIZE (TREE_TYPE (exp))))))
@@ -606,7 +606,7 @@ get_ref_base_and_extent (tree exp, HOST_WIDE_INT *poffset,
   if (seen_variable_array_ref
       && maxsize != -1
       && (!bit_offset.fits_shwi ()
-	  || !host_integerp (TYPE_SIZE (TREE_TYPE (exp)), 1)
+	  || !tree_fits_uhwi_p (TYPE_SIZE (TREE_TYPE (exp)))
 	  || (bit_offset.to_shwi () + maxsize
 	      == (HOST_WIDE_INT) TREE_INT_CST_LOW
 	           (TYPE_SIZE (TREE_TYPE (exp))))))
@@ -631,7 +631,7 @@ get_ref_base_and_extent (tree exp, HOST_WIDE_INT *poffset,
       /* If maxsize is unknown adjust it according to the size of the
          base decl.  */
       if (maxsize == -1
-	  && host_integerp (DECL_SIZE (exp), 1))
+	  && tree_fits_uhwi_p (DECL_SIZE (exp)))
 	maxsize = TREE_INT_CST_LOW (DECL_SIZE (exp)) - hbit_offset;
     }
   else if (CONSTANT_CLASS_P (exp))
@@ -639,7 +639,7 @@ get_ref_base_and_extent (tree exp, HOST_WIDE_INT *poffset,
       /* If maxsize is unknown adjust it according to the size of the
          base type constant.  */
       if (maxsize == -1
-	  && host_integerp (TYPE_SIZE (TREE_TYPE (exp)), 1))
+	  && tree_fits_uhwi_p (TYPE_SIZE (TREE_TYPE (exp))))
 	maxsize = TREE_INT_CST_LOW (TYPE_SIZE (TREE_TYPE (exp))) - hbit_offset;
     }
 
diff --git a/gcc/tree-object-size.c b/gcc/tree-object-size.c
index 965dffa4290f6c645d68c59a39f836553e527b1b..98d44bda3f5835647561997ddf965558f9efa4d2 100644
--- a/gcc/tree-object-size.c
+++ b/gcc/tree-object-size.c
@@ -81,7 +81,7 @@ static unsigned HOST_WIDE_INT offset_limit;
 static void
 init_offset_limit (void)
 {
-  if (host_integerp (TYPE_MAX_VALUE (sizetype), 1))
+  if (tree_fits_uhwi_p (TYPE_MAX_VALUE (sizetype)))
     offset_limit = tree_low_cst (TYPE_MAX_VALUE (sizetype), 1);
   else
     offset_limit = -1;
@@ -209,14 +209,14 @@ addr_object_size (struct object_size_info *osi, const_tree ptr,
     }
   else if (pt_var
 	   && DECL_P (pt_var)
-	   && host_integerp (DECL_SIZE_UNIT (pt_var), 1)
+	   && tree_fits_uhwi_p (DECL_SIZE_UNIT (pt_var))
 	   && (unsigned HOST_WIDE_INT)
 	        tree_low_cst (DECL_SIZE_UNIT (pt_var), 1) < offset_limit)
     pt_var_size = DECL_SIZE_UNIT (pt_var);
   else if (pt_var
 	   && TREE_CODE (pt_var) == STRING_CST
 	   && TYPE_SIZE_UNIT (TREE_TYPE (pt_var))
-	   && host_integerp (TYPE_SIZE_UNIT (TREE_TYPE (pt_var)), 1)
+	   && tree_fits_uhwi_p (TYPE_SIZE_UNIT (TREE_TYPE (pt_var)))
 	   && (unsigned HOST_WIDE_INT)
 	      tree_low_cst (TYPE_SIZE_UNIT (TREE_TYPE (pt_var)), 1)
 	      < offset_limit)
@@ -243,7 +243,7 @@ addr_object_size (struct object_size_info *osi, const_tree ptr,
 	  if (var != pt_var && TREE_CODE (var) == ARRAY_REF)
 	    var = TREE_OPERAND (var, 0);
 	  if (! TYPE_SIZE_UNIT (TREE_TYPE (var))
-	      || ! host_integerp (TYPE_SIZE_UNIT (TREE_TYPE (var)), 1)
+	      || ! tree_fits_uhwi_p (TYPE_SIZE_UNIT (TREE_TYPE (var)))
 	      || (pt_var_size
 		  && tree_int_cst_lt (pt_var_size,
 				      TYPE_SIZE_UNIT (TREE_TYPE (var)))))
@@ -371,7 +371,7 @@ addr_object_size (struct object_size_info *osi, const_tree ptr,
   else
     bytes = pt_var_size;
 
-  if (host_integerp (bytes, 1))
+  if (tree_fits_uhwi_p (bytes))
     return tree_low_cst (bytes, 1);
 
   return unknown[object_size_type];
@@ -435,7 +435,7 @@ alloc_object_size (const_gimple call, int object_size_type)
   else if (arg1 >= 0)
     bytes = fold_convert (sizetype, gimple_call_arg (call, arg1));
 
-  if (bytes && host_integerp (bytes, 1))
+  if (bytes && tree_fits_uhwi_p (bytes))
     return tree_low_cst (bytes, 1);
 
   return unknown[object_size_type];
@@ -796,7 +796,7 @@ plus_stmt_object_size (struct object_size_info *osi, tree var, gimple stmt)
       && (TREE_CODE (op0) == SSA_NAME
 	  || TREE_CODE (op0) == ADDR_EXPR))
     {
-      if (! host_integerp (op1, 1))
+      if (! tree_fits_uhwi_p (op1))
 	bytes = unknown[object_size_type];
       else if (TREE_CODE (op0) == SSA_NAME)
 	return merge_object_sizes (osi, var, op0, tree_low_cst (op1, 1));
@@ -1228,7 +1228,7 @@ compute_object_sizes (void)
 		{
 		  tree ost = gimple_call_arg (call, 1);
 
-		  if (host_integerp (ost, 1))
+		  if (tree_fits_uhwi_p (ost))
 		    {
 		      unsigned HOST_WIDE_INT object_size_type
 			= tree_low_cst (ost, 1);
diff --git a/gcc/tree-sra.c b/gcc/tree-sra.c
index 2ac9ba1f0042418a1627454e0bd018bdd22faa5c..71769eb7d87c45532a8de3e9aaaef050280f5836 100644
--- a/gcc/tree-sra.c
+++ b/gcc/tree-sra.c
@@ -742,12 +742,12 @@ type_internals_preclude_sra_p (tree type, const char **msg)
 		*msg = "zero structure field size";
 	        return true;
 	      }
-	    if (!host_integerp (DECL_FIELD_OFFSET (fld), 1))
+	    if (!tree_fits_uhwi_p (DECL_FIELD_OFFSET (fld)))
 	      {
 		*msg = "structure field offset not fixed";
 		return true;
 	      }
-	    if (!host_integerp (DECL_SIZE (fld), 1))
+	    if (!tree_fits_uhwi_p (DECL_SIZE (fld)))
 	      {
 	        *msg = "structure field size not fixed";
 		return true;
@@ -1651,12 +1651,12 @@ build_user_friendly_ref_for_offset (tree *res, tree type, HOST_WIDE_INT offset,
 		continue;
 
 	      tr_pos = bit_position (fld);
-	      if (!tr_pos || !host_integerp (tr_pos, 1))
+	      if (!tr_pos || !tree_fits_uhwi_p (tr_pos))
 		continue;
 	      pos = TREE_INT_CST_LOW (tr_pos);
 	      gcc_assert (TREE_CODE (type) == RECORD_TYPE || pos == 0);
 	      tr_size = DECL_SIZE (fld);
-	      if (!tr_size || !host_integerp (tr_size, 1))
+	      if (!tr_size || !tree_fits_uhwi_p (tr_size))
 		continue;
 	      size = TREE_INT_CST_LOW (tr_size);
 	      if (size == 0)
@@ -1681,7 +1681,7 @@ build_user_friendly_ref_for_offset (tree *res, tree type, HOST_WIDE_INT offset,
 
 	case ARRAY_TYPE:
 	  tr_size = TYPE_SIZE (TREE_TYPE (type));
-	  if (!tr_size || !host_integerp (tr_size, 1))
+	  if (!tr_size || !tree_fits_uhwi_p (tr_size))
 	    return false;
 	  el_size = tree_low_cst (tr_size, 1);
 
@@ -1759,7 +1759,7 @@ maybe_add_sra_candidate (tree var)
       reject (var, "has incomplete type");
       return false;
     }
-  if (!host_integerp (TYPE_SIZE (type), 1))
+  if (!tree_fits_uhwi_p (TYPE_SIZE (type)))
     {
       reject (var, "type size not fixed");
       return false;
@@ -2799,8 +2799,8 @@ sra_modify_expr (tree *expr, gimple_stmt_iterator *gsi, bool write)
     {
       HOST_WIDE_INT start_offset, chunk_size;
       if (bfr
-	  && host_integerp (TREE_OPERAND (bfr, 1), 1)
-	  && host_integerp (TREE_OPERAND (bfr, 2), 1))
+	  && tree_fits_uhwi_p (TREE_OPERAND (bfr, 1))
+	  && tree_fits_uhwi_p (TREE_OPERAND (bfr, 2)))
 	{
 	  chunk_size = tree_low_cst (TREE_OPERAND (bfr, 1), 1);
 	  start_offset = access->offset
@@ -3693,7 +3693,7 @@ find_param_candidates (void)
 	continue;
 
       if (!COMPLETE_TYPE_P (type)
-	  || !host_integerp (TYPE_SIZE (type), 1)
+	  || !tree_fits_uhwi_p (TYPE_SIZE (type))
           || tree_low_cst (TYPE_SIZE (type), 1) == 0
 	  || (AGGREGATE_TYPE_P (type)
 	      && type_internals_preclude_sra_p (type, &msg)))
diff --git a/gcc/tree-ssa-ccp.c b/gcc/tree-ssa-ccp.c
index 50006abdc052253ce8e30023bf9db32efdc5d756..6ba912d11f8a76aeaade54c08b9b4b00c20d2cba 100644
--- a/gcc/tree-ssa-ccp.c
+++ b/gcc/tree-ssa-ccp.c
@@ -1487,7 +1487,7 @@ bit_value_assume_aligned (gimple stmt)
 	       && TREE_CODE (ptrval.value) == INTEGER_CST)
 	      || ptrval.mask.is_minus_one ());
   align = gimple_call_arg (stmt, 1);
-  if (!host_integerp (align, 1))
+  if (!tree_fits_uhwi_p (align))
     return ptrval;
   aligni = tree_low_cst (align, 1);
   if (aligni <= 1
@@ -1496,7 +1496,7 @@ bit_value_assume_aligned (gimple stmt)
   if (gimple_call_num_args (stmt) > 2)
     {
       misalign = gimple_call_arg (stmt, 2);
-      if (!host_integerp (misalign, 1))
+      if (!tree_fits_uhwi_p (misalign))
 	return ptrval;
       misaligni = tree_low_cst (misalign, 1);
       if (misaligni >= aligni)
@@ -1881,7 +1881,7 @@ fold_builtin_alloca_with_align (gimple stmt)
   arg = get_constant_value (gimple_call_arg (stmt, 0));
   if (arg == NULL_TREE
       || TREE_CODE (arg) != INTEGER_CST
-      || !host_integerp (arg, 1))
+      || !tree_fits_uhwi_p (arg))
     return NULL_TREE;
 
   size = TREE_INT_CST_LOW (arg);
diff --git a/gcc/tree-ssa-forwprop.c b/gcc/tree-ssa-forwprop.c
index e793dbfe88c8d98457ee231548b0b8e2fa402d32..e8b4f73ee62e6d0109c18b3c78b1a9395457a56b 100644
--- a/gcc/tree-ssa-forwprop.c
+++ b/gcc/tree-ssa-forwprop.c
@@ -1528,7 +1528,7 @@ simplify_builtin_call (gimple_stmt_iterator *gsi_p, tree callee2)
 	  use_operand_p use_p;
 
 	  if (!tree_fits_shwi_p (val2)
-	      || !host_integerp (len2, 1))
+	      || !tree_fits_uhwi_p (len2))
 	    break;
 	  if (is_gimple_call (stmt1))
 	    {
@@ -1547,12 +1547,12 @@ simplify_builtin_call (gimple_stmt_iterator *gsi_p, tree callee2)
 	      src1 = gimple_call_arg (stmt1, 1);
 	      len1 = gimple_call_arg (stmt1, 2);
 	      lhs1 = gimple_call_lhs (stmt1);
-	      if (!host_integerp (len1, 1))
+	      if (!tree_fits_uhwi_p (len1))
 		break;
 	      str1 = string_constant (src1, &off1);
 	      if (str1 == NULL_TREE)
 		break;
-	      if (!host_integerp (off1, 1)
+	      if (!tree_fits_uhwi_p (off1)
 		  || compare_tree_int (off1, TREE_STRING_LENGTH (str1) - 1) > 0
 		  || compare_tree_int (len1, TREE_STRING_LENGTH (str1)
 					     - tree_low_cst (off1, 1)) > 0
@@ -1593,7 +1593,7 @@ simplify_builtin_call (gimple_stmt_iterator *gsi_p, tree callee2)
 	  /* If the difference between the second and first destination pointer
 	     is not constant, or is bigger than memcpy length, bail out.  */
 	  if (diff == NULL
-	      || !host_integerp (diff, 1)
+	      || !tree_fits_uhwi_p (diff)
 	      || tree_int_cst_lt (len1, diff))
 	    break;
 
@@ -2317,8 +2317,8 @@ simplify_rotate (gimple_stmt_iterator *gsi)
     return false;
 
   /* CNT1 + CNT2 == B case above.  */
-  if (host_integerp (def_arg2[0], 1)
-      && host_integerp (def_arg2[1], 1)
+  if (tree_fits_uhwi_p (def_arg2[0])
+      && tree_fits_uhwi_p (def_arg2[1])
       && (unsigned HOST_WIDE_INT) tree_low_cst (def_arg2[0], 1)
 	 + tree_low_cst (def_arg2[1], 1) == TYPE_PRECISION (rtype))
     rotcnt = def_arg2[0];
diff --git a/gcc/tree-ssa-loop-ivcanon.c b/gcc/tree-ssa-loop-ivcanon.c
index 9fd649e6e0930c3013cb84a0f71f08c37150e811..0ac5963e1153deb839a184b68d0a0ad430c22662 100644
--- a/gcc/tree-ssa-loop-ivcanon.c
+++ b/gcc/tree-ssa-loop-ivcanon.c
@@ -667,7 +667,7 @@ try_unroll_loop_completely (struct loop *loop,
      If the number of execution of loop is determined by standard induction
      variable test, then EXIT and EDGE_TO_CANCEL are the two edges leaving
      from the iv test.  */
-  if (host_integerp (niter, 1))
+  if (tree_fits_uhwi_p (niter))
     {
       n_unroll = tree_low_cst (niter, 1);
       n_unroll_found = true;
diff --git a/gcc/tree-ssa-loop-prefetch.c b/gcc/tree-ssa-loop-prefetch.c
index e00989527aa44081f097cb6e4bdd4112bfa67304..426f4bcb4e7e543af9185a02b3e609a16d0f5b6e 100644
--- a/gcc/tree-ssa-loop-prefetch.c
+++ b/gcc/tree-ssa-loop-prefetch.c
@@ -1508,7 +1508,7 @@ self_reuse_distance (data_reference_p dr, unsigned *loop_sizes, unsigned n,
       if (TREE_CODE (ref) == ARRAY_REF)
 	{
 	  stride = TYPE_SIZE_UNIT (TREE_TYPE (ref));
-	  if (host_integerp (stride, 1))
+	  if (tree_fits_uhwi_p (stride))
 	    astride = tree_low_cst (stride, 1);
 	  else
 	    astride = L1_CACHE_LINE_SIZE;
diff --git a/gcc/tree-ssa-phiopt.c b/gcc/tree-ssa-phiopt.c
index 4fdaba26d0eb76fe3e4e0911fdbfde3522f78599..666a9155e26ab31b812e8bc52d7d8bda3c2f4e9a 100644
--- a/gcc/tree-ssa-phiopt.c
+++ b/gcc/tree-ssa-phiopt.c
@@ -1975,9 +1975,9 @@ hoist_adjacent_loads (basic_block bb0, basic_block bb1,
       tree_offset2 = bit_position (field2);
       tree_size2 = DECL_SIZE (field2);
 
-      if (!host_integerp (tree_offset1, 1)
-	  || !host_integerp (tree_offset2, 1)
-	  || !host_integerp (tree_size2, 1))
+      if (!tree_fits_uhwi_p (tree_offset1)
+	  || !tree_fits_uhwi_p (tree_offset2)
+	  || !tree_fits_uhwi_p (tree_size2))
 	continue;
 
       offset1 = TREE_INT_CST_LOW (tree_offset1);
diff --git a/gcc/tree-ssa-sccvn.c b/gcc/tree-ssa-sccvn.c
index fe01a4128dc9463fc7910b224945c4ea17ff6505..a49a282a69f6e2a427c952509fd96f9db85d88ab 100644
--- a/gcc/tree-ssa-sccvn.c
+++ b/gcc/tree-ssa-sccvn.c
@@ -936,7 +936,7 @@ ao_ref_init_from_vn_reference (ao_ref *ref,
     }
   if (size_tree != NULL_TREE)
     {
-      if (!host_integerp (size_tree, 1))
+      if (!tree_fits_uhwi_p (size_tree))
 	size = -1;
       else
 	size = TREE_INT_CST_LOW (size_tree);
@@ -1006,7 +1006,7 @@ ao_ref_init_from_vn_reference (ao_ref *ref,
 	       parts manually.  */
 
 	    if (op->op1
-		|| !host_integerp (DECL_FIELD_OFFSET (field), 1))
+		|| !tree_fits_uhwi_p (DECL_FIELD_OFFSET (field)))
 	      max_size = -1;
 	    else
 	      {
@@ -1586,7 +1586,7 @@ vn_reference_lookup_3 (ao_ref *ref, tree vuse, void *vr_)
   if (is_gimple_reg_type (vr->type)
       && gimple_call_builtin_p (def_stmt, BUILT_IN_MEMSET)
       && integer_zerop (gimple_call_arg (def_stmt, 1))
-      && host_integerp (gimple_call_arg (def_stmt, 2), 1)
+      && tree_fits_uhwi_p (gimple_call_arg (def_stmt, 2))
       && TREE_CODE (gimple_call_arg (def_stmt, 0)) == ADDR_EXPR)
     {
       tree ref2 = TREE_OPERAND (gimple_call_arg (def_stmt, 0), 0);
@@ -1835,7 +1835,7 @@ vn_reference_lookup_3 (ao_ref *ref, tree vuse, void *vr_)
 	       || TREE_CODE (gimple_call_arg (def_stmt, 0)) == SSA_NAME)
 	   && (TREE_CODE (gimple_call_arg (def_stmt, 1)) == ADDR_EXPR
 	       || TREE_CODE (gimple_call_arg (def_stmt, 1)) == SSA_NAME)
-	   && host_integerp (gimple_call_arg (def_stmt, 2), 1))
+	   && tree_fits_uhwi_p (gimple_call_arg (def_stmt, 2)))
     {
       tree lhs, rhs;
       ao_ref r;
@@ -1862,7 +1862,7 @@ vn_reference_lookup_3 (ao_ref *ref, tree vuse, void *vr_)
 	  if (!tem)
 	    return (void *)-1;
 	  if (TREE_CODE (tem) == MEM_REF
-	      && host_integerp (TREE_OPERAND (tem, 1), 1))
+	      && tree_fits_uhwi_p (TREE_OPERAND (tem, 1)))
 	    {
 	      lhs = TREE_OPERAND (tem, 0);
 	      lhs_offset += TREE_INT_CST_LOW (TREE_OPERAND (tem, 1));
@@ -1888,7 +1888,7 @@ vn_reference_lookup_3 (ao_ref *ref, tree vuse, void *vr_)
 	  if (!tem)
 	    return (void *)-1;
 	  if (TREE_CODE (tem) == MEM_REF
-	      && host_integerp (TREE_OPERAND (tem, 1), 1))
+	      && tree_fits_uhwi_p (TREE_OPERAND (tem, 1)))
 	    {
 	      rhs = TREE_OPERAND (tem, 0);
 	      rhs_offset += TREE_INT_CST_LOW (TREE_OPERAND (tem, 1));
@@ -1909,7 +1909,7 @@ vn_reference_lookup_3 (ao_ref *ref, tree vuse, void *vr_)
 	   && !DECL_P (base))
 	  || (TREE_CODE (base) == MEM_REF
 	      && (TREE_OPERAND (base, 0) != lhs
-		  || !host_integerp (TREE_OPERAND (base, 1), 1)))
+		  || !tree_fits_uhwi_p (TREE_OPERAND (base, 1))))
 	  || (DECL_P (base)
 	      && (TREE_CODE (lhs) != ADDR_EXPR
 		  || TREE_OPERAND (lhs, 0) != base)))
@@ -3221,7 +3221,7 @@ simplify_binary_expression (gimple stmt)
   /* Pointer plus constant can be represented as invariant address.
      Do so to allow further propatation, see also tree forwprop.  */
   if (code == POINTER_PLUS_EXPR
-      && host_integerp (op1, 1)
+      && tree_fits_uhwi_p (op1)
       && TREE_CODE (op0) == ADDR_EXPR
       && is_gimple_min_invariant (op0))
     return build_invariant_address (TREE_TYPE (op0),
diff --git a/gcc/tree-ssa-strlen.c b/gcc/tree-ssa-strlen.c
index 0e66b67bb240fdfe5f648786f88feab40a9d25f6..bacc59fd0e776233db6cc0cd868ce203b2547b69 100644
--- a/gcc/tree-ssa-strlen.c
+++ b/gcc/tree-ssa-strlen.c
@@ -846,9 +846,9 @@ adjust_last_stmt (strinfo si, gimple stmt, bool is_strcat)
     }
 
   len = gimple_call_arg (last.stmt, 2);
-  if (host_integerp (len, 1))
+  if (tree_fits_uhwi_p (len))
     {
-      if (!host_integerp (last.len, 1)
+      if (!tree_fits_uhwi_p (last.len)
 	  || integer_zerop (len)
 	  || (unsigned HOST_WIDE_INT) tree_low_cst (len, 1)
 	     != (unsigned HOST_WIDE_INT) tree_low_cst (last.len, 1) + 1)
@@ -1310,7 +1310,7 @@ handle_builtin_memcpy (enum built_in_function bcode, gimple_stmt_iterator *gsi)
     return;
 
   if (olddsi != NULL
-      && host_integerp (len, 1)
+      && tree_fits_uhwi_p (len)
       && !integer_zerop (len))
     adjust_last_stmt (olddsi, stmt, false);
 
@@ -1336,7 +1336,7 @@ handle_builtin_memcpy (enum built_in_function bcode, gimple_stmt_iterator *gsi)
       si = NULL;
       /* Handle memcpy (x, "abcd", 5) or
 	 memcpy (x, "abc\0uvw", 7).  */
-      if (!host_integerp (len, 1)
+      if (!tree_fits_uhwi_p (len)
 	  || (unsigned HOST_WIDE_INT) tree_low_cst (len, 1)
 	     <= (unsigned HOST_WIDE_INT) ~idx)
 	return;
@@ -1626,7 +1626,7 @@ handle_pointer_plus (gimple_stmt_iterator *gsi)
   if (idx < 0)
     {
       tree off = gimple_assign_rhs2 (stmt);
-      if (host_integerp (off, 1)
+      if (tree_fits_uhwi_p (off)
 	  && (unsigned HOST_WIDE_INT) tree_low_cst (off, 1)
 	     <= (unsigned HOST_WIDE_INT) ~idx)
 	ssa_ver_to_stridx[SSA_NAME_VERSION (lhs)]
diff --git a/gcc/tree-ssa-structalias.c b/gcc/tree-ssa-structalias.c
index 78693a32e893fc0c9ca583acc8323e7c1b3d1d32..f1172e7f7c9cf70c35e21836bcb79da8dabc60b8 100644
--- a/gcc/tree-ssa-structalias.c
+++ b/gcc/tree-ssa-structalias.c
@@ -3429,7 +3429,7 @@ get_constraint_for_1 (tree t, vec<ce_s> *results, bool address_p,
 		  && curr)
 		{
 		  unsigned HOST_WIDE_INT size;
-		  if (host_integerp (TYPE_SIZE (TREE_TYPE (t)), 1))
+		  if (tree_fits_uhwi_p (TYPE_SIZE (TREE_TYPE (t))))
 		    size = TREE_INT_CST_LOW (TYPE_SIZE (TREE_TYPE (t)));
 		  else
 		    size = -1;
@@ -5348,7 +5348,7 @@ push_fields_onto_fieldstack (tree type, vec<fieldoff_s> *fieldstack,
 	      }
 
 	    if (!DECL_SIZE (field)
-		|| !host_integerp (DECL_SIZE (field), 1))
+		|| !tree_fits_uhwi_p (DECL_SIZE (field)))
 	      has_unknown_size = true;
 
 	    /* If adjacent fields do not contain pointers merge them.  */
@@ -5624,7 +5624,7 @@ create_variable_info_for_1 (tree decl, const char *name)
   unsigned int i;
 
   if (!declsize
-      || !host_integerp (declsize, 1))
+      || !tree_fits_uhwi_p (declsize))
     {
       vi = new_var_info (decl, name);
       vi->offset = 0;
diff --git a/gcc/tree-stdarg.c b/gcc/tree-stdarg.c
index b0d2dacd8e122b03eda22bcb8761b999c2040584..e39734730c4c07bd8158ef45a64a8a68d026187e 100644
--- a/gcc/tree-stdarg.c
+++ b/gcc/tree-stdarg.c
@@ -172,7 +172,7 @@ va_list_counter_bump (struct stdarg_info *si, tree counter, tree rhs,
       if ((rhs_code == POINTER_PLUS_EXPR
 	   || rhs_code == PLUS_EXPR)
 	  && TREE_CODE (rhs1) == SSA_NAME
-	  && host_integerp (gimple_assign_rhs2 (stmt), 1))
+	  && tree_fits_uhwi_p (gimple_assign_rhs2 (stmt)))
 	{
 	  ret += tree_low_cst (gimple_assign_rhs2 (stmt), 1);
 	  lhs = rhs1;
@@ -182,7 +182,7 @@ va_list_counter_bump (struct stdarg_info *si, tree counter, tree rhs,
       if (rhs_code == ADDR_EXPR 
 	  && TREE_CODE (TREE_OPERAND (rhs1, 0)) == MEM_REF
 	  && TREE_CODE (TREE_OPERAND (TREE_OPERAND (rhs1, 0), 0)) == SSA_NAME
-	  && host_integerp (TREE_OPERAND (TREE_OPERAND (rhs1, 0), 1), 1))
+	  && tree_fits_uhwi_p (TREE_OPERAND (TREE_OPERAND (rhs1, 0), 1)))
 	{
 	  ret += tree_low_cst (TREE_OPERAND (TREE_OPERAND (rhs1, 0), 1), 1);
 	  lhs = TREE_OPERAND (TREE_OPERAND (rhs1, 0), 0);
@@ -239,7 +239,7 @@ va_list_counter_bump (struct stdarg_info *si, tree counter, tree rhs,
       if ((rhs_code == POINTER_PLUS_EXPR
 	   || rhs_code == PLUS_EXPR)
 	  && TREE_CODE (rhs1) == SSA_NAME
-	  && host_integerp (gimple_assign_rhs2 (stmt), 1))
+	  && tree_fits_uhwi_p (gimple_assign_rhs2 (stmt)))
 	{
 	  val -= tree_low_cst (gimple_assign_rhs2 (stmt), 1);
 	  lhs = rhs1;
@@ -249,7 +249,7 @@ va_list_counter_bump (struct stdarg_info *si, tree counter, tree rhs,
       if (rhs_code == ADDR_EXPR 
 	  && TREE_CODE (TREE_OPERAND (rhs1, 0)) == MEM_REF
 	  && TREE_CODE (TREE_OPERAND (TREE_OPERAND (rhs1, 0), 0)) == SSA_NAME
-	  && host_integerp (TREE_OPERAND (TREE_OPERAND (rhs1, 0), 1), 1))
+	  && tree_fits_uhwi_p (TREE_OPERAND (TREE_OPERAND (rhs1, 0), 1)))
 	{
 	  val -= tree_low_cst (TREE_OPERAND (TREE_OPERAND (rhs1, 0), 1), 1);
 	  lhs = TREE_OPERAND (TREE_OPERAND (rhs1, 0), 0);
@@ -589,7 +589,7 @@ check_all_va_list_escapes (struct stdarg_info *si)
 		  if (rhs_code == MEM_REF
 		      && TREE_OPERAND (rhs, 0) == use
 		      && TYPE_SIZE_UNIT (TREE_TYPE (rhs))
-		      && host_integerp (TYPE_SIZE_UNIT (TREE_TYPE (rhs)), 1)
+		      && tree_fits_uhwi_p (TYPE_SIZE_UNIT (TREE_TYPE (rhs)))
 		      && si->offsets[SSA_NAME_VERSION (use)] != -1)
 		    {
 		      unsigned HOST_WIDE_INT gpr_size;
diff --git a/gcc/tree-switch-conversion.c b/gcc/tree-switch-conversion.c
index 9d5734a54531005a4808bb1ad7bfec6b318c4e02..322eafe5272b142088993920a5e39935a371037f 100644
--- a/gcc/tree-switch-conversion.c
+++ b/gcc/tree-switch-conversion.c
@@ -697,7 +697,7 @@ static bool
 check_range (struct switch_conv_info *info)
 {
   gcc_assert (info->range_size);
-  if (!host_integerp (info->range_size, 1))
+  if (!tree_fits_uhwi_p (info->range_size))
     {
       info->reason = "index range way too large or otherwise unusable";
       return false;
diff --git a/gcc/tree-vect-data-refs.c b/gcc/tree-vect-data-refs.c
index 380002161a216abec0b91bedcfac16e81d6e7a69..c4246079a259146ce060547591c5971f37f0e7d0 100644
--- a/gcc/tree-vect-data-refs.c
+++ b/gcc/tree-vect-data-refs.c
@@ -772,7 +772,7 @@ vect_compute_data_ref_alignment (struct data_reference *dr)
   /* Modulo alignment.  */
   misalign = size_binop (FLOOR_MOD_EXPR, misalign, alignment);
 
-  if (!host_integerp (misalign, 1))
+  if (!tree_fits_uhwi_p (misalign))
     {
       /* Negative or overflowed misalignment value.  */
       if (dump_enabled_p ())
@@ -960,7 +960,7 @@ vect_verify_datarefs_alignment (loop_vec_info loop_vinfo, bb_vec_info bb_vinfo)
 static bool
 not_size_aligned (tree exp)
 {
-  if (!host_integerp (TYPE_SIZE (TREE_TYPE (exp)), 1))
+  if (!tree_fits_uhwi_p (TYPE_SIZE (TREE_TYPE (exp))))
     return true;
 
   return (TREE_INT_CST_LOW (TYPE_SIZE (TREE_TYPE (exp)))
@@ -2544,8 +2544,8 @@ vect_analyze_data_ref_accesses (loop_vec_info loop_vinfo, bb_vec_info bb_vinfo)
 	  /* Check that the data-refs have the same constant size and step.  */
 	  tree sza = TYPE_SIZE_UNIT (TREE_TYPE (DR_REF (dra)));
 	  tree szb = TYPE_SIZE_UNIT (TREE_TYPE (DR_REF (drb)));
-	  if (!host_integerp (sza, 1)
-	      || !host_integerp (szb, 1)
+	  if (!tree_fits_uhwi_p (sza)
+	      || !tree_fits_uhwi_p (szb)
 	      || !tree_int_cst_equal (sza, szb)
 	      || !tree_fits_shwi_p (DR_STEP (dra))
 	      || !tree_fits_shwi_p (DR_STEP (drb))
@@ -3268,7 +3268,7 @@ again:
 		      STRIP_NOPS (off);
 		      if (TREE_CODE (DR_INIT (newdr)) == INTEGER_CST
 			  && TREE_CODE (off) == MULT_EXPR
-			  && host_integerp (TREE_OPERAND (off, 1), 1))
+			  && tree_fits_uhwi_p (TREE_OPERAND (off, 1)))
 			{
 			  tree step = TREE_OPERAND (off, 1);
 			  off = TREE_OPERAND (off, 0);
diff --git a/gcc/tree-vect-generic.c b/gcc/tree-vect-generic.c
index 130193ce878f2d6c3ef282189df5d56787e424f3..b13e433b24d25803531772f99a9bf53ecaeaec16 100644
--- a/gcc/tree-vect-generic.c
+++ b/gcc/tree-vect-generic.c
@@ -485,7 +485,7 @@ expand_vector_divmod (gimple_stmt_iterator *gsi, tree type, tree op0,
 		      unsigned HOST_WIDE_INT d2;
 		      int this_pre_shift;
 
-		      if (!host_integerp (cst2, 1))
+		      if (!tree_fits_uhwi_p (cst2))
 			return NULL_TREE;
 		      d2 = tree_low_cst (cst2, 1) & mask;
 		      if (d2 == 0)
@@ -1054,7 +1054,7 @@ vector_element (gimple_stmt_iterator *gsi, tree vect, tree idx, tree *ptmpvec)
       /* Given that we're about to compute a binary modulus,
 	 we don't care about the high bits of the value.  */
       index = TREE_INT_CST_LOW (idx);
-      if (!host_integerp (idx, 1) || index >= elements)
+      if (!tree_fits_uhwi_p (idx) || index >= elements)
 	{
 	  index &= elements - 1;
 	  idx = build_int_cst (TREE_TYPE (idx), index);
@@ -1186,7 +1186,7 @@ lower_vec_perm (gimple_stmt_iterator *gsi)
 	  unsigned HOST_WIDE_INT index;
 
 	  index = TREE_INT_CST_LOW (i_val);
-	  if (!host_integerp (i_val, 1) || index >= elements)
+	  if (!tree_fits_uhwi_p (i_val) || index >= elements)
 	    i_val = build_int_cst (mask_elt_type, index & (elements - 1));
 
           if (two_operand_p && (index & elements) != 0)
diff --git a/gcc/tree-vect-patterns.c b/gcc/tree-vect-patterns.c
index ba0f4feea6e07fbfc60e0dc9cabe83026d87c85d..a0d366ad211f80d226307dd488f1feb453ae9de7 100644
--- a/gcc/tree-vect-patterns.c
+++ b/gcc/tree-vect-patterns.c
@@ -1635,7 +1635,7 @@ vect_recog_rotate_pattern (vec<gimple> *stmts, tree *type_in, tree *type_out)
 
   if (TREE_CODE (def) == INTEGER_CST)
     {
-      if (!host_integerp (def, 1)
+      if (!tree_fits_uhwi_p (def)
 	  || (unsigned HOST_WIDE_INT) tree_low_cst (def, 1)
 	     >= GET_MODE_PRECISION (TYPE_MODE (type))
 	  || integer_zerop (def))
diff --git a/gcc/tree-vrp.c b/gcc/tree-vrp.c
index 656e8e1c9bcda59dd2e985159114b5bcb5207c86..e2ff918602aaeef35b2bd54ea100255f216cdab2 100644
--- a/gcc/tree-vrp.c
+++ b/gcc/tree-vrp.c
@@ -5015,7 +5015,7 @@ register_edge_assert_for_2 (tree name, edge e, gimple_stmt_iterator bsi,
 	  name2 = gimple_assign_rhs1 (def_stmt);
 	  cst2 = gimple_assign_rhs2 (def_stmt);
 	  if (TREE_CODE (name2) == SSA_NAME
-	      && host_integerp (cst2, 1)
+	      && tree_fits_uhwi_p (cst2)
 	      && INTEGRAL_TYPE_P (TREE_TYPE (name2))
 	      && IN_RANGE (tree_low_cst (cst2, 1), 1, prec - 1)
 	      && prec <= HOST_BITS_PER_DOUBLE_INT
diff --git a/gcc/tree.c b/gcc/tree.c
index 59c5452a9a050da79695c505e04d601f300ee13d..4f290ba2f82a51aba817cadcaed4e86dab25c9ae 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -2210,7 +2210,7 @@ tree_ctz (const_tree expr)
       return MIN (ret1 + ret2, prec);
     case LSHIFT_EXPR:
       ret1 = tree_ctz (TREE_OPERAND (expr, 0));
-      if (host_integerp (TREE_OPERAND (expr, 1), 1)
+      if (tree_fits_uhwi_p (TREE_OPERAND (expr, 1))
 	  && ((unsigned HOST_WIDE_INT) tree_low_cst (TREE_OPERAND (expr, 1), 1)
 	      < (unsigned HOST_WIDE_INT) prec))
 	{
@@ -2219,7 +2219,7 @@ tree_ctz (const_tree expr)
 	}
       return ret1;
     case RSHIFT_EXPR:
-      if (host_integerp (TREE_OPERAND (expr, 1), 1)
+      if (tree_fits_uhwi_p (TREE_OPERAND (expr, 1))
 	  && ((unsigned HOST_WIDE_INT) tree_low_cst (TREE_OPERAND (expr, 1), 1)
 	      < (unsigned HOST_WIDE_INT) prec))
 	{
@@ -2674,7 +2674,7 @@ max_int_size_in_bytes (const_tree type)
     {
       size_tree = TYPE_ARRAY_MAX_SIZE (type);
 
-      if (size_tree && host_integerp (size_tree, 1))
+      if (size_tree && tree_fits_uhwi_p (size_tree))
 	size = tree_low_cst (size_tree, 1);
     }
 
@@ -2685,7 +2685,7 @@ max_int_size_in_bytes (const_tree type)
     {
       size_tree = lang_hooks.types.max_size (type);
 
-      if (size_tree && host_integerp (size_tree, 1))
+      if (size_tree && tree_fits_uhwi_p (size_tree))
 	size = tree_low_cst (size_tree, 1);
     }
 
@@ -7282,7 +7282,7 @@ compare_tree_int (const_tree t, unsigned HOST_WIDE_INT u)
 bool
 valid_constant_size_p (const_tree size)
 {
-  if (! host_integerp (size, 1)
+  if (! tree_fits_uhwi_p (size)
       || TREE_OVERFLOW (size)
       || tree_int_cst_sign_bit (size) != 0)
     return false;
@@ -7686,7 +7686,7 @@ build_nonstandard_integer_type (unsigned HOST_WIDE_INT precision,
     fixup_signed_type (itype);
 
   ret = itype;
-  if (host_integerp (TYPE_MAX_VALUE (itype), 1))
+  if (tree_fits_uhwi_p (TYPE_MAX_VALUE (itype)))
     ret = type_hash_canon (tree_low_cst (TYPE_MAX_VALUE (itype), 1), itype);
   if (precision <= MAX_INT_CACHED_PREC)
     nonstandard_integer_type_cache[precision + unsignedp] = ret;
@@ -8523,7 +8523,7 @@ get_narrower (tree op, int *unsignedp_ptr)
       && TREE_CODE (TREE_TYPE (op)) != FIXED_POINT_TYPE
       /* Ensure field is laid out already.  */
       && DECL_SIZE (TREE_OPERAND (op, 1)) != 0
-      && host_integerp (DECL_SIZE (TREE_OPERAND (op, 1)), 1))
+      && tree_fits_uhwi_p (DECL_SIZE (TREE_OPERAND (op, 1))))
     {
       unsigned HOST_WIDE_INT innerprec
 	= tree_low_cst (DECL_SIZE (TREE_OPERAND (op, 1)), 1);
diff --git a/gcc/tsan.c b/gcc/tsan.c
index 544d535f0cf218584fa2b101ef0ee98d0f7031e2..26833ee244bc1ed9059532b64d7a5f597cae4409 100644
--- a/gcc/tsan.c
+++ b/gcc/tsan.c
@@ -447,7 +447,7 @@ instrument_builtin_call (gimple_stmt_iterator *gsi)
 	  case check_last:
 	  case fetch_op:
 	    last_arg = gimple_call_arg (stmt, num - 1);
-	    if (!host_integerp (last_arg, 1)
+	    if (!tree_fits_uhwi_p (last_arg)
 		|| (unsigned HOST_WIDE_INT) tree_low_cst (last_arg, 1)
 		   > MEMMODEL_SEQ_CST)
 	      return;
@@ -519,11 +519,11 @@ instrument_builtin_call (gimple_stmt_iterator *gsi)
 	    gcc_assert (num == 6);
 	    for (j = 0; j < 6; j++)
 	      args[j] = gimple_call_arg (stmt, j);
-	    if (!host_integerp (args[4], 1)
+	    if (!tree_fits_uhwi_p (args[4])
 		|| (unsigned HOST_WIDE_INT) tree_low_cst (args[4], 1)
 		   > MEMMODEL_SEQ_CST)
 	      return;
-	    if (!host_integerp (args[5], 1)
+	    if (!tree_fits_uhwi_p (args[5])
 		|| (unsigned HOST_WIDE_INT) tree_low_cst (args[5], 1)
 		   > MEMMODEL_SEQ_CST)
 	      return;
diff --git a/gcc/ubsan.c b/gcc/ubsan.c
index 9dc19c9d29add73ab8d44e5ff5fa6539fefbddc8..c752a019589fd93e07bcd54d95bd31816b7a1b4e 100644
--- a/gcc/ubsan.c
+++ b/gcc/ubsan.c
@@ -233,7 +233,7 @@ ubsan_source_location (location_t loc)
 static unsigned short
 get_ubsan_type_info_for_type (tree type)
 {
-  gcc_assert (TYPE_SIZE (type) && host_integerp (TYPE_SIZE (type), 1));
+  gcc_assert (TYPE_SIZE (type) && tree_fits_uhwi_p (TYPE_SIZE (type)));
   int prec = exact_log2 (tree_low_cst (TYPE_SIZE (type), 1));
   gcc_assert (prec != -1);
   return (prec << 1) | !TYPE_UNSIGNED (type);
diff --git a/gcc/varasm.c b/gcc/varasm.c
index 3420e2205668c53101ce1a2b5bf944d6754a101e..d7930631f88b6c837aba7a852c64cbec3f051e5a 100644
--- a/gcc/varasm.c
+++ b/gcc/varasm.c
@@ -1136,7 +1136,7 @@ get_block_for_decl (tree decl)
      constant size.  */
   if (DECL_SIZE_UNIT (decl) == NULL)
     return NULL;
-  if (!host_integerp (DECL_SIZE_UNIT (decl), 1))
+  if (!tree_fits_uhwi_p (DECL_SIZE_UNIT (decl)))
     return NULL;
 
   /* Find out which section should contain DECL.  We cannot put it into