blob: af227d27d9208e33113675c3094c7734317842d0 [file] [log] [blame]
Peter Collingbourne6fa33f52013-08-07 22:47:18 +00001//===-- DataFlowSanitizer.cpp - dynamic data flow analysis ----------------===//
2//
3// The LLVM Compiler Infrastructure
4//
5// This file is distributed under the University of Illinois Open Source
6// License. See LICENSE.TXT for details.
7//
8//===----------------------------------------------------------------------===//
9/// \file
10/// This file is a part of DataFlowSanitizer, a generalised dynamic data flow
11/// analysis.
12///
13/// Unlike other Sanitizer tools, this tool is not designed to detect a specific
14/// class of bugs on its own. Instead, it provides a generic dynamic data flow
15/// analysis framework to be used by clients to help detect application-specific
16/// issues within their own code.
17///
18/// The analysis is based on automatic propagation of data flow labels (also
19/// known as taint labels) through a program as it performs computation. Each
20/// byte of application memory is backed by two bytes of shadow memory which
21/// hold the label. On Linux/x86_64, memory is laid out as follows:
22///
23/// +--------------------+ 0x800000000000 (top of memory)
24/// | application memory |
25/// +--------------------+ 0x700000008000 (kAppAddr)
26/// | |
27/// | unused |
28/// | |
29/// +--------------------+ 0x200200000000 (kUnusedAddr)
30/// | union table |
31/// +--------------------+ 0x200000000000 (kUnionTableAddr)
32/// | shadow memory |
33/// +--------------------+ 0x000000010000 (kShadowAddr)
34/// | reserved by kernel |
35/// +--------------------+ 0x000000000000
36///
37/// To derive a shadow memory address from an application memory address,
38/// bits 44-46 are cleared to bring the address into the range
39/// [0x000000008000,0x100000000000). Then the address is shifted left by 1 to
40/// account for the double byte representation of shadow labels and move the
41/// address into the shadow memory range. See the function
42/// DataFlowSanitizer::getShadowAddress below.
43///
44/// For more information, please refer to the design document:
45/// http://clang.llvm.org/docs/DataFlowSanitizerDesign.html
46
47#include "llvm/Transforms/Instrumentation.h"
48#include "llvm/ADT/DenseMap.h"
49#include "llvm/ADT/DenseSet.h"
50#include "llvm/ADT/DepthFirstIterator.h"
51#include "llvm/Analysis/ValueTracking.h"
52#include "llvm/IR/InlineAsm.h"
53#include "llvm/IR/IRBuilder.h"
54#include "llvm/IR/LLVMContext.h"
55#include "llvm/IR/MDBuilder.h"
56#include "llvm/IR/Type.h"
57#include "llvm/IR/Value.h"
58#include "llvm/InstVisitor.h"
59#include "llvm/Pass.h"
60#include "llvm/Support/CommandLine.h"
61#include "llvm/Transforms/Utils/BasicBlockUtils.h"
Peter Collingbourneaaae6e92013-08-09 21:42:53 +000062#include "llvm/Transforms/Utils/Local.h"
Peter Collingbourne6fa33f52013-08-07 22:47:18 +000063#include "llvm/Transforms/Utils/SpecialCaseList.h"
64#include <iterator>
65
66using namespace llvm;
67
68// The -dfsan-preserve-alignment flag controls whether this pass assumes that
69// alignment requirements provided by the input IR are correct. For example,
70// if the input IR contains a load with alignment 8, this flag will cause
71// the shadow load to have alignment 16. This flag is disabled by default as
72// we have unfortunately encountered too much code (including Clang itself;
73// see PR14291) which performs misaligned access.
74static cl::opt<bool> ClPreserveAlignment(
75 "dfsan-preserve-alignment",
76 cl::desc("respect alignment requirements provided by input IR"), cl::Hidden,
77 cl::init(false));
78
79// The greylist file controls how shadow parameters are passed.
80// The program acts as though every function in the greylist is passed
81// parameters with zero shadow and that its return value also has zero shadow.
82// This avoids the use of TLS or extra function parameters to pass shadow state
83// and essentially makes the function conform to the "native" (i.e. unsanitized)
84// ABI.
85static cl::opt<std::string> ClGreylistFile(
86 "dfsan-greylist",
87 cl::desc("File containing the list of functions with a native ABI"),
88 cl::Hidden);
89
90static cl::opt<bool> ClArgsABI(
91 "dfsan-args-abi",
92 cl::desc("Use the argument ABI rather than the TLS ABI"),
93 cl::Hidden);
94
95namespace {
96
97class DataFlowSanitizer : public ModulePass {
98 friend struct DFSanFunction;
99 friend class DFSanVisitor;
100
101 enum {
102 ShadowWidth = 16
103 };
104
105 enum InstrumentedABI {
106 IA_None,
107 IA_MemOnly,
108 IA_Args,
109 IA_TLS
110 };
111
112 DataLayout *DL;
113 Module *Mod;
114 LLVMContext *Ctx;
115 IntegerType *ShadowTy;
116 PointerType *ShadowPtrTy;
117 IntegerType *IntptrTy;
118 ConstantInt *ZeroShadow;
119 ConstantInt *ShadowPtrMask;
120 ConstantInt *ShadowPtrMul;
121 Constant *ArgTLS;
122 Constant *RetvalTLS;
123 void *(*GetArgTLSPtr)();
124 void *(*GetRetvalTLSPtr)();
125 Constant *GetArgTLS;
126 Constant *GetRetvalTLS;
127 FunctionType *DFSanUnionFnTy;
128 FunctionType *DFSanUnionLoadFnTy;
129 Constant *DFSanUnionFn;
130 Constant *DFSanUnionLoadFn;
131 MDNode *ColdCallWeights;
Alexey Samsonove39e1312013-08-12 11:46:09 +0000132 OwningPtr<SpecialCaseList> Greylist;
Peter Collingbourne6fa33f52013-08-07 22:47:18 +0000133 DenseMap<Value *, Function *> UnwrappedFnMap;
134
135 Value *getShadowAddress(Value *Addr, Instruction *Pos);
136 Value *combineShadows(Value *V1, Value *V2, Instruction *Pos);
137 FunctionType *getInstrumentedFunctionType(FunctionType *T);
138 InstrumentedABI getInstrumentedABI(Function *F);
139 InstrumentedABI getDefaultInstrumentedABI();
140
141public:
142 DataFlowSanitizer(void *(*getArgTLS)() = 0, void *(*getRetValTLS)() = 0);
143 static char ID;
144 bool doInitialization(Module &M);
145 bool runOnModule(Module &M);
146};
147
148struct DFSanFunction {
149 DataFlowSanitizer &DFS;
150 Function *F;
151 DataFlowSanitizer::InstrumentedABI IA;
152 Value *ArgTLSPtr;
153 Value *RetvalTLSPtr;
154 DenseMap<Value *, Value *> ValShadowMap;
155 DenseMap<AllocaInst *, AllocaInst *> AllocaShadowMap;
156 std::vector<std::pair<PHINode *, PHINode *> > PHIFixups;
157 DenseSet<Instruction *> SkipInsts;
158
159 DFSanFunction(DataFlowSanitizer &DFS, Function *F)
160 : DFS(DFS), F(F), IA(DFS.getInstrumentedABI(F)), ArgTLSPtr(0),
161 RetvalTLSPtr(0) {}
162 Value *getArgTLSPtr();
163 Value *getArgTLS(unsigned Index, Instruction *Pos);
164 Value *getRetvalTLS();
165 Value *getShadow(Value *V);
166 void setShadow(Instruction *I, Value *Shadow);
167 Value *combineOperandShadows(Instruction *Inst);
168 Value *loadShadow(Value *ShadowAddr, uint64_t Size, uint64_t Align,
169 Instruction *Pos);
170 void storeShadow(Value *Addr, uint64_t Size, uint64_t Align, Value *Shadow,
171 Instruction *Pos);
172};
173
174class DFSanVisitor : public InstVisitor<DFSanVisitor> {
175public:
176 DFSanFunction &DFSF;
177 DFSanVisitor(DFSanFunction &DFSF) : DFSF(DFSF) {}
178
179 void visitOperandShadowInst(Instruction &I);
180
181 void visitBinaryOperator(BinaryOperator &BO);
182 void visitCastInst(CastInst &CI);
183 void visitCmpInst(CmpInst &CI);
184 void visitGetElementPtrInst(GetElementPtrInst &GEPI);
185 void visitLoadInst(LoadInst &LI);
186 void visitStoreInst(StoreInst &SI);
187 void visitReturnInst(ReturnInst &RI);
188 void visitCallSite(CallSite CS);
189 void visitPHINode(PHINode &PN);
190 void visitExtractElementInst(ExtractElementInst &I);
191 void visitInsertElementInst(InsertElementInst &I);
192 void visitShuffleVectorInst(ShuffleVectorInst &I);
193 void visitExtractValueInst(ExtractValueInst &I);
194 void visitInsertValueInst(InsertValueInst &I);
195 void visitAllocaInst(AllocaInst &I);
196 void visitSelectInst(SelectInst &I);
197 void visitMemTransferInst(MemTransferInst &I);
198};
199
200}
201
202char DataFlowSanitizer::ID;
203INITIALIZE_PASS(DataFlowSanitizer, "dfsan",
204 "DataFlowSanitizer: dynamic data flow analysis.", false, false)
205
206ModulePass *llvm::createDataFlowSanitizerPass(void *(*getArgTLS)(),
207 void *(*getRetValTLS)()) {
208 return new DataFlowSanitizer(getArgTLS, getRetValTLS);
209}
210
211DataFlowSanitizer::DataFlowSanitizer(void *(*getArgTLS)(),
212 void *(*getRetValTLS)())
213 : ModulePass(ID), GetArgTLSPtr(getArgTLS), GetRetvalTLSPtr(getRetValTLS),
Alexey Samsonove39e1312013-08-12 11:46:09 +0000214 Greylist(SpecialCaseList::createOrDie(ClGreylistFile)) {}
Peter Collingbourne6fa33f52013-08-07 22:47:18 +0000215
216FunctionType *DataFlowSanitizer::getInstrumentedFunctionType(FunctionType *T) {
217 llvm::SmallVector<Type *, 4> ArgTypes;
218 std::copy(T->param_begin(), T->param_end(), std::back_inserter(ArgTypes));
219 for (unsigned i = 0, e = T->getNumParams(); i != e; ++i)
220 ArgTypes.push_back(ShadowTy);
221 if (T->isVarArg())
222 ArgTypes.push_back(ShadowPtrTy);
223 Type *RetType = T->getReturnType();
224 if (!RetType->isVoidTy())
225 RetType = StructType::get(RetType, ShadowTy, (Type *)0);
226 return FunctionType::get(RetType, ArgTypes, T->isVarArg());
227}
228
229bool DataFlowSanitizer::doInitialization(Module &M) {
230 DL = getAnalysisIfAvailable<DataLayout>();
231 if (!DL)
232 return false;
233
234 Mod = &M;
235 Ctx = &M.getContext();
236 ShadowTy = IntegerType::get(*Ctx, ShadowWidth);
237 ShadowPtrTy = PointerType::getUnqual(ShadowTy);
238 IntptrTy = DL->getIntPtrType(*Ctx);
239 ZeroShadow = ConstantInt::getSigned(ShadowTy, 0);
Peter Collingbourne46c72c72013-08-08 00:15:27 +0000240 ShadowPtrMask = ConstantInt::getSigned(IntptrTy, ~0x700000000000LL);
Peter Collingbourne6fa33f52013-08-07 22:47:18 +0000241 ShadowPtrMul = ConstantInt::getSigned(IntptrTy, ShadowWidth / 8);
242
243 Type *DFSanUnionArgs[2] = { ShadowTy, ShadowTy };
244 DFSanUnionFnTy =
245 FunctionType::get(ShadowTy, DFSanUnionArgs, /*isVarArg=*/ false);
246 Type *DFSanUnionLoadArgs[2] = { ShadowPtrTy, IntptrTy };
247 DFSanUnionLoadFnTy =
248 FunctionType::get(ShadowTy, DFSanUnionLoadArgs, /*isVarArg=*/ false);
249
250 if (GetArgTLSPtr) {
251 Type *ArgTLSTy = ArrayType::get(ShadowTy, 64);
252 ArgTLS = 0;
253 GetArgTLS = ConstantExpr::getIntToPtr(
254 ConstantInt::get(IntptrTy, uintptr_t(GetArgTLSPtr)),
255 PointerType::getUnqual(
256 FunctionType::get(PointerType::getUnqual(ArgTLSTy), (Type *)0)));
257 }
258 if (GetRetvalTLSPtr) {
259 RetvalTLS = 0;
260 GetRetvalTLS = ConstantExpr::getIntToPtr(
261 ConstantInt::get(IntptrTy, uintptr_t(GetRetvalTLSPtr)),
262 PointerType::getUnqual(
263 FunctionType::get(PointerType::getUnqual(ShadowTy), (Type *)0)));
264 }
265
266 ColdCallWeights = MDBuilder(*Ctx).createBranchWeights(1, 1000);
267 return true;
268}
269
270DataFlowSanitizer::InstrumentedABI
271DataFlowSanitizer::getInstrumentedABI(Function *F) {
Alexey Samsonove39e1312013-08-12 11:46:09 +0000272 if (Greylist->isIn(*F))
Peter Collingbourne6fa33f52013-08-07 22:47:18 +0000273 return IA_MemOnly;
274 else
275 return getDefaultInstrumentedABI();
276}
277
278DataFlowSanitizer::InstrumentedABI
279DataFlowSanitizer::getDefaultInstrumentedABI() {
280 return ClArgsABI ? IA_Args : IA_TLS;
281}
282
283bool DataFlowSanitizer::runOnModule(Module &M) {
284 if (!DL)
285 return false;
286
287 if (!GetArgTLSPtr) {
288 Type *ArgTLSTy = ArrayType::get(ShadowTy, 64);
289 ArgTLS = Mod->getOrInsertGlobal("__dfsan_arg_tls", ArgTLSTy);
290 if (GlobalVariable *G = dyn_cast<GlobalVariable>(ArgTLS))
291 G->setThreadLocalMode(GlobalVariable::InitialExecTLSModel);
292 }
293 if (!GetRetvalTLSPtr) {
294 RetvalTLS = Mod->getOrInsertGlobal("__dfsan_retval_tls", ShadowTy);
295 if (GlobalVariable *G = dyn_cast<GlobalVariable>(RetvalTLS))
296 G->setThreadLocalMode(GlobalVariable::InitialExecTLSModel);
297 }
298
299 DFSanUnionFn = Mod->getOrInsertFunction("__dfsan_union", DFSanUnionFnTy);
300 if (Function *F = dyn_cast<Function>(DFSanUnionFn)) {
301 F->addAttribute(AttributeSet::FunctionIndex, Attribute::ReadNone);
302 F->addAttribute(AttributeSet::ReturnIndex, Attribute::ZExt);
303 F->addAttribute(1, Attribute::ZExt);
304 F->addAttribute(2, Attribute::ZExt);
305 }
306 DFSanUnionLoadFn =
307 Mod->getOrInsertFunction("__dfsan_union_load", DFSanUnionLoadFnTy);
308 if (Function *F = dyn_cast<Function>(DFSanUnionLoadFn)) {
309 F->addAttribute(AttributeSet::ReturnIndex, Attribute::ZExt);
310 }
311
312 std::vector<Function *> FnsToInstrument;
313 for (Module::iterator i = M.begin(), e = M.end(); i != e; ++i) {
314 if (!i->isIntrinsic() && i != DFSanUnionFn && i != DFSanUnionLoadFn)
315 FnsToInstrument.push_back(&*i);
316 }
317
318 // First, change the ABI of every function in the module. Greylisted
319 // functions keep their original ABI and get a wrapper function.
320 for (std::vector<Function *>::iterator i = FnsToInstrument.begin(),
321 e = FnsToInstrument.end();
322 i != e; ++i) {
323 Function &F = **i;
324
325 FunctionType *FT = F.getFunctionType();
326 FunctionType *NewFT = getInstrumentedFunctionType(FT);
327 // If the function types are the same (i.e. void()), we don't need to do
328 // anything here.
329 if (FT != NewFT) {
330 switch (getInstrumentedABI(&F)) {
331 case IA_Args: {
332 Function *NewF = Function::Create(NewFT, F.getLinkage(), "", &M);
333 NewF->setCallingConv(F.getCallingConv());
334 NewF->setAttributes(F.getAttributes().removeAttributes(
335 *Ctx, AttributeSet::ReturnIndex,
336 AttributeFuncs::typeIncompatible(NewFT->getReturnType(),
337 AttributeSet::ReturnIndex)));
338 for (Function::arg_iterator FArg = F.arg_begin(),
339 NewFArg = NewF->arg_begin(),
340 FArgEnd = F.arg_end();
341 FArg != FArgEnd; ++FArg, ++NewFArg) {
342 FArg->replaceAllUsesWith(NewFArg);
343 }
344 NewF->getBasicBlockList().splice(NewF->begin(), F.getBasicBlockList());
345
346 for (Function::use_iterator ui = F.use_begin(), ue = F.use_end();
347 ui != ue;) {
348 BlockAddress *BA = dyn_cast<BlockAddress>(ui.getUse().getUser());
349 ++ui;
350 if (BA) {
351 BA->replaceAllUsesWith(
352 BlockAddress::get(NewF, BA->getBasicBlock()));
353 delete BA;
354 }
355 }
356 F.replaceAllUsesWith(
357 ConstantExpr::getBitCast(NewF, PointerType::getUnqual(FT)));
358 NewF->takeName(&F);
359 F.eraseFromParent();
360 *i = NewF;
361 break;
362 }
363 case IA_MemOnly: {
364 assert(!FT->isVarArg() && "varargs not handled here yet");
365 assert(getDefaultInstrumentedABI() == IA_Args);
366 Function *NewF =
367 Function::Create(NewFT, GlobalValue::LinkOnceODRLinkage,
368 std::string("dfsw$") + F.getName(), &M);
369 NewF->setCallingConv(F.getCallingConv());
370 NewF->setAttributes(F.getAttributes());
371
372 BasicBlock *BB = BasicBlock::Create(*Ctx, "entry", NewF);
373 std::vector<Value *> Args;
374 unsigned n = FT->getNumParams();
375 for (Function::arg_iterator i = NewF->arg_begin(); n != 0; ++i, --n)
376 Args.push_back(&*i);
377 CallInst *CI = CallInst::Create(&F, Args, "", BB);
378 if (FT->getReturnType()->isVoidTy())
379 ReturnInst::Create(*Ctx, BB);
380 else {
381 Value *InsVal = InsertValueInst::Create(
382 UndefValue::get(NewFT->getReturnType()), CI, 0, "", BB);
383 Value *InsShadow =
384 InsertValueInst::Create(InsVal, ZeroShadow, 1, "", BB);
385 ReturnInst::Create(*Ctx, InsShadow, BB);
386 }
387
388 Value *WrappedFnCst =
389 ConstantExpr::getBitCast(NewF, PointerType::getUnqual(FT));
390 F.replaceAllUsesWith(WrappedFnCst);
391 UnwrappedFnMap[WrappedFnCst] = &F;
392 break;
393 }
394 default:
395 break;
396 }
397 }
398 }
399
400 for (std::vector<Function *>::iterator i = FnsToInstrument.begin(),
401 e = FnsToInstrument.end();
402 i != e; ++i) {
403 if ((*i)->isDeclaration())
404 continue;
405
Peter Collingbourneaaae6e92013-08-09 21:42:53 +0000406 removeUnreachableBlocks(**i);
407
Peter Collingbourne6fa33f52013-08-07 22:47:18 +0000408 DFSanFunction DFSF(*this, *i);
409
410 // DFSanVisitor may create new basic blocks, which confuses df_iterator.
411 // Build a copy of the list before iterating over it.
412 llvm::SmallVector<BasicBlock *, 4> BBList;
413 std::copy(df_begin(&(*i)->getEntryBlock()), df_end(&(*i)->getEntryBlock()),
414 std::back_inserter(BBList));
415
416 for (llvm::SmallVector<BasicBlock *, 4>::iterator i = BBList.begin(),
417 e = BBList.end();
418 i != e; ++i) {
419 Instruction *Inst = &(*i)->front();
420 while (1) {
421 // DFSanVisitor may split the current basic block, changing the current
422 // instruction's next pointer and moving the next instruction to the
423 // tail block from which we should continue.
424 Instruction *Next = Inst->getNextNode();
Peter Collingbournea90d91f2013-08-12 22:38:39 +0000425 // DFSanVisitor may delete Inst, so keep track of whether it was a
426 // terminator.
427 bool IsTerminator = isa<TerminatorInst>(Inst);
Peter Collingbourne6fa33f52013-08-07 22:47:18 +0000428 if (!DFSF.SkipInsts.count(Inst))
429 DFSanVisitor(DFSF).visit(Inst);
Peter Collingbournea90d91f2013-08-12 22:38:39 +0000430 if (IsTerminator)
Peter Collingbourne6fa33f52013-08-07 22:47:18 +0000431 break;
432 Inst = Next;
433 }
434 }
435
436 for (std::vector<std::pair<PHINode *, PHINode *> >::iterator
437 i = DFSF.PHIFixups.begin(),
438 e = DFSF.PHIFixups.end();
439 i != e; ++i) {
440 for (unsigned val = 0, n = i->first->getNumIncomingValues(); val != n;
441 ++val) {
442 i->second->setIncomingValue(
443 val, DFSF.getShadow(i->first->getIncomingValue(val)));
444 }
445 }
446 }
447
448 return false;
449}
450
451Value *DFSanFunction::getArgTLSPtr() {
452 if (ArgTLSPtr)
453 return ArgTLSPtr;
454 if (DFS.ArgTLS)
455 return ArgTLSPtr = DFS.ArgTLS;
456
457 IRBuilder<> IRB(F->getEntryBlock().begin());
458 return ArgTLSPtr = IRB.CreateCall(DFS.GetArgTLS);
459}
460
461Value *DFSanFunction::getRetvalTLS() {
462 if (RetvalTLSPtr)
463 return RetvalTLSPtr;
464 if (DFS.RetvalTLS)
465 return RetvalTLSPtr = DFS.RetvalTLS;
466
467 IRBuilder<> IRB(F->getEntryBlock().begin());
468 return RetvalTLSPtr = IRB.CreateCall(DFS.GetRetvalTLS);
469}
470
471Value *DFSanFunction::getArgTLS(unsigned Idx, Instruction *Pos) {
472 IRBuilder<> IRB(Pos);
473 return IRB.CreateConstGEP2_64(getArgTLSPtr(), 0, Idx);
474}
475
476Value *DFSanFunction::getShadow(Value *V) {
477 if (!isa<Argument>(V) && !isa<Instruction>(V))
478 return DFS.ZeroShadow;
479 Value *&Shadow = ValShadowMap[V];
480 if (!Shadow) {
481 if (Argument *A = dyn_cast<Argument>(V)) {
482 switch (IA) {
483 case DataFlowSanitizer::IA_TLS: {
484 Value *ArgTLSPtr = getArgTLSPtr();
485 Instruction *ArgTLSPos =
486 DFS.ArgTLS ? &*F->getEntryBlock().begin()
487 : cast<Instruction>(ArgTLSPtr)->getNextNode();
488 IRBuilder<> IRB(ArgTLSPos);
489 Shadow = IRB.CreateLoad(getArgTLS(A->getArgNo(), ArgTLSPos));
490 break;
491 }
492 case DataFlowSanitizer::IA_Args: {
493 unsigned ArgIdx = A->getArgNo() + F->getArgumentList().size() / 2;
494 Function::arg_iterator i = F->arg_begin();
495 while (ArgIdx--)
496 ++i;
497 Shadow = i;
498 break;
499 }
500 default:
501 Shadow = DFS.ZeroShadow;
502 break;
503 }
504 } else {
505 Shadow = DFS.ZeroShadow;
506 }
507 }
508 return Shadow;
509}
510
511void DFSanFunction::setShadow(Instruction *I, Value *Shadow) {
512 assert(!ValShadowMap.count(I));
513 assert(Shadow->getType() == DFS.ShadowTy);
514 ValShadowMap[I] = Shadow;
515}
516
517Value *DataFlowSanitizer::getShadowAddress(Value *Addr, Instruction *Pos) {
518 assert(Addr != RetvalTLS && "Reinstrumenting?");
519 IRBuilder<> IRB(Pos);
520 return IRB.CreateIntToPtr(
521 IRB.CreateMul(
522 IRB.CreateAnd(IRB.CreatePtrToInt(Addr, IntptrTy), ShadowPtrMask),
523 ShadowPtrMul),
524 ShadowPtrTy);
525}
526
527// Generates IR to compute the union of the two given shadows, inserting it
528// before Pos. Returns the computed union Value.
529Value *DataFlowSanitizer::combineShadows(Value *V1, Value *V2,
530 Instruction *Pos) {
531 if (V1 == ZeroShadow)
532 return V2;
533 if (V2 == ZeroShadow)
534 return V1;
535 if (V1 == V2)
536 return V1;
537 IRBuilder<> IRB(Pos);
538 BasicBlock *Head = Pos->getParent();
539 Value *Ne = IRB.CreateICmpNE(V1, V2);
540 Instruction *NeInst = dyn_cast<Instruction>(Ne);
541 if (NeInst) {
542 BranchInst *BI = cast<BranchInst>(SplitBlockAndInsertIfThen(
543 NeInst, /*Unreachable=*/ false, ColdCallWeights));
544 IRBuilder<> ThenIRB(BI);
545 CallInst *Call = ThenIRB.CreateCall2(DFSanUnionFn, V1, V2);
546 Call->addAttribute(AttributeSet::ReturnIndex, Attribute::ZExt);
547 Call->addAttribute(1, Attribute::ZExt);
548 Call->addAttribute(2, Attribute::ZExt);
549
550 BasicBlock *Tail = BI->getSuccessor(0);
551 PHINode *Phi = PHINode::Create(ShadowTy, 2, "", Tail->begin());
552 Phi->addIncoming(Call, Call->getParent());
553 Phi->addIncoming(ZeroShadow, Head);
554 Pos = Phi;
555 return Phi;
556 } else {
557 assert(0 && "todo");
558 return 0;
559 }
560}
561
562// A convenience function which folds the shadows of each of the operands
563// of the provided instruction Inst, inserting the IR before Inst. Returns
564// the computed union Value.
565Value *DFSanFunction::combineOperandShadows(Instruction *Inst) {
566 if (Inst->getNumOperands() == 0)
567 return DFS.ZeroShadow;
568
569 Value *Shadow = getShadow(Inst->getOperand(0));
570 for (unsigned i = 1, n = Inst->getNumOperands(); i != n; ++i) {
571 Shadow = DFS.combineShadows(Shadow, getShadow(Inst->getOperand(i)), Inst);
572 }
573 return Shadow;
574}
575
576void DFSanVisitor::visitOperandShadowInst(Instruction &I) {
577 Value *CombinedShadow = DFSF.combineOperandShadows(&I);
578 DFSF.setShadow(&I, CombinedShadow);
579}
580
581// Generates IR to load shadow corresponding to bytes [Addr, Addr+Size), where
582// Addr has alignment Align, and take the union of each of those shadows.
583Value *DFSanFunction::loadShadow(Value *Addr, uint64_t Size, uint64_t Align,
584 Instruction *Pos) {
585 if (AllocaInst *AI = dyn_cast<AllocaInst>(Addr)) {
586 llvm::DenseMap<AllocaInst *, AllocaInst *>::iterator i =
587 AllocaShadowMap.find(AI);
588 if (i != AllocaShadowMap.end()) {
589 IRBuilder<> IRB(Pos);
590 return IRB.CreateLoad(i->second);
591 }
592 }
593
594 uint64_t ShadowAlign = Align * DFS.ShadowWidth / 8;
595 SmallVector<Value *, 2> Objs;
596 GetUnderlyingObjects(Addr, Objs, DFS.DL);
597 bool AllConstants = true;
598 for (SmallVector<Value *, 2>::iterator i = Objs.begin(), e = Objs.end();
599 i != e; ++i) {
600 if (isa<Function>(*i) || isa<BlockAddress>(*i))
601 continue;
602 if (isa<GlobalVariable>(*i) && cast<GlobalVariable>(*i)->isConstant())
603 continue;
604
605 AllConstants = false;
606 break;
607 }
608 if (AllConstants)
609 return DFS.ZeroShadow;
610
611 Value *ShadowAddr = DFS.getShadowAddress(Addr, Pos);
612 switch (Size) {
613 case 0:
614 return DFS.ZeroShadow;
615 case 1: {
616 LoadInst *LI = new LoadInst(ShadowAddr, "", Pos);
617 LI->setAlignment(ShadowAlign);
618 return LI;
619 }
620 case 2: {
621 IRBuilder<> IRB(Pos);
622 Value *ShadowAddr1 =
623 IRB.CreateGEP(ShadowAddr, ConstantInt::get(DFS.IntptrTy, 1));
624 return DFS.combineShadows(IRB.CreateAlignedLoad(ShadowAddr, ShadowAlign),
625 IRB.CreateAlignedLoad(ShadowAddr1, ShadowAlign),
626 Pos);
627 }
628 }
629 if (Size % (64 / DFS.ShadowWidth) == 0) {
630 // Fast path for the common case where each byte has identical shadow: load
631 // shadow 64 bits at a time, fall out to a __dfsan_union_load call if any
632 // shadow is non-equal.
633 BasicBlock *FallbackBB = BasicBlock::Create(*DFS.Ctx, "", F);
634 IRBuilder<> FallbackIRB(FallbackBB);
635 CallInst *FallbackCall = FallbackIRB.CreateCall2(
636 DFS.DFSanUnionLoadFn, ShadowAddr, ConstantInt::get(DFS.IntptrTy, Size));
637 FallbackCall->addAttribute(AttributeSet::ReturnIndex, Attribute::ZExt);
638
639 // Compare each of the shadows stored in the loaded 64 bits to each other,
640 // by computing (WideShadow rotl ShadowWidth) == WideShadow.
641 IRBuilder<> IRB(Pos);
642 Value *WideAddr =
643 IRB.CreateBitCast(ShadowAddr, Type::getInt64PtrTy(*DFS.Ctx));
644 Value *WideShadow = IRB.CreateAlignedLoad(WideAddr, ShadowAlign);
645 Value *TruncShadow = IRB.CreateTrunc(WideShadow, DFS.ShadowTy);
646 Value *ShlShadow = IRB.CreateShl(WideShadow, DFS.ShadowWidth);
647 Value *ShrShadow = IRB.CreateLShr(WideShadow, 64 - DFS.ShadowWidth);
648 Value *RotShadow = IRB.CreateOr(ShlShadow, ShrShadow);
649 Value *ShadowsEq = IRB.CreateICmpEQ(WideShadow, RotShadow);
650
651 BasicBlock *Head = Pos->getParent();
652 BasicBlock *Tail = Head->splitBasicBlock(Pos);
653 // In the following code LastBr will refer to the previous basic block's
654 // conditional branch instruction, whose true successor is fixed up to point
655 // to the next block during the loop below or to the tail after the final
656 // iteration.
657 BranchInst *LastBr = BranchInst::Create(FallbackBB, FallbackBB, ShadowsEq);
658 ReplaceInstWithInst(Head->getTerminator(), LastBr);
659
660 for (uint64_t Ofs = 64 / DFS.ShadowWidth; Ofs != Size;
661 Ofs += 64 / DFS.ShadowWidth) {
662 BasicBlock *NextBB = BasicBlock::Create(*DFS.Ctx, "", F);
663 IRBuilder<> NextIRB(NextBB);
664 WideAddr = NextIRB.CreateGEP(WideAddr, ConstantInt::get(DFS.IntptrTy, 1));
665 Value *NextWideShadow = NextIRB.CreateAlignedLoad(WideAddr, ShadowAlign);
666 ShadowsEq = NextIRB.CreateICmpEQ(WideShadow, NextWideShadow);
667 LastBr->setSuccessor(0, NextBB);
668 LastBr = NextIRB.CreateCondBr(ShadowsEq, FallbackBB, FallbackBB);
669 }
670
671 LastBr->setSuccessor(0, Tail);
672 FallbackIRB.CreateBr(Tail);
673 PHINode *Shadow = PHINode::Create(DFS.ShadowTy, 2, "", &Tail->front());
674 Shadow->addIncoming(FallbackCall, FallbackBB);
675 Shadow->addIncoming(TruncShadow, LastBr->getParent());
676 return Shadow;
677 }
678
679 IRBuilder<> IRB(Pos);
680 CallInst *FallbackCall = IRB.CreateCall2(
681 DFS.DFSanUnionLoadFn, ShadowAddr, ConstantInt::get(DFS.IntptrTy, Size));
682 FallbackCall->addAttribute(AttributeSet::ReturnIndex, Attribute::ZExt);
683 return FallbackCall;
684}
685
686void DFSanVisitor::visitLoadInst(LoadInst &LI) {
687 uint64_t Size = DFSF.DFS.DL->getTypeStoreSize(LI.getType());
688 uint64_t Align;
689 if (ClPreserveAlignment) {
690 Align = LI.getAlignment();
691 if (Align == 0)
692 Align = DFSF.DFS.DL->getABITypeAlignment(LI.getType());
693 } else {
694 Align = 1;
695 }
696 IRBuilder<> IRB(&LI);
697 Value *LoadedShadow =
698 DFSF.loadShadow(LI.getPointerOperand(), Size, Align, &LI);
699 Value *PtrShadow = DFSF.getShadow(LI.getPointerOperand());
700 DFSF.setShadow(&LI, DFSF.DFS.combineShadows(LoadedShadow, PtrShadow, &LI));
701}
702
703void DFSanFunction::storeShadow(Value *Addr, uint64_t Size, uint64_t Align,
704 Value *Shadow, Instruction *Pos) {
705 if (AllocaInst *AI = dyn_cast<AllocaInst>(Addr)) {
706 llvm::DenseMap<AllocaInst *, AllocaInst *>::iterator i =
707 AllocaShadowMap.find(AI);
708 if (i != AllocaShadowMap.end()) {
709 IRBuilder<> IRB(Pos);
710 IRB.CreateStore(Shadow, i->second);
711 return;
712 }
713 }
714
715 uint64_t ShadowAlign = Align * DFS.ShadowWidth / 8;
716 IRBuilder<> IRB(Pos);
717 Value *ShadowAddr = DFS.getShadowAddress(Addr, Pos);
718 if (Shadow == DFS.ZeroShadow) {
719 IntegerType *ShadowTy = IntegerType::get(*DFS.Ctx, Size * DFS.ShadowWidth);
720 Value *ExtZeroShadow = ConstantInt::get(ShadowTy, 0);
721 Value *ExtShadowAddr =
722 IRB.CreateBitCast(ShadowAddr, PointerType::getUnqual(ShadowTy));
723 IRB.CreateAlignedStore(ExtZeroShadow, ExtShadowAddr, ShadowAlign);
724 return;
725 }
726
727 const unsigned ShadowVecSize = 128 / DFS.ShadowWidth;
728 uint64_t Offset = 0;
729 if (Size >= ShadowVecSize) {
730 VectorType *ShadowVecTy = VectorType::get(DFS.ShadowTy, ShadowVecSize);
731 Value *ShadowVec = UndefValue::get(ShadowVecTy);
732 for (unsigned i = 0; i != ShadowVecSize; ++i) {
733 ShadowVec = IRB.CreateInsertElement(
734 ShadowVec, Shadow, ConstantInt::get(Type::getInt32Ty(*DFS.Ctx), i));
735 }
736 Value *ShadowVecAddr =
737 IRB.CreateBitCast(ShadowAddr, PointerType::getUnqual(ShadowVecTy));
738 do {
739 Value *CurShadowVecAddr = IRB.CreateConstGEP1_32(ShadowVecAddr, Offset);
740 IRB.CreateAlignedStore(ShadowVec, CurShadowVecAddr, ShadowAlign);
741 Size -= ShadowVecSize;
742 ++Offset;
743 } while (Size >= ShadowVecSize);
744 Offset *= ShadowVecSize;
745 }
746 while (Size > 0) {
747 Value *CurShadowAddr = IRB.CreateConstGEP1_32(ShadowAddr, Offset);
748 IRB.CreateAlignedStore(Shadow, CurShadowAddr, ShadowAlign);
749 --Size;
750 ++Offset;
751 }
752}
753
754void DFSanVisitor::visitStoreInst(StoreInst &SI) {
755 uint64_t Size =
756 DFSF.DFS.DL->getTypeStoreSize(SI.getValueOperand()->getType());
757 uint64_t Align;
758 if (ClPreserveAlignment) {
759 Align = SI.getAlignment();
760 if (Align == 0)
761 Align = DFSF.DFS.DL->getABITypeAlignment(SI.getValueOperand()->getType());
762 } else {
763 Align = 1;
764 }
765 DFSF.storeShadow(SI.getPointerOperand(), Size, Align,
766 DFSF.getShadow(SI.getValueOperand()), &SI);
767}
768
769void DFSanVisitor::visitBinaryOperator(BinaryOperator &BO) {
770 visitOperandShadowInst(BO);
771}
772
773void DFSanVisitor::visitCastInst(CastInst &CI) { visitOperandShadowInst(CI); }
774
775void DFSanVisitor::visitCmpInst(CmpInst &CI) { visitOperandShadowInst(CI); }
776
777void DFSanVisitor::visitGetElementPtrInst(GetElementPtrInst &GEPI) {
778 visitOperandShadowInst(GEPI);
779}
780
781void DFSanVisitor::visitExtractElementInst(ExtractElementInst &I) {
782 visitOperandShadowInst(I);
783}
784
785void DFSanVisitor::visitInsertElementInst(InsertElementInst &I) {
786 visitOperandShadowInst(I);
787}
788
789void DFSanVisitor::visitShuffleVectorInst(ShuffleVectorInst &I) {
790 visitOperandShadowInst(I);
791}
792
793void DFSanVisitor::visitExtractValueInst(ExtractValueInst &I) {
794 visitOperandShadowInst(I);
795}
796
797void DFSanVisitor::visitInsertValueInst(InsertValueInst &I) {
798 visitOperandShadowInst(I);
799}
800
801void DFSanVisitor::visitAllocaInst(AllocaInst &I) {
802 bool AllLoadsStores = true;
803 for (Instruction::use_iterator i = I.use_begin(), e = I.use_end(); i != e;
804 ++i) {
805 if (isa<LoadInst>(*i))
806 continue;
807
808 if (StoreInst *SI = dyn_cast<StoreInst>(*i)) {
809 if (SI->getPointerOperand() == &I)
810 continue;
811 }
812
813 AllLoadsStores = false;
814 break;
815 }
816 if (AllLoadsStores) {
817 IRBuilder<> IRB(&I);
818 DFSF.AllocaShadowMap[&I] = IRB.CreateAlloca(DFSF.DFS.ShadowTy);
819 }
820 DFSF.setShadow(&I, DFSF.DFS.ZeroShadow);
821}
822
823void DFSanVisitor::visitSelectInst(SelectInst &I) {
824 Value *CondShadow = DFSF.getShadow(I.getCondition());
825 Value *TrueShadow = DFSF.getShadow(I.getTrueValue());
826 Value *FalseShadow = DFSF.getShadow(I.getFalseValue());
827
828 if (isa<VectorType>(I.getCondition()->getType())) {
829 DFSF.setShadow(
830 &I, DFSF.DFS.combineShadows(
831 CondShadow,
832 DFSF.DFS.combineShadows(TrueShadow, FalseShadow, &I), &I));
833 } else {
834 Value *ShadowSel;
835 if (TrueShadow == FalseShadow) {
836 ShadowSel = TrueShadow;
837 } else {
838 ShadowSel =
839 SelectInst::Create(I.getCondition(), TrueShadow, FalseShadow, "", &I);
840 }
841 DFSF.setShadow(&I, DFSF.DFS.combineShadows(CondShadow, ShadowSel, &I));
842 }
843}
844
845void DFSanVisitor::visitMemTransferInst(MemTransferInst &I) {
846 IRBuilder<> IRB(&I);
847 Value *DestShadow = DFSF.DFS.getShadowAddress(I.getDest(), &I);
848 Value *SrcShadow = DFSF.DFS.getShadowAddress(I.getSource(), &I);
849 Value *LenShadow = IRB.CreateMul(
850 I.getLength(),
851 ConstantInt::get(I.getLength()->getType(), DFSF.DFS.ShadowWidth / 8));
852 Value *AlignShadow;
853 if (ClPreserveAlignment) {
854 AlignShadow = IRB.CreateMul(I.getAlignmentCst(),
855 ConstantInt::get(I.getAlignmentCst()->getType(),
856 DFSF.DFS.ShadowWidth / 8));
857 } else {
858 AlignShadow = ConstantInt::get(I.getAlignmentCst()->getType(),
859 DFSF.DFS.ShadowWidth / 8);
860 }
861 Type *Int8Ptr = Type::getInt8PtrTy(*DFSF.DFS.Ctx);
862 DestShadow = IRB.CreateBitCast(DestShadow, Int8Ptr);
863 SrcShadow = IRB.CreateBitCast(SrcShadow, Int8Ptr);
864 IRB.CreateCall5(I.getCalledValue(), DestShadow, SrcShadow, LenShadow,
865 AlignShadow, I.getVolatileCst());
866}
867
868void DFSanVisitor::visitReturnInst(ReturnInst &RI) {
869 if (RI.getReturnValue()) {
870 switch (DFSF.IA) {
871 case DataFlowSanitizer::IA_TLS: {
872 Value *S = DFSF.getShadow(RI.getReturnValue());
873 IRBuilder<> IRB(&RI);
874 IRB.CreateStore(S, DFSF.getRetvalTLS());
875 break;
876 }
877 case DataFlowSanitizer::IA_Args: {
878 IRBuilder<> IRB(&RI);
879 Type *RT = DFSF.F->getFunctionType()->getReturnType();
880 Value *InsVal =
881 IRB.CreateInsertValue(UndefValue::get(RT), RI.getReturnValue(), 0);
882 Value *InsShadow =
883 IRB.CreateInsertValue(InsVal, DFSF.getShadow(RI.getReturnValue()), 1);
884 RI.setOperand(0, InsShadow);
885 break;
886 }
887 default:
888 break;
889 }
890 }
891}
892
893void DFSanVisitor::visitCallSite(CallSite CS) {
894 Function *F = CS.getCalledFunction();
895 if ((F && F->isIntrinsic()) || isa<InlineAsm>(CS.getCalledValue())) {
896 visitOperandShadowInst(*CS.getInstruction());
897 return;
898 }
899
900 DenseMap<Value *, Function *>::iterator i =
901 DFSF.DFS.UnwrappedFnMap.find(CS.getCalledValue());
902 if (i != DFSF.DFS.UnwrappedFnMap.end()) {
903 CS.setCalledFunction(i->second);
904 DFSF.setShadow(CS.getInstruction(), DFSF.DFS.ZeroShadow);
905 return;
906 }
907
908 IRBuilder<> IRB(CS.getInstruction());
909
910 FunctionType *FT = cast<FunctionType>(
911 CS.getCalledValue()->getType()->getPointerElementType());
912 if (DFSF.DFS.getDefaultInstrumentedABI() == DataFlowSanitizer::IA_TLS) {
913 for (unsigned i = 0, n = FT->getNumParams(); i != n; ++i) {
914 IRB.CreateStore(DFSF.getShadow(CS.getArgument(i)),
915 DFSF.getArgTLS(i, CS.getInstruction()));
916 }
917 }
918
919 Instruction *Next = 0;
920 if (!CS.getType()->isVoidTy()) {
921 if (InvokeInst *II = dyn_cast<InvokeInst>(CS.getInstruction())) {
922 if (II->getNormalDest()->getSinglePredecessor()) {
923 Next = II->getNormalDest()->begin();
924 } else {
925 BasicBlock *NewBB =
926 SplitEdge(II->getParent(), II->getNormalDest(), &DFSF.DFS);
927 Next = NewBB->begin();
928 }
929 } else {
930 Next = CS->getNextNode();
931 }
932
933 if (DFSF.DFS.getDefaultInstrumentedABI() == DataFlowSanitizer::IA_TLS) {
934 IRBuilder<> NextIRB(Next);
935 LoadInst *LI = NextIRB.CreateLoad(DFSF.getRetvalTLS());
936 DFSF.SkipInsts.insert(LI);
937 DFSF.setShadow(CS.getInstruction(), LI);
938 }
939 }
940
941 // Do all instrumentation for IA_Args down here to defer tampering with the
942 // CFG in a way that SplitEdge may be able to detect.
943 if (DFSF.DFS.getDefaultInstrumentedABI() == DataFlowSanitizer::IA_Args) {
944 FunctionType *NewFT = DFSF.DFS.getInstrumentedFunctionType(FT);
945 Value *Func =
946 IRB.CreateBitCast(CS.getCalledValue(), PointerType::getUnqual(NewFT));
947 std::vector<Value *> Args;
948
949 CallSite::arg_iterator i = CS.arg_begin(), e = CS.arg_end();
950 for (unsigned n = FT->getNumParams(); n != 0; ++i, --n)
951 Args.push_back(*i);
952
953 i = CS.arg_begin();
954 for (unsigned n = FT->getNumParams(); n != 0; ++i, --n)
955 Args.push_back(DFSF.getShadow(*i));
956
957 if (FT->isVarArg()) {
958 unsigned VarArgSize = CS.arg_size() - FT->getNumParams();
959 ArrayType *VarArgArrayTy = ArrayType::get(DFSF.DFS.ShadowTy, VarArgSize);
960 AllocaInst *VarArgShadow =
961 new AllocaInst(VarArgArrayTy, "", DFSF.F->getEntryBlock().begin());
962 Args.push_back(IRB.CreateConstGEP2_32(VarArgShadow, 0, 0));
963 for (unsigned n = 0; i != e; ++i, ++n) {
964 IRB.CreateStore(DFSF.getShadow(*i),
965 IRB.CreateConstGEP2_32(VarArgShadow, 0, n));
966 Args.push_back(*i);
967 }
968 }
969
970 CallSite NewCS;
971 if (InvokeInst *II = dyn_cast<InvokeInst>(CS.getInstruction())) {
972 NewCS = IRB.CreateInvoke(Func, II->getNormalDest(), II->getUnwindDest(),
973 Args);
974 } else {
975 NewCS = IRB.CreateCall(Func, Args);
976 }
977 NewCS.setCallingConv(CS.getCallingConv());
978 NewCS.setAttributes(CS.getAttributes().removeAttributes(
979 *DFSF.DFS.Ctx, AttributeSet::ReturnIndex,
980 AttributeFuncs::typeIncompatible(NewCS.getInstruction()->getType(),
981 AttributeSet::ReturnIndex)));
982
983 if (Next) {
984 ExtractValueInst *ExVal =
985 ExtractValueInst::Create(NewCS.getInstruction(), 0, "", Next);
986 DFSF.SkipInsts.insert(ExVal);
987 ExtractValueInst *ExShadow =
988 ExtractValueInst::Create(NewCS.getInstruction(), 1, "", Next);
989 DFSF.SkipInsts.insert(ExShadow);
990 DFSF.setShadow(ExVal, ExShadow);
991
992 CS.getInstruction()->replaceAllUsesWith(ExVal);
993 }
994
995 CS.getInstruction()->eraseFromParent();
996 }
997}
998
999void DFSanVisitor::visitPHINode(PHINode &PN) {
1000 PHINode *ShadowPN =
1001 PHINode::Create(DFSF.DFS.ShadowTy, PN.getNumIncomingValues(), "", &PN);
1002
1003 // Give the shadow phi node valid predecessors to fool SplitEdge into working.
1004 Value *UndefShadow = UndefValue::get(DFSF.DFS.ShadowTy);
1005 for (PHINode::block_iterator i = PN.block_begin(), e = PN.block_end(); i != e;
1006 ++i) {
1007 ShadowPN->addIncoming(UndefShadow, *i);
1008 }
1009
1010 DFSF.PHIFixups.push_back(std::make_pair(&PN, ShadowPN));
1011 DFSF.setShadow(&PN, ShadowPN);
1012}