diff --git docs/ObjectiveCLiterals.rst docs/ObjectiveCLiterals.rst
index 8907c1e..4956760 100644
--- docs/ObjectiveCLiterals.rst
+++ docs/ObjectiveCLiterals.rst
@@ -119,8 +119,8 @@ Objective-C provides a new syntax for boxing C expressions:
 
     @( <expression> )
 
-Expressions of scalar (numeric, enumerated, BOOL) and C string pointer
-types are supported:
+Expressions of scalar (numeric, enumerated, BOOL), C string pointer
+and some C structures (via NSValue) are supported:
 
 .. code-block:: objc
 
@@ -136,6 +136,12 @@ types are supported:
     NSString *path = @(getenv("PATH"));       // [NSString stringWithUTF8String:(getenv("PATH"))]
     NSArray *pathComponents = [path componentsSeparatedByString:@":"];
 
+    // NS structs
+    NSValue *center = @(view.center);         // Point p = view.point;
+                                              // [NSValue valueWithBytes:&p objCType:@encode(Point)];
+    NSValue *frame = @(view.frame);           // Rect r = view.frame;
+                                              // [NSValue valueWithBytes:&r objCType:@encode(Rect)];
+
 Boxed Enums
 -----------
 
@@ -218,6 +224,42 @@ character data is valid. Passing ``NULL`` as the character pointer will
 raise an exception at runtime. When possible, the compiler will reject
 ``NULL`` character pointers used in boxed expressions.
 
+Boxed C Structures
+------------------
+
+Boxed expressions support construction of NSValue objects.
+It said that C structures can be used, the only requirement is:
+structure should be marked with ``objc_boxable`` attribute.
+To support older version of frameworks and/or third-party libraries
+you may need to add the attribute via ``typedef``.
+
+.. code-block:: objc
+
+    struct __attribute__((objc_boxable)) Point {
+        // ...
+    };
+
+    typedef struct __attribute__((objc_boxable)) _Size {
+        // ...
+    } Size;
+
+    typedef struct _Rect {
+        // ...
+    } Rect;
+
+    struct Point p;
+    NSValue *point = @(p);          // ok
+    Size s;
+    NSValue *size = @(s);           // ok
+
+    Rect r;
+    NSValue *bad_rect = @(r);       // error
+
+    typedef struct  _Rect Rect __attribute__((objc_boxable));
+
+    NSValue *good_rect = @(r);      // ok
+
+
 Container Literals
 ==================
 
@@ -539,6 +581,22 @@ checks. Here are examples of their use:
         }
     #endif
 
+    #if __has_attribute(objc_boxable)
+        typedef struct _Rect Rect __attribute__((objc_boxable));
+    #endif
+
+    #if __has_feature(objc_boxed_nsvalue_expressions)
+        CABasicAnimation animation = [CABasicAnimation animationWithKeyPath:@"position"];
+        animation.fromValue = @(layer.position);
+        animation.toValue = @(newPosition);
+        [layer addAnimation:animation forKey:@"move"];
+    #else
+        CABasicAnimation animation = [CABasicAnimation animationWithKeyPath:@"position"];
+        animation.fromValue = [NSValue valueWithCGPoint:layer.position];
+        animation.toValue = [NSValue valueWithCGPoint:newPosition];
+        [layer addAnimation:animation forKey:@"move"];
+    #endif
+
 Code can use also ``__has_feature(objc_bool)`` to check for the
 availability of numeric literals support. This checks for the new
 ``__objc_yes / __objc_no`` keywords, which enable the use of
diff --git include/clang/AST/ASTMutationListener.h include/clang/AST/ASTMutationListener.h
index 4f3acc3..1edc75e 100644
--- include/clang/AST/ASTMutationListener.h
+++ include/clang/AST/ASTMutationListener.h
@@ -14,6 +14,7 @@
 #define LLVM_CLANG_AST_ASTMUTATIONLISTENER_H
 
 namespace clang {
+  class Attr;
   class ClassTemplateDecl;
   class ClassTemplateSpecializationDecl;
   class CXXDestructorDecl;
@@ -29,6 +30,7 @@ namespace clang {
   class ObjCInterfaceDecl;
   class ObjCPropertyDecl;
   class QualType;
+  class RecordDecl;
   class TagDecl;
   class VarDecl;
   class VarTemplateDecl;
@@ -119,6 +121,14 @@ public:
   /// \param M The containing module in which the definition was made visible,
   ///        if any.
   virtual void RedefinedHiddenDefinition(const NamedDecl *D, Module *M) {}
+  
+  /// \bried An attribute was added to a RecordDecl
+  ///
+  /// \param Attr The attribute that was added to the Record
+  ///
+  /// \param Record The RecordDecl that got a new attribute
+  virtual void AddedAttributeToRecord(const Attr *Attr, 
+                                      const RecordDecl *Record) {}
 
   // NOTE: If new methods are added they should also be added to
   // MultiplexASTMutationListener.
diff --git include/clang/AST/ExprObjC.h include/clang/AST/ExprObjC.h
index f296e8f..899e648 100644
--- include/clang/AST/ExprObjC.h
+++ include/clang/AST/ExprObjC.h
@@ -86,7 +86,7 @@ public:
 };
 
 /// ObjCBoxedExpr - used for generalized expression boxing.
-/// as in: @(strdup("hello world")) or @(random())
+/// as in: @(strdup("hello world")), @(random()) or @(view.frame)
 /// Also used for boxing non-parenthesized numeric literals;
 /// as in: @42 or \@true (c++/objc++) or \@__yes (c/objc).
 class ObjCBoxedExpr : public Expr {
diff --git include/clang/AST/NSAPI.h include/clang/AST/NSAPI.h
index fc994c1..ce2c7ce 100644
--- include/clang/AST/NSAPI.h
+++ include/clang/AST/NSAPI.h
@@ -37,8 +37,9 @@ public:
     ClassId_NSMutableSet,
     ClassId_NSCountedSet,
     ClassId_NSMutableOrderedSet,
+    ClassId_NSValue
   };
-  static const unsigned NumClassIds = 10;
+  static const unsigned NumClassIds = 11;
 
   enum NSStringMethodKind {
     NSStr_stringWithString,
diff --git include/clang/AST/Type.h include/clang/AST/Type.h
index 8cd29b7..043d8e5 100644
--- include/clang/AST/Type.h
+++ include/clang/AST/Type.h
@@ -1564,6 +1564,7 @@ public:
   bool isRecordType() const;
   bool isClassType() const;
   bool isStructureType() const;
+  bool isObjCBoxableStructureType() const;
   bool isInterfaceType() const;
   bool isStructureOrClassType() const;
   bool isUnionType() const;
diff --git include/clang/Basic/Attr.td include/clang/Basic/Attr.td
index 4c0e56b..a3649d3 100644
--- include/clang/Basic/Attr.td
+++ include/clang/Basic/Attr.td
@@ -1108,6 +1108,13 @@ def ObjCRuntimeName : Attr {
   let Documentation = [ObjCRuntimeNameDocs];
 }
 
+def ObjCBoxable : Attr {
+  let Spellings = [GNU<"objc_boxable">];
+  let Subjects = SubjectList<[Struct, TypedefName], ErrorDiag,
+        "ExpectedStructOrUnionOrTypedef">;
+  let Documentation = [Undocumented];
+}
+
 def OptimizeNone : InheritableAttr {
   let Spellings = [GNU<"optnone">, CXX11<"clang", "optnone">];
   let Subjects = SubjectList<[Function, ObjCMethod]>;
diff --git include/clang/Basic/DiagnosticSemaKinds.td include/clang/Basic/DiagnosticSemaKinds.td
index 71cba01..1885bb3 100644
--- include/clang/Basic/DiagnosticSemaKinds.td
+++ include/clang/Basic/DiagnosticSemaKinds.td
@@ -2081,12 +2081,16 @@ def err_attr_objc_ownership_redundant : Error<
   "the type %0 is already explicitly ownership-qualified">;
 def err_undeclared_nsnumber : Error<
   "NSNumber must be available to use Objective-C literals">;
+def err_undeclared_nsvalue : Error<
+  "NSValue must be available to use Objective-C boxed expressions">;
 def err_invalid_nsnumber_type : Error<
   "%0 is not a valid literal type for NSNumber">;
 def err_undeclared_nsstring : Error<
   "cannot box a string value because NSString has not been declared">;
 def err_objc_illegal_boxed_expression_type : Error<
   "illegal type %0 used in a boxed expression">;
+def err_objc_non_trivially_copyable_boxed_expression_type : Error<
+  "non-trivially copyable type %0 cannot be used in a boxed expression">;
 def err_objc_incomplete_boxed_expression_type : Error<
   "incomplete type %0 used in a boxed expression">;
 def err_undeclared_nsarray : Error<
diff --git include/clang/Sema/Sema.h include/clang/Sema/Sema.h
index 691f21d..6527adc 100644
--- include/clang/Sema/Sema.h
+++ include/clang/Sema/Sema.h
@@ -653,9 +653,15 @@ public:
   /// \brief The declaration of the Objective-C NSNumber class.
   ObjCInterfaceDecl *NSNumberDecl;
 
+  /// \brief The declaration of the Objective-C NSValue class.
+  ObjCInterfaceDecl *NSValueDecl;
+
   /// \brief Pointer to NSNumber type (NSNumber *).
   QualType NSNumberPointer;
 
+  /// \brief Pointer to NSValue type (NSValue *).
+  QualType NSValuePointer;
+
   /// \brief The Objective-C NSNumber methods used to create NSNumber literals.
   ObjCMethodDecl *NSNumberLiteralMethods[NSAPI::NumNSNumberLiteralMethods];
 
@@ -668,6 +674,9 @@ public:
   /// \brief The declaration of the stringWithUTF8String: method.
   ObjCMethodDecl *StringWithUTF8StringMethod;
 
+  /// \brief The declaration of the valueWithBytes:objCType: method.
+  ObjCMethodDecl *ValueWithBytesObjCTypeMethod;
+
   /// \brief The declaration of the Objective-C NSArray class.
   ObjCInterfaceDecl *NSArrayDecl;
 
@@ -4930,9 +4939,9 @@ public:
 
   /// BuildObjCBoxedExpr - builds an ObjCBoxedExpr AST node for the
   /// '@' prefixed parenthesized expression. The type of the expression will
-  /// either be "NSNumber *" or "NSString *" depending on the type of
-  /// ValueType, which is allowed to be a built-in numeric type or
-  /// "char *" or "const char *".
+  /// either be "NSNumber *", "NSString *" or "NSValue *" depending on the type
+  /// of ValueType, which is allowed to be a built-in numeric type, "char *",
+  /// "const char *" or C structure with attribute 'objc_boxable'.
   ExprResult BuildObjCBoxedExpr(SourceRange SR, Expr *ValueExpr);
 
   ExprResult BuildObjCSubscriptExpression(SourceLocation RB, Expr *BaseExpr,
diff --git lib/AST/NSAPI.cpp lib/AST/NSAPI.cpp
index 2749100..a9b10ed 100644
--- lib/AST/NSAPI.cpp
+++ lib/AST/NSAPI.cpp
@@ -30,7 +30,8 @@ IdentifierInfo *NSAPI::getNSClassId(NSClassIdKindKind K) const {
     "NSNumber",
     "NSMutableSet",
     "NSCountedSet",
-    "NSMutableOrderedSet"
+    "NSMutableOrderedSet",
+    "NSValue"
   };
 
   if (!ClassIds[K])
diff --git lib/AST/Type.cpp lib/AST/Type.cpp
index 09bb769..aca6521 100644
--- lib/AST/Type.cpp
+++ lib/AST/Type.cpp
@@ -364,6 +364,11 @@ bool Type::isStructureType() const {
     return RT->getDecl()->isStruct();
   return false;
 }
+bool Type::isObjCBoxableStructureType() const {
+  if (const RecordType *RT = getAs<RecordType>())
+    return RT->getDecl()->hasAttr<ObjCBoxableAttr>();
+  return false;
+}
 bool Type::isInterfaceType() const {
   if (const RecordType *RT = getAs<RecordType>())
     return RT->getDecl()->isInterface();
diff --git lib/CodeGen/CGObjC.cpp lib/CodeGen/CGObjC.cpp
index 9981fcc..23ae79a 100644
--- lib/CodeGen/CGObjC.cpp
+++ lib/CodeGen/CGObjC.cpp
@@ -55,13 +55,15 @@ llvm::Value *CodeGenFunction::EmitObjCStringLiteral(const ObjCStringLiteral *E)
 
 /// EmitObjCBoxedExpr - This routine generates code to call
 /// the appropriate expression boxing method. This will either be
-/// one of +[NSNumber numberWith<Type>:], or +[NSString stringWithUTF8String:].
+/// one of +[NSNumber numberWith<Type>:], or +[NSString stringWithUTF8String:],
+/// or [NSValue valueWithBytes:objCType:].
 ///
 llvm::Value *
 CodeGenFunction::EmitObjCBoxedExpr(const ObjCBoxedExpr *E) {
   // Generate the correct selector for this literal's concrete type.
   // Get the method.
   const ObjCMethodDecl *BoxingMethod = E->getBoxingMethod();
+  const Expr *SubExpr = E->getSubExpr();
   assert(BoxingMethod && "BoxingMethod is null");
   assert(BoxingMethod->isClassMethod() && "BoxingMethod must be a class method");
   Selector Sel = BoxingMethod->getSelector();
@@ -73,8 +75,31 @@ CodeGenFunction::EmitObjCBoxedExpr(const ObjCBoxedExpr *E) {
   const ObjCInterfaceDecl *ClassDecl = BoxingMethod->getClassInterface();
   llvm::Value *Receiver = Runtime.GetClass(*this, ClassDecl);
 
+  const ParmVarDecl *argDecl = *BoxingMethod->param_begin();
+  QualType ArgQT = argDecl->getType().getUnqualifiedType();
+  RValue RV = EmitAnyExpr(SubExpr);
   CallArgList Args;
-  EmitCallArgs(Args, BoxingMethod, E->arg_begin(), E->arg_end());
+  Args.add(RV, ArgQT);
+  
+  // ObjCBoxedExpr supports boxing of structs and unions 
+  // via [NSValue valueWithBytes:objCType:]
+  if (const UnaryOperator *UO = 
+                              dyn_cast<UnaryOperator>(SubExpr->IgnoreCasts())) {
+    QualType ValueType(UO->getSubExpr()->IgnoreCasts()->getType());
+    if (ValueType->isObjCBoxableStructureType()) {
+
+      const ParmVarDecl *ArgDecl = *BoxingMethod->param_begin() + 1;
+      QualType ArgTy = ArgDecl->getType();
+      
+      std::string Str;
+      getContext().getObjCEncodingForType(ValueType, Str);
+
+      llvm::GlobalVariable *GV = CGM.GetAddrOfConstantCString(Str);
+      llvm::Value *Cast = Builder.CreateBitCast(GV, ConvertType(ArgTy));
+      
+      Args.add(RValue::get(Cast), ArgTy.getUnqualifiedType());
+    }
+  }
 
   RValue result = Runtime.GenerateMessageSend(
       *this, ReturnValueSlot(), BoxingMethod->getReturnType(), Sel, Receiver,
diff --git lib/Frontend/MultiplexConsumer.cpp lib/Frontend/MultiplexConsumer.cpp
index 219e949..1e482d4 100644
--- lib/Frontend/MultiplexConsumer.cpp
+++ lib/Frontend/MultiplexConsumer.cpp
@@ -14,6 +14,7 @@
 //===----------------------------------------------------------------------===//
 
 #include "clang/Frontend/MultiplexConsumer.h"
+#include "clang/AST/Attr.h"
 #include "clang/AST/ASTMutationListener.h"
 #include "clang/AST/DeclGroup.h"
 #include "clang/Serialization/ASTDeserializationListener.h"
@@ -112,6 +113,8 @@ public:
   void DeclarationMarkedUsed(const Decl *D) override;
   void DeclarationMarkedOpenMPThreadPrivate(const Decl *D) override;
   void RedefinedHiddenDefinition(const NamedDecl *D, Module *M) override;
+  void AddedAttributeToRecord(const Attr *Attr, 
+                              const RecordDecl *Record) override;
 
 private:
   std::vector<ASTMutationListener*> Listeners;
@@ -200,6 +203,13 @@ void MultiplexASTMutationListener::RedefinedHiddenDefinition(const NamedDecl *D,
   for (auto *L : Listeners)
     L->RedefinedHiddenDefinition(D, M);
 }
+  
+void MultiplexASTMutationListener::AddedAttributeToRecord(
+                                                    const Attr *Attr, 
+                                                    const RecordDecl *Record) {
+  for (auto *L : Listeners)
+    L->AddedAttributeToRecord(Attr, Record);
+}
 
 }  // end namespace clang
 
diff --git lib/Lex/PPMacroExpansion.cpp lib/Lex/PPMacroExpansion.cpp
index 0aaf3dd..3a79b56 100644
--- lib/Lex/PPMacroExpansion.cpp
+++ lib/Lex/PPMacroExpansion.cpp
@@ -1097,6 +1097,7 @@ static bool HasFeature(const Preprocessor &PP, const IdentifierInfo *II) {
       .Case("objc_array_literals", LangOpts.ObjC2)
       .Case("objc_dictionary_literals", LangOpts.ObjC2)
       .Case("objc_boxed_expressions", LangOpts.ObjC2)
+      .Case("objc_boxed_nsvalue_expressions", LangOpts.ObjC2)
       .Case("arc_cf_code_audited", true)
       .Case("objc_bridge_id", true)
       .Case("objc_bridge_id_on_typedefs", true)
diff --git lib/Sema/SemaDeclAttr.cpp lib/Sema/SemaDeclAttr.cpp
index ab3e0ab..cf0cb7b 100644
--- lib/Sema/SemaDeclAttr.cpp
+++ lib/Sema/SemaDeclAttr.cpp
@@ -20,6 +20,7 @@
 #include "clang/AST/Expr.h"
 #include "clang/AST/ExprCXX.h"
 #include "clang/AST/Mangle.h"
+#include "clang/AST/ASTMutationListener.h"
 #include "clang/Basic/CharInfo.h"
 #include "clang/Basic/SourceManager.h"
 #include "clang/Basic/TargetInfo.h"
@@ -3927,6 +3928,24 @@ static void handleObjCRuntimeName(Sema &S, Decl *D,
                                  Attr.getAttributeSpellingListIndex()));
 }
 
+static void handleObjCBoxable(Sema &S, Decl *D, const AttributeList &Attr) {
+  RecordDecl *RD = nullptr;
+  if (const TypedefDecl *TD = dyn_cast<TypedefDecl>(D)) {
+    const RecordType *RT = TD->getUnderlyingType()->getAs<RecordType>();
+    RD = RT->getDecl();
+  } else {
+    RD = dyn_cast<RecordDecl>(D);
+  }
+  if (RD) {
+    ObjCBoxableAttr *BoxableAttr = ::new (S.Context) 
+                          ObjCBoxableAttr(Attr.getRange(), S.Context,
+                                          Attr.getAttributeSpellingListIndex());
+    RD->addAttr(BoxableAttr);
+    if (ASTMutationListener *L = S.getASTMutationListener())
+      L->AddedAttributeToRecord(BoxableAttr, RD);
+  }
+}
+
 static void handleObjCOwnershipAttr(Sema &S, Decl *D,
                                     const AttributeList &Attr) {
   if (hasDeclarator(D)) return;
@@ -4695,6 +4714,10 @@ static void ProcessDeclAttribute(Sema &S, Scope *scope, Decl *D,
   case AttributeList::AT_ObjCRuntimeName:
     handleObjCRuntimeName(S, D, Attr);
     break;
+
+  case AttributeList::AT_ObjCBoxable:
+    handleObjCBoxable(S, D, Attr);
+    break;
           
   case AttributeList::AT_CFAuditedTransfer:
     handleCFAuditedTransferAttr(S, D, Attr);
diff --git lib/Sema/SemaExprObjC.cpp lib/Sema/SemaExprObjC.cpp
index 63b7485..42a29dd 100644
--- lib/Sema/SemaExprObjC.cpp
+++ lib/Sema/SemaExprObjC.cpp
@@ -574,6 +574,134 @@ ExprResult Sema::BuildObjCBoxedExpr(SourceRange SR, Expr *ValueExpr) {
     BoxingMethod = getNSNumberFactoryMethod(*this, SR.getBegin(),
                                             ET->getDecl()->getIntegerType());
     BoxedType = NSNumberPointer;
+  } else if (ValueType->isObjCBoxableStructureType()) {
+    // Support for structure types, that marked as objc_boxable
+    // struct __attribute__((objc_boxable)) s { ... };
+    
+    // Look up the NSValue class, if we haven't done so already. It's cached
+    // in the Sema instance.
+    if (!NSValueDecl) {
+      IdentifierInfo *NSValueId =
+      NSAPIObj->getNSClassId(NSAPI::ClassId_NSValue);
+      NamedDecl *IF = LookupSingleName(TUScope, NSValueId,
+                                       SR.getBegin(), Sema::LookupOrdinaryName);
+      NSValueDecl = dyn_cast_or_null<ObjCInterfaceDecl>(IF);
+      if (!NSValueDecl) {
+        if (getLangOpts().DebuggerObjCLiteral) {
+          // Create a stub definition of NSValue.
+          DeclContext *TU = Context.getTranslationUnitDecl();
+          NSValueDecl = ObjCInterfaceDecl::Create(Context, TU,
+                                                  SourceLocation(), NSValueId,
+                                                  nullptr, SourceLocation());
+        } else {
+          // Otherwise, require a declaration of NSValue.
+          Diag(SR.getBegin(), diag::err_undeclared_nsvalue);
+          return ExprError();
+        }
+      } else if (!NSValueDecl->hasDefinition()) {
+        Diag(SR.getBegin(), diag::err_undeclared_nsvalue);
+        return ExprError();
+      }
+      
+      // generate the pointer to NSValue type.
+      QualType NSValueObject = Context.getObjCInterfaceType(NSValueDecl);
+      NSValuePointer = Context.getObjCObjectPointerType(NSValueObject);
+    }
+    
+    if (!ValueWithBytesObjCTypeMethod) {
+      IdentifierInfo *II[] = {
+        &Context.Idents.get("valueWithBytes"),
+        &Context.Idents.get("objCType")
+      };
+      Selector ValueWithBytesObjCType = Context.Selectors.getSelector(2, II);
+      
+      // Look for the appropriate method within NSValue.
+      BoxingMethod = NSValueDecl->lookupClassMethod(ValueWithBytesObjCType);
+      if (!BoxingMethod && getLangOpts().DebuggerObjCLiteral) {
+        // Debugger needs to work even if NSString hasn't been defined.
+        TypeSourceInfo *ReturnTInfo = nullptr;
+        ObjCMethodDecl *M = ObjCMethodDecl::Create(
+                                               Context,
+                                               SourceLocation(),
+                                               SourceLocation(),
+                                               ValueWithBytesObjCType,
+                                               NSValuePointer,
+                                               ReturnTInfo,
+                                               NSValueDecl,
+                                               /*isInstance=*/false,
+                                               /*isVariadic=*/false,
+                                               /*isPropertyAccessor=*/false,
+                                               /*isImplicitlyDeclared=*/true,
+                                               /*isDefined=*/false,
+                                               ObjCMethodDecl::Required,
+                                               /*HasRelatedResultType=*/false);
+        
+        SmallVector<ParmVarDecl *, 2> Params;
+        
+        ParmVarDecl *bytes =
+        ParmVarDecl::Create(Context, M,
+                            SourceLocation(), SourceLocation(),
+                            &Context.Idents.get("bytes"),
+                            Context.VoidPtrTy.withConst(),
+                            /*TInfo=*/nullptr,
+                            SC_None, nullptr);
+        Params.push_back(bytes);
+        
+        QualType ConstCharType = Context.CharTy.withConst();
+        ParmVarDecl *type =
+        ParmVarDecl::Create(Context, M,
+                            SourceLocation(), SourceLocation(),
+                            &Context.Idents.get("type"),
+                            Context.getPointerType(ConstCharType),
+                            /*TInfo=*/nullptr,
+                            SC_None, nullptr);
+        Params.push_back(type);
+        
+        M->setMethodParams(Context, Params, None);
+        BoxingMethod = M;
+      }
+      
+      if (!validateBoxingMethod(*this, SR.getBegin(), NSValueDecl,
+                                ValueWithBytesObjCType, BoxingMethod))
+        return ExprError();
+      
+      ValueWithBytesObjCTypeMethod = BoxingMethod;
+    }
+    
+    if (getLangOpts().CPlusPlus && ValueExpr->isGLValue()) {
+      ExprResult Temp = PerformCopyInitialization(
+                            InitializedEntity::InitializeTemporary(ValueType),
+                            ValueExpr->getExprLoc(), ValueExpr);
+      if (Temp.isInvalid())
+        return ExprError();
+      ValueExpr = Temp.get();
+    }
+    
+    if (!ValueType.isTriviallyCopyableType(Context)) {
+      Diag(SR.getBegin(), 
+           diag::err_objc_non_trivially_copyable_boxed_expression_type)
+        << ValueType << ValueExpr->getSourceRange();
+      return ExprError();
+    }
+    
+    QualType ExprPtrType = Context.getPointerType(ValueExpr->getType());
+    SourceLocation ESL = ValueExpr->getSourceRange().getBegin();
+    UnaryOperator *UO = new (Context) UnaryOperator(ValueExpr, UO_AddrOf,
+                                                    ExprPtrType,
+                                                    VK_RValue, OK_Ordinary,
+                                                    ESL);
+    CXXCastPath Path;
+    QualType ConstVoidType = Context.getPointerType(Context.VoidTy.withConst());
+    ImplicitCastExpr *ICE = ImplicitCastExpr::Create(Context,
+                                                     ConstVoidType,
+                                                     CK_BitCast,
+                                                     UO,
+                                                     &Path,
+                                                     VK_RValue);
+    ValueExpr = ICE;
+    
+    BoxingMethod = ValueWithBytesObjCTypeMethod;
+    BoxedType = NSValuePointer;
   }
 
   if (!BoxingMethod) {
@@ -582,6 +710,8 @@ ExprResult Sema::BuildObjCBoxedExpr(SourceRange SR, Expr *ValueExpr) {
     return ExprError();
   }
   
+  DiagnoseUseOfDecl(BoxingMethod, SR.getBegin());
+  
   // Convert the expression to the type that the parameter requires.
   ParmVarDecl *ParamDecl = BoxingMethod->parameters()[0];
   InitializedEntity Entity = InitializedEntity::InitializeParameter(Context,
diff --git test/CodeGenObjC/Inputs/nsvalue-boxed-expressions-support.h test/CodeGenObjC/Inputs/nsvalue-boxed-expressions-support.h
new file mode 100644
index 0000000..3895c15
--- /dev/null
+++ test/CodeGenObjC/Inputs/nsvalue-boxed-expressions-support.h
@@ -0,0 +1,63 @@
+#ifndef NSVALUE_BOXED_EXPRESSIONS_SUPPORT_H
+#define NSVALUE_BOXED_EXPRESSIONS_SUPPORT_H
+
+#define BOXABLE __attribute__((objc_boxable))
+
+typedef unsigned long NSUInteger;
+typedef double CGFloat;
+
+typedef struct BOXABLE _NSRange {
+    NSUInteger location;
+    NSUInteger length;
+} NSRange;
+
+typedef struct BOXABLE _NSPoint {
+    CGFloat x;
+    CGFloat y;
+} NSPoint;
+
+typedef struct BOXABLE _NSSize {
+    CGFloat width;
+    CGFloat height;
+} NSSize;
+
+typedef struct BOXABLE _NSRect {
+    NSPoint origin;
+    NSSize size;
+} NSRect;
+
+struct CGPoint {
+  CGFloat x;
+  CGFloat y;
+};
+typedef struct CGPoint CGPoint BOXABLE;
+
+struct CGSize {
+  CGFloat width;
+  CGFloat height;
+};
+typedef struct CGSize CGSize BOXABLE;
+
+struct CGRect {
+  CGPoint origin;
+  CGSize size;
+};
+typedef struct CGRect CGRect BOXABLE;
+
+struct NSEdgeInsets {
+  CGFloat top;
+  CGFloat left;
+  CGFloat bottom;
+  CGFloat right;
+};
+typedef struct NSEdgeInsets NSEdgeInsets BOXABLE;
+
+@interface NSValue
+
++ (NSValue *)valueWithBytes:(const void *)value objCType:(const char *)type;
+
+@end
+
+NSRange getRange();
+
+#endif // NSVALUE_BOXED_EXPRESSIONS_SUPPORT_H
diff --git test/CodeGenObjC/nsvalue-objc-boxable-ios-arc.m test/CodeGenObjC/nsvalue-objc-boxable-ios-arc.m
new file mode 100644
index 0000000..1153c2f
--- /dev/null
+++ test/CodeGenObjC/nsvalue-objc-boxable-ios-arc.m
@@ -0,0 +1,115 @@
+// RUN: %clang_cc1 -I %S/Inputs -triple armv7-apple-ios8.0.0 -emit-llvm -fobjc-arc -O2 -disable-llvm-optzns -o - %s | FileCheck %s
+
+#import "nsvalue-boxed-expressions-support.h"
+
+// CHECK:      [[CLASS:@.*]]        = external global %struct._class_t
+// CHECK:      [[NSVALUE:@.*]]      = {{.*}}[[CLASS]]{{.*}}
+// CHECK:      [[RANGE_STR:.*]]     = {{.*}}_NSRange=II{{.*}}
+// CHECK:      [[METH:@.*]]         = private global{{.*}}valueWithBytes:objCType:{{.*}}
+// CHECK:      [[VALUE_SEL:@.*]]    = {{.*}}[[METH]]{{.*}}
+// CHECK:      [[POINT_STR:.*]]     = {{.*}}CGPoint=dd{{.*}}
+// CHECK:      [[SIZE_STR:.*]]      = {{.*}}CGSize=dd{{.*}}
+// CHECK:      [[RECT_STR:.*]]      = {{.*}}CGRect={CGPoint=dd}{CGSize=dd}}{{.*}}
+// CHECK:      [[EDGE_STR:.*]]      = {{.*}}NSEdgeInsets=dddd{{.*}}
+
+// CHECK-LABEL: define void @doRange()
+void doRange() {
+  // CHECK:      [[RANGE:%.*]]      = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[RANGE:%.*]]      = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[RANGE]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]   = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[RANGE_CAST:%.*]] = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      [[SEL:%.*]]        = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]       = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSRange ns_range = { .location = 0, .length = 42 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[RANGE_CAST]], i8* {{.*}}[[RANGE_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *range = @(ns_range);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doPoint()
+void doPoint() {
+  // CHECK:      [[POINT:%.*]]      = bitcast %struct.CGPoint* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[POINT:%.*]]      = bitcast %struct.CGPoint* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[POINT]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]   = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[POINT_CAST:%.*]] = bitcast %struct.CGPoint* {{.*}}
+  // CHECK:      [[SEL:%.*]]        = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]       = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  CGPoint cg_point = { .x = 42, .y = 24 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[POINT_CAST]], i8* {{.*}}[[POINT_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *point = @(cg_point);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doSize()
+void doSize() {
+  // CHECK:      [[SIZE:%.*]]      = bitcast %struct.CGSize* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[SIZE:%.*]]      = bitcast %struct.CGSize* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[SIZE]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[SIZE_CAST:%.*]] = bitcast %struct.CGSize* {{.*}}
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  CGSize cg_size = { .width = 42, .height = 24 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[SIZE_CAST]], i8* {{.*}}[[SIZE_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *size = @(cg_size);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doRect()
+void doRect() {
+  // CHECK:      [[RECT:%.*]]      = alloca %struct.CGRect{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[RECT_CAST:%.*]] = bitcast %struct.CGRect* [[RECT]] to i8*
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]{{.*}}
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  CGPoint cg_point = { .x = 42, .y = 24 };
+  CGSize cg_size = { .width = 42, .height = 24 };
+  CGRect cg_rect = { .origin = cg_point, .size = cg_size };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[RECT_CAST]], i8*{{.*}}[[RECT_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *rect = @(cg_rect);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doNSEdgeInsets()
+void doNSEdgeInsets() {
+  // CHECK:      [[EDGE:%.*]]      = alloca %struct.NSEdgeInsets{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[EDGE_CAST:%.*]] = bitcast %struct.NSEdgeInsets* {{.*}}
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSEdgeInsets ns_edge_insets;
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[EDGE_CAST]], i8*{{.*}}[[EDGE_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *edge_insets = @(ns_edge_insets);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doRangeRValue() 
+void doRangeRValue() {
+  // CHECK:     [[COERCE:%.*]]          = alloca %struct._NSRange{{.*}}
+  // CHECK:     [[RECV_PTR:%.*]]        = load {{.*}} [[NSVALUE]]
+  // CHECK:     call {{.*}} @getRange {{.*}} [[COERCE]]{{.*}}
+  // CHECK:     [[COERCE_CAST:%.*]]     = bitcast %struct._NSRange* [[COERCE]]{{.*}}
+  // CHECK:     [[SEL:%.*]]             = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:     [[RECV:%.*]]            = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  // CHECK:     call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[COERCE_CAST]], i8* {{.*}}[[RANGE_STR]]{{.*}})
+  // CHECK:     call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *range_rvalue = @(getRange());
+  // CHECK:     call void @objc_release
+  // CHECK:     ret void
+}
+
diff --git test/CodeGenObjC/nsvalue-objc-boxable-ios.m test/CodeGenObjC/nsvalue-objc-boxable-ios.m
new file mode 100644
index 0000000..582f17e
--- /dev/null
+++ test/CodeGenObjC/nsvalue-objc-boxable-ios.m
@@ -0,0 +1,103 @@
+// RUN: %clang_cc1 -I %S/Inputs -triple armv7-apple-ios8.0.0 -emit-llvm -O2 -disable-llvm-optzns -o - %s | FileCheck %s
+
+#import "nsvalue-boxed-expressions-support.h"
+
+// CHECK:      [[CLASS:@.*]]        = external global %struct._class_t
+// CHECK:      [[NSVALUE:@.*]]      = {{.*}}[[CLASS]]{{.*}}
+// CHECK:      [[RANGE_STR:.*]]     = {{.*}}_NSRange=II{{.*}}
+// CHECK:      [[METH:@.*]]         = private global{{.*}}valueWithBytes:objCType:{{.*}}
+// CHECK:      [[VALUE_SEL:@.*]]    = {{.*}}[[METH]]{{.*}}
+// CHECK:      [[POINT_STR:.*]]     = {{.*}}CGPoint=dd{{.*}}
+// CHECK:      [[SIZE_STR:.*]]      = {{.*}}CGSize=dd{{.*}}
+// CHECK:      [[RECT_STR:.*]]      = {{.*}}CGRect={CGPoint=dd}{CGSize=dd}}{{.*}}
+// CHECK:      [[EDGE_STR:.*]]      = {{.*}}NSEdgeInsets=dddd{{.*}}
+
+// CHECK-LABEL: define void @doRange()
+void doRange() {
+  // CHECK:      [[RANGE:%.*]]      = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[RANGE:%.*]]      = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[RANGE]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]   = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[RANGE_CAST:%.*]] = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      [[SEL:%.*]]        = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]       = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSRange ns_range = { .location = 0, .length = 42 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[RANGE_CAST]], i8* {{.*}}[[RANGE_STR]]{{.*}})
+  NSValue *range = @(ns_range);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doPoint()
+void doPoint() {
+  // CHECK:      [[POINT:%.*]]      = bitcast %struct.CGPoint* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[POINT:%.*]]      = bitcast %struct.CGPoint* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[POINT]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]   = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[POINT_CAST:%.*]] = bitcast %struct.CGPoint* {{.*}}
+  // CHECK:      [[SEL:%.*]]        = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]       = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  CGPoint cg_point = { .x = 42, .y = 24 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[POINT_CAST]], i8* {{.*}}[[POINT_STR]]{{.*}})
+  NSValue *point = @(cg_point);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doSize()
+void doSize() {
+  // CHECK:      [[SIZE:%.*]]      = bitcast %struct.CGSize* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[SIZE:%.*]]      = bitcast %struct.CGSize* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[SIZE]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[SIZE_CAST:%.*]] = bitcast %struct.CGSize* {{.*}}
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  CGSize cg_size = { .width = 42, .height = 24 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[SIZE_CAST]], i8* {{.*}}[[SIZE_STR]]{{.*}})
+  NSValue *size = @(cg_size);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doRect()
+void doRect() {
+  // CHECK:      [[RECT:%.*]]      = alloca %struct.CGRect{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[RECT_CAST:%.*]] = bitcast %struct.CGRect* [[RECT]] to i8*
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]{{.*}}
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  CGPoint cg_point = { .x = 42, .y = 24 };
+  CGSize cg_size = { .width = 42, .height = 24 };
+  CGRect cg_rect = { .origin = cg_point, .size = cg_size };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[RECT_CAST]], i8*{{.*}}[[RECT_STR]]{{.*}})
+  NSValue *rect = @(cg_rect);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doNSEdgeInsets()
+void doNSEdgeInsets() {
+  // CHECK:      [[EDGE:%.*]]      = alloca %struct.NSEdgeInsets{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[EDGE_CAST:%.*]] = bitcast %struct.NSEdgeInsets* {{.*}}
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSEdgeInsets ns_edge_insets;
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[EDGE_CAST]], i8*{{.*}}[[EDGE_STR]]{{.*}})
+  NSValue *edge_insets = @(ns_edge_insets);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doRangeRValue() 
+void doRangeRValue() {
+  // CHECK:     [[COERCE:%.*]]          = alloca %struct._NSRange{{.*}}
+  // CHECK:     [[RECV_PTR:%.*]]        = load {{.*}} [[NSVALUE]]
+  // CHECK:     call {{.*}} @getRange {{.*}} [[COERCE]]{{.*}}
+  // CHECK:     [[COERCE_CAST:%.*]]     = bitcast %struct._NSRange* [[COERCE]]{{.*}}
+  // CHECK:     [[SEL:%.*]]             = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:     [[RECV:%.*]]            = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  // CHECK:     call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[COERCE_CAST]], i8* {{.*}}[[RANGE_STR]]{{.*}})
+  NSValue *range_rvalue = @(getRange());
+  // CHECK: ret void
+}
+
diff --git test/CodeGenObjC/nsvalue-objc-boxable-mac-arc.m test/CodeGenObjC/nsvalue-objc-boxable-mac-arc.m
new file mode 100644
index 0000000..56da050
--- /dev/null
+++ test/CodeGenObjC/nsvalue-objc-boxable-mac-arc.m
@@ -0,0 +1,119 @@
+// RUN: %clang_cc1 -I %S/Inputs -triple x86_64-apple-macosx -emit-llvm -fobjc-arc -O2 -disable-llvm-optzns -o - %s | FileCheck %s
+
+#import "nsvalue-boxed-expressions-support.h"
+
+// CHECK:      [[CLASS:@.*]]        = external global %struct._class_t
+// CHECK:      [[NSVALUE:@.*]]      = {{.*}}[[CLASS]]{{.*}}
+// CHECK:      [[RANGE_STR:.*]]     = {{.*}}_NSRange=QQ{{.*}}
+// CHECK:      [[METH:@.*]]         = private global{{.*}}valueWithBytes:objCType:{{.*}}
+// CHECK:      [[VALUE_SEL:@.*]]    = {{.*}}[[METH]]{{.*}}
+// CHECK:      [[POINT_STR:.*]]     = {{.*}}_NSPoint=dd{{.*}}
+// CHECK:      [[SIZE_STR:.*]]      = {{.*}}_NSSize=dd{{.*}}
+// CHECK:      [[RECT_STR:.*]]      = {{.*}}_NSRect={_NSPoint=dd}{_NSSize=dd}}{{.*}}
+// CHECK:      [[EDGE_STR:.*]]      = {{.*}}NSEdgeInsets=dddd{{.*}}
+
+// CHECK-LABEL: define void @doRange()
+void doRange() {
+  // CHECK:      [[RANGE:%.*]]      = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[RANGE:%.*]]      = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[RANGE]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]   = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[RANGE_CAST:%.*]] = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      [[SEL:%.*]]        = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]       = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSRange ns_range = { .location = 0, .length = 42 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[RANGE_CAST]], i8* {{.*}}[[RANGE_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *range = @(ns_range);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doPoint()
+void doPoint() {
+  // CHECK:      [[POINT:%.*]]      = bitcast %struct._NSPoint* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[POINT:%.*]]      = bitcast %struct._NSPoint* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[POINT]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]   = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[POINT_CAST:%.*]] = bitcast %struct._NSPoint* {{.*}}
+  // CHECK:      [[SEL:%.*]]        = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]       = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSPoint ns_point = { .x = 42, .y = 24 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[POINT_CAST]], i8* {{.*}}[[POINT_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *point = @(ns_point);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doSize()
+void doSize() {
+  // CHECK:      [[SIZE:%.*]]      = bitcast %struct._NSSize* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[SIZE:%.*]]      = bitcast %struct._NSSize* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[SIZE]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[SIZE_CAST:%.*]] = bitcast %struct._NSSize* {{.*}}
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSSize ns_size = { .width = 42, .height = 24 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[SIZE_CAST]], i8* {{.*}}[[SIZE_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *size = @(ns_size);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doRect()
+void doRect() {
+  // CHECK:      [[RECT:%.*]]      = alloca %struct._NSRect{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[RECT_CAST:%.*]] = bitcast %struct._NSRect* [[RECT]] to i8*
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]{{.*}}
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSPoint ns_point = { .x = 42, .y = 24 };
+  NSSize ns_size = { .width = 42, .height = 24 };
+  NSRect ns_rect = { .origin = ns_point, .size = ns_size };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[RECT_CAST]], i8*{{.*}}[[RECT_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *rect = @(ns_rect);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doNSEdgeInsets()
+void doNSEdgeInsets() {
+  // CHECK:      [[EDGE:%.*]]      = alloca %struct.NSEdgeInsets{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[EDGE_CAST:%.*]] = bitcast %struct.NSEdgeInsets* {{.*}}
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSEdgeInsets ns_edge_insets;
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[EDGE_CAST]], i8*{{.*}}[[EDGE_STR]]{{.*}})
+  // CHECK:      call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *edge_insets = @(ns_edge_insets);
+  // CHECK:      call void @objc_release
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doRangeRValue() 
+void doRangeRValue() {
+  // CHECK:     [[COERCE:%.*]]          = alloca %struct._NSRange{{.*}}
+  // CHECK:     [[RECV_PTR:%.*]]        = load {{.*}} [[NSVALUE]]
+  // CHECK:     [[RVAL:%.*]]            = call {{.*}} @getRange()
+  // CHECK:     [[COERCE_CAST:%.*]]     = bitcast %struct._NSRange* [[COERCE]]{{.*}}
+  // CHECK:     [[COERCE_CAST_PTR:%.*]] = getelementptr {{.*}} [[COERCE_CAST]], {{.*}}
+  // CHECK:     [[EXTR_RVAL:%.*]]       = extractvalue {{.*}} [[RVAL]]{{.*}}
+  // CHECK:     store {{.*}}[[EXTR_RVAL]]{{.*}}[[COERCE_CAST_PTR]]{{.*}}
+  // CHECK:     [[COERCE_CAST:%.*]]     = bitcast %struct._NSRange* [[COERCE]]{{.*}}
+  // CHECK:     [[SEL:%.*]]             = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:     [[RECV:%.*]]            = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  // CHECK:     call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[COERCE_CAST]], i8* {{.*}}[[RANGE_STR]]{{.*}})
+  // CHECK:     call i8* @objc_retainAutoreleasedReturnValue
+  NSValue *range_rvalue = @(getRange());
+  // CHECK:     call void @objc_release
+  // CHECK:     ret void
+}
+
diff --git test/CodeGenObjC/nsvalue-objc-boxable-mac.m test/CodeGenObjC/nsvalue-objc-boxable-mac.m
new file mode 100644
index 0000000..695e934
--- /dev/null
+++ test/CodeGenObjC/nsvalue-objc-boxable-mac.m
@@ -0,0 +1,107 @@
+// RUN: %clang_cc1 -I %S/Inputs -triple x86_64-apple-macosx -emit-llvm -O2 -disable-llvm-optzns -o - %s | FileCheck %s
+
+#import "nsvalue-boxed-expressions-support.h"
+
+// CHECK:      [[CLASS:@.*]]        = external global %struct._class_t
+// CHECK:      [[NSVALUE:@.*]]      = {{.*}}[[CLASS]]{{.*}}
+// CHECK:      [[RANGE_STR:.*]]     = {{.*}}_NSRange=QQ{{.*}}
+// CHECK:      [[METH:@.*]]         = private global{{.*}}valueWithBytes:objCType:{{.*}}
+// CHECK:      [[VALUE_SEL:@.*]]    = {{.*}}[[METH]]{{.*}}
+// CHECK:      [[POINT_STR:.*]]     = {{.*}}_NSPoint=dd{{.*}}
+// CHECK:      [[SIZE_STR:.*]]      = {{.*}}_NSSize=dd{{.*}}
+// CHECK:      [[RECT_STR:.*]]      = {{.*}}_NSRect={_NSPoint=dd}{_NSSize=dd}}{{.*}}
+// CHECK:      [[EDGE_STR:.*]]      = {{.*}}NSEdgeInsets=dddd{{.*}}
+
+// CHECK-LABEL: define void @doRange()
+void doRange() {
+  // CHECK:      [[RANGE:%.*]]      = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[RANGE:%.*]]      = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[RANGE]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]   = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[RANGE_CAST:%.*]] = bitcast %struct._NSRange* {{.*}}
+  // CHECK:      [[SEL:%.*]]        = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]       = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSRange ns_range = { .location = 0, .length = 42 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[RANGE_CAST]], i8* {{.*}}[[RANGE_STR]]{{.*}})
+  NSValue *range = @(ns_range);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doPoint()
+void doPoint() {
+  // CHECK:      [[POINT:%.*]]      = bitcast %struct._NSPoint* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[POINT:%.*]]      = bitcast %struct._NSPoint* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[POINT]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]   = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[POINT_CAST:%.*]] = bitcast %struct._NSPoint* {{.*}}
+  // CHECK:      [[SEL:%.*]]        = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]       = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSPoint ns_point = { .x = 42, .y = 24 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[POINT_CAST]], i8* {{.*}}[[POINT_STR]]{{.*}})
+  NSValue *point = @(ns_point);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doSize()
+void doSize() {
+  // CHECK:      [[SIZE:%.*]]      = bitcast %struct._NSSize* {{.*}}
+  // CHECK:      call void @llvm.lifetime.start{{.*}}
+  // CHECK:      [[SIZE:%.*]]      = bitcast %struct._NSSize* {{.*}}
+  // CHECK:      call void @llvm.memcpy{{.*}}[[SIZE]]{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[SIZE_CAST:%.*]] = bitcast %struct._NSSize* {{.*}}
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSSize ns_size = { .width = 42, .height = 24 };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[SIZE_CAST]], i8* {{.*}}[[SIZE_STR]]{{.*}})
+  NSValue *size = @(ns_size);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doRect()
+void doRect() {
+  // CHECK:      [[RECT:%.*]]      = alloca %struct._NSRect{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[RECT_CAST:%.*]] = bitcast %struct._NSRect* [[RECT]] to i8*
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]{{.*}}
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSPoint ns_point = { .x = 42, .y = 24 };
+  NSSize ns_size = { .width = 42, .height = 24 };
+  NSRect ns_rect = { .origin = ns_point, .size = ns_size };
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[RECT_CAST]], i8*{{.*}}[[RECT_STR]]{{.*}})
+  NSValue *rect = @(ns_rect);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doNSEdgeInsets()
+void doNSEdgeInsets() {
+  // CHECK:      [[EDGE:%.*]]      = alloca %struct.NSEdgeInsets{{.*}}
+  // CHECK:      [[RECV_PTR:%.*]]  = load {{.*}} [[NSVALUE]]
+  // CHECK:      [[EDGE_CAST:%.*]] = bitcast %struct.NSEdgeInsets* {{.*}}
+  // CHECK:      [[SEL:%.*]]       = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:      [[RECV:%.*]]      = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  NSEdgeInsets ns_edge_insets;
+  // CHECK:      call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[EDGE_CAST]], i8*{{.*}}[[EDGE_STR]]{{.*}})
+  NSValue *edge_insets = @(ns_edge_insets);
+  // CHECK:      ret void
+}
+
+// CHECK-LABEL: define void @doRangeRValue() 
+void doRangeRValue() {
+  // CHECK:     [[COERCE:%.*]]          = alloca %struct._NSRange{{.*}}
+  // CHECK:     [[RECV_PTR:%.*]]        = load {{.*}} [[NSVALUE]]
+  // CHECK:     [[RVAL:%.*]]            = call {{.*}} @getRange()
+  // CHECK:     [[COERCE_CAST:%.*]]     = bitcast %struct._NSRange* [[COERCE]]{{.*}}
+  // CHECK:     [[COERCE_CAST_PTR:%.*]] = getelementptr {{.*}} [[COERCE_CAST]], {{.*}}
+  // CHECK:     [[EXTR_RVAL:%.*]]       = extractvalue {{.*}} [[RVAL]]{{.*}}
+  // CHECK:     store {{.*}}[[EXTR_RVAL]]{{.*}}[[COERCE_CAST_PTR]]{{.*}}
+  // CHECK:     [[COERCE_CAST:%.*]]     = bitcast %struct._NSRange* [[COERCE]]{{.*}}
+  // CHECK:     [[SEL:%.*]]             = load i8*, i8** [[VALUE_SEL]]
+  // CHECK:     [[RECV:%.*]]            = bitcast %struct._class_t* [[RECV_PTR]] to i8*
+  // CHECK:     call {{.*objc_msgSend.*}}(i8* [[RECV]], i8* [[SEL]], i8* [[COERCE_CAST]], i8* {{.*}}[[RANGE_STR]]{{.*}})
+  NSValue *range_rvalue = @(getRange());
+  // CHECK: ret void
+}
+
diff --git test/Index/annotate-literals.m test/Index/annotate-literals.m
index 20bfd2c..a1e4fb2 100644
--- test/Index/annotate-literals.m
+++ test/Index/annotate-literals.m
@@ -29,44 +29,61 @@ typedef unsigned char BOOL;
 + (id)dictionaryWithObjects:(const id [])objects forKeys:(const id [])keys count:(unsigned long)cnt;
 @end
 
-void test_literals(id k1, id o1, id k2, id o2, id k3) {
+@interface NSValue
++ (NSValue *)valueWithBytes:(const void *)value objCType:(const char *)type;
+@end
+
+typedef struct __attribute__((objc_boxable)) _c_struct {
+  int dummy;
+} c_struct;
+
+void test_literals(id k1, id o1, id k2, id o2, id k3, c_struct s) {
   id objects = @[ o1, o2 ];
   id dict = @{ k1 : o1,
                k2 : o2,
                k3 : @17 };
+  id val = @(s);
 }
 
 
-// RUN: c-index-test -test-annotate-tokens=%s:33:1:37:1 %s | FileCheck -check-prefix=CHECK-LITERALS %s
+// RUN: c-index-test -test-annotate-tokens=%s:41:1:46:1 %s | FileCheck -check-prefix=CHECK-LITERALS %s
 
-// CHECK-LITERALS: Identifier: "id" [33:3 - 33:5] TypeRef=id:0:0
-// CHECK-LITERALS: Identifier: "objects" [33:6 - 33:13] VarDecl=objects:33:6 (Definition)
-// CHECK-LITERALS: Punctuation: "=" [33:14 - 33:15] VarDecl=objects:33:6 (Definition)
-// CHECK-LITERALS: Punctuation: "@" [33:16 - 33:17] UnexposedExpr=
-// CHECK-LITERALS: Punctuation: "[" [33:17 - 33:18] UnexposedExpr=
-// CHECK-LITERALS: Identifier: "o1" [33:19 - 33:21] DeclRefExpr=o1:32:30
-// CHECK-LITERALS: Punctuation: "," [33:21 - 33:22] UnexposedExpr=
-// CHECK-LITERALS: Identifier: "o2" [33:23 - 33:25] DeclRefExpr=o2:32:44
-// CHECK-LITERALS: Punctuation: "]" [33:26 - 33:27] UnexposedExpr=
-// CHECK-LITERALS: Punctuation: ";" [33:27 - 33:28] DeclStmt=
-// CHECK-LITERALS: Identifier: "id" [34:3 - 34:5] TypeRef=id:0:0
-// CHECK-LITERALS: Identifier: "dict" [34:6 - 34:10] VarDecl=dict:34:6 (Definition)
-// CHECK-LITERALS: Punctuation: "=" [34:11 - 34:12] VarDecl=dict:34:6 (Definition)
-// CHECK-LITERALS: Punctuation: "@" [34:13 - 34:14] UnexposedExpr=
-// CHECK-LITERALS: Punctuation: "{" [34:14 - 34:15] UnexposedExpr=
-// CHECK-LITERALS: Identifier: "k1" [34:16 - 34:18] DeclRefExpr=k1:32:23
-// CHECK-LITERALS: Punctuation: ":" [34:19 - 34:20] UnexposedExpr=
-// CHECK-LITERALS: Identifier: "o1" [34:21 - 34:23] DeclRefExpr=o1:32:30
-// CHECK-LITERALS: Punctuation: "," [34:23 - 34:24] UnexposedExpr=
-// CHECK-LITERALS: Identifier: "k2" [35:16 - 35:18] DeclRefExpr=k2:32:37
-// CHECK-LITERALS: Punctuation: ":" [35:19 - 35:20] UnexposedExpr=
-// CHECK-LITERALS: Identifier: "o2" [35:21 - 35:23] DeclRefExpr=o2:32:44
-// CHECK-LITERALS: Punctuation: "," [35:23 - 35:24] UnexposedExpr=
-// CHECK-LITERALS: Identifier: "k3" [36:16 - 36:18] DeclRefExpr=k3:32:51
-// CHECK-LITERALS: Punctuation: ":" [36:19 - 36:20] UnexposedExpr=
-// CHECK-LITERALS: Punctuation: "@" [36:21 - 36:22] UnexposedExpr=
-// CHECK-LITERALS: Literal: "17" [36:22 - 36:24] IntegerLiteral=
-// CHECK-LITERALS: Punctuation: "}" [36:25 - 36:26] UnexposedExpr=
-// CHECK-LITERALS: Punctuation: ";" [36:26 - 36:27] DeclStmt=
-// CHECK-LITERALS: Punctuation: "}" [37:1 - 37:2] CompoundStmt=
+// CHECK-LITERALS: Identifier: "id" [41:3 - 41:5] TypeRef=id:0:0
+// CHECK-LITERALS: Identifier: "objects" [41:6 - 41:13] VarDecl=objects:41:6 (Definition)
+// CHECK-LITERALS: Punctuation: "=" [41:14 - 41:15] VarDecl=objects:41:6 (Definition)
+// CHECK-LITERALS: Punctuation: "@" [41:16 - 41:17] UnexposedExpr=
+// CHECK-LITERALS: Punctuation: "[" [41:17 - 41:18] UnexposedExpr=
+// CHECK-LITERALS: Identifier: "o1" [41:19 - 41:21] DeclRefExpr=o1:40:30
+// CHECK-LITERALS: Punctuation: "," [41:21 - 41:22] UnexposedExpr=
+// CHECK-LITERALS: Identifier: "o2" [41:23 - 41:25] DeclRefExpr=o2:40:44
+// CHECK-LITERALS: Punctuation: "]" [41:26 - 41:27] UnexposedExpr=
+// CHECK-LITERALS: Punctuation: ";" [41:27 - 41:28] DeclStmt=
+// CHECK-LITERALS: Identifier: "id" [42:3 - 42:5] TypeRef=id:0:0
+// CHECK-LITERALS: Identifier: "dict" [42:6 - 42:10] VarDecl=dict:42:6 (Definition)
+// CHECK-LITERALS: Punctuation: "=" [42:11 - 42:12] VarDecl=dict:42:6 (Definition)
+// CHECK-LITERALS: Punctuation: "@" [42:13 - 42:14] UnexposedExpr=
+// CHECK-LITERALS: Punctuation: "{" [42:14 - 42:15] UnexposedExpr=
+// CHECK-LITERALS: Identifier: "k1" [42:16 - 42:18] DeclRefExpr=k1:40:23
+// CHECK-LITERALS: Punctuation: ":" [42:19 - 42:20] UnexposedExpr=
+// CHECK-LITERALS: Identifier: "o1" [42:21 - 42:23] DeclRefExpr=o1:40:30
+// CHECK-LITERALS: Punctuation: "," [42:23 - 42:24] UnexposedExpr=
+// CHECK-LITERALS: Identifier: "k2" [43:16 - 43:18] DeclRefExpr=k2:40:37
+// CHECK-LITERALS: Punctuation: ":" [43:19 - 43:20] UnexposedExpr=
+// CHECK-LITERALS: Identifier: "o2" [43:21 - 43:23] DeclRefExpr=o2:40:44
+// CHECK-LITERALS: Punctuation: "," [43:23 - 43:24] UnexposedExpr=
+// CHECK-LITERALS: Identifier: "k3" [44:16 - 44:18] DeclRefExpr=k3:40:51
+// CHECK-LITERALS: Punctuation: ":" [44:19 - 44:20] UnexposedExpr=
+// CHECK-LITERALS: Punctuation: "@" [44:21 - 44:22] UnexposedExpr=
+// CHECK-LITERALS: Literal: "17" [44:22 - 44:24] IntegerLiteral=
+// CHECK-LITERALS: Punctuation: "}" [44:25 - 44:26] UnexposedExpr=
+// CHECK-LITERALS: Punctuation: ";" [44:26 - 44:27] DeclStmt=
+// CHECK-LITERALS: Identifier: "id" [45:3 - 45:5] TypeRef=id:0:0
+// CHECK-LITERALS: Identifier: "val" [45:6 - 45:9] VarDecl=val:45:6 (Definition)
+// CHECK-LITERALS: Punctuation: "=" [45:10 - 45:11] VarDecl=val:45:6 (Definition)
+// CHECK-LITERALS: Punctuation: "@" [45:12 - 45:13] UnexposedExpr=
+// CHECK-LITERALS: Punctuation: "(" [45:13 - 45:14] ParenExpr=
+// CHECK-LITERALS: Identifier: "s" [45:14 - 45:15] DeclRefExpr=s:40:64
+// CHECK-LITERALS: Punctuation: ")" [45:15 - 45:16] ParenExpr=
+// CHECK-LITERALS: Punctuation: ";" [45:16 - 45:17] DeclStmt=
+// CHECK-LITERALS: Punctuation: "}" [46:1 - 46:2] CompoundStmt=
 
diff --git test/Lexer/has_attribute_objc_boxable.m test/Lexer/has_attribute_objc_boxable.m
new file mode 100644
index 0000000..e172ecaba
--- /dev/null
+++ test/Lexer/has_attribute_objc_boxable.m
@@ -0,0 +1,8 @@
+// RUN: %clang_cc1 -E %s -o - | FileCheck %s
+
+#if __has_attribute(objc_boxable)
+int has_objc_boxable_attribute();
+#endif
+
+// CHECK: has_objc_boxable_attribute
+
diff --git test/Lexer/has_feature_boxed_nsvalue_expressions.m test/Lexer/has_feature_boxed_nsvalue_expressions.m
new file mode 100644
index 0000000..8c66bcb
--- /dev/null
+++ test/Lexer/has_feature_boxed_nsvalue_expressions.m
@@ -0,0 +1,8 @@
+// RUN: %clang_cc1 -E %s -o - | FileCheck %s
+
+#if __has_feature(objc_boxed_nsvalue_expressions)
+int has_objc_boxed_nsvalue_expressions();
+#endif
+
+// CHECK: has_objc_boxed_nsvalue_expressions
+
diff --git test/PCH/subscripting-literals.m test/PCH/subscripting-literals.m
index 1675373..725e580 100644
--- test/PCH/subscripting-literals.m
+++ test/PCH/subscripting-literals.m
@@ -30,6 +30,14 @@
 
 @class NSString;
 
+@interface NSValue
++ (NSValue *)valueWithBytes:(const void *)bytes objCType:(const char *)type;
+@end
+
+typedef struct __attribute__((objc_boxable)) _some_struct {
+  int dummy;
+} some_struct;
+
 id testArray(int idx, id p) {
   NSMutableArray *array;
   array[idx] = p;
@@ -44,4 +52,9 @@ void testDict(NSString *key, id newObject, id oldObject) {
   NSDictionary *dict = @{ key: newObject, key: oldObject };
 }
 
+void testBoxableValue() {
+  some_struct ss;
+  id value = @(ss);
+}
+
 #endif
diff --git test/SemaObjC/objc-boxed-expressions-nsvalue.m test/SemaObjC/objc-boxed-expressions-nsvalue.m
new file mode 100644
index 0000000..903b472
--- /dev/null
+++ test/SemaObjC/objc-boxed-expressions-nsvalue.m
@@ -0,0 +1,94 @@
+// RUN: %clang_cc1  -fsyntax-only -triple x86_64-apple-macosx10.9 -verify %s
+
+#define BOXABLE __attribute__((objc_boxable))
+
+typedef struct BOXABLE _NSPoint {
+  int dummy;
+} NSPoint;
+
+typedef struct BOXABLE _NSSize {
+  int dummy;
+} NSSize;
+
+typedef struct BOXABLE _NSRect {
+  int dummy;
+} NSRect;
+
+typedef struct BOXABLE _CGPoint {
+  int dummy;
+} CGPoint;
+
+typedef struct BOXABLE _CGSize {
+  int dummy;
+} CGSize;
+
+typedef struct BOXABLE _CGRect {
+  int dummy;
+} CGRect;
+
+typedef struct BOXABLE _NSRange {
+  int dummy;
+} NSRange;
+
+typedef struct BOXABLE _NSEdgeInsets {
+  int dummy;
+} NSEdgeInsets;
+
+typedef struct BOXABLE _NSEdgeInsets NSEdgeInsets;
+
+typedef struct _SomeStruct {
+  double d;
+} SomeStruct;
+
+void checkNSValueDiagnostic() {
+  NSRect rect;
+  id value = @(rect); // expected-error{{NSValue must be available to use Objective-C boxed expressions}}
+}
+
+@interface NSValue
++ (NSValue *)valueWithBytes:(const void *)value objCType:(const char *)type;
+@end
+
+int main() {
+  NSPoint ns_point;
+  id ns_point_value = @(ns_point);
+
+  NSSize ns_size;
+  id ns_size_value = @(ns_size);
+
+  NSRect ns_rect;
+  id ns_rect_value = @(ns_rect);
+
+  CGPoint cg_point;
+  id cg_point_value = @(cg_point);
+
+  CGSize cg_size;
+  id cg_size_value = @(cg_size);
+
+  CGRect cg_rect;
+  id cg_rect_value = @(cg_rect);
+
+  NSRange ns_range;
+  id ns_range_value = @(ns_range);
+
+  NSEdgeInsets edge_insets;
+  id edge_insets_object = @(edge_insets);
+
+  SomeStruct s;
+  id err = @(s); // expected-error{{illegal type 'SomeStruct' (aka 'struct _SomeStruct') used in a boxed expression}}
+}
+
+CGRect getRect() {
+  CGRect r;
+  return r;
+}
+
+SomeStruct getSomeStruct() {
+  SomeStruct s;
+  return s;
+}
+
+void rvalue() {
+  id rv_rect = @(getRect());
+  id rv_some_struct = @(getSomeStruct()); // expected-error {{illegal type 'SomeStruct' (aka 'struct _SomeStruct') used in a boxed expression}}
+}
diff --git test/SemaObjCXX/objc-boxed-expressions-nsvalue.mm test/SemaObjCXX/objc-boxed-expressions-nsvalue.mm
new file mode 100644
index 0000000..612cbb4
--- /dev/null
+++ test/SemaObjCXX/objc-boxed-expressions-nsvalue.mm
@@ -0,0 +1,103 @@
+// RUN: %clang_cc1  -fsyntax-only -triple x86_64-apple-macosx10.9 -verify %s
+
+#define BOXABLE __attribute__((objc_boxable))
+
+typedef struct BOXABLE _NSPoint {
+  int dummy;
+} NSPoint;
+
+typedef struct BOXABLE _NSSize {
+  int dummy;
+} NSSize;
+
+typedef struct BOXABLE _NSRect {
+  int dummy;
+} NSRect;
+
+typedef struct BOXABLE _CGPoint {
+  int dummy;
+} CGPoint;
+
+typedef struct BOXABLE _CGSize {
+  int dummy;
+} CGSize;
+
+typedef struct BOXABLE _CGRect {
+  int dummy;
+} CGRect;
+
+typedef struct BOXABLE _NSRange {
+  int dummy;
+} NSRange;
+
+typedef struct BOXABLE _NSEdgeInsets {
+  int dummy;
+} NSEdgeInsets;
+
+typedef struct BOXABLE _NSEdgeInsets NSEdgeInsets;
+
+typedef struct _SomeStruct {
+  double d;
+} SomeStruct;
+
+struct BOXABLE NonTriviallyCopyable {
+  double d;
+  NonTriviallyCopyable() {}
+  NonTriviallyCopyable(const NonTriviallyCopyable &obj) {}
+};
+
+void checkNSValueDiagnostic() {
+  NSRect rect;
+  id value = @(rect); // expected-error{{NSValue must be available to use Objective-C boxed expressions}}
+}
+
+@interface NSValue
++ (NSValue *)valueWithBytes:(const void *)value objCType:(const char *)type;
+@end
+
+int main() {
+  NSPoint ns_point;
+  id ns_point_value = @(ns_point);
+
+  NSSize ns_size;
+  id ns_size_value = @(ns_size);
+
+  NSRect ns_rect;
+  id ns_rect_value = @(ns_rect);
+
+  CGPoint cg_point;
+  id cg_point_value = @(cg_point);
+
+  CGSize cg_size;
+  id cg_size_value = @(cg_size);
+
+  CGRect cg_rect;
+  id cg_rect_value = @(cg_rect);
+
+  NSRange ns_range;
+  id ns_range_value = @(ns_range);
+
+  NSEdgeInsets edge_insets;
+  id edge_insets_object = @(edge_insets);
+
+  SomeStruct s;
+  id err = @(s); // expected-error{{illegal type 'SomeStruct' (aka '_SomeStruct') used in a boxed expression}}
+
+  NonTriviallyCopyable ntc;
+  id ntcErr = @(ntc); // expected-error{{non-trivially copyable type 'NonTriviallyCopyable' cannot be used in a boxed expression}}
+}
+
+CGRect getRect() {
+  CGRect r;
+  return r;
+}
+
+SomeStruct getSomeStruct() {
+  SomeStruct s;
+  return s;
+}
+
+void rvalue() {
+  id rv_rect = @(getRect());
+  id rv_some_struct = @(getSomeStruct()); // expected-error {{illegal type 'SomeStruct' (aka '_SomeStruct') used in a boxed expression}}
+}
