Skip to content
Snippets Groups Projects
SMPInstr.cpp 197 KiB
Newer Older
		this->MDAddRegDef(R_ax, false);
		this->MDAddRegDef(R_cx, false);
		this->MDAddRegDef(R_dx, false);
		if (this->MDIsInterruptCall()) {
			this->MDAddRegUse(R_ax, false);
			this->MDAddRegUse(R_cx, false);
			this->MDAddRegUse(R_dx, false);
		}
	else if (this->MDIsEnterInstr() || this->MDIsLeaveInstr()) {
		// Entire function prologue or epilogue microcoded.
		this->MDAddRegDef(R_sp, false);
		this->MDAddRegUse(R_sp, false);
		this->MDAddRegDef(R_bp, false);
		this->MDAddRegUse(R_bp, false);
	else if (this->SMPcmd.itype == NN_maskmovq) {
		this->MDAddRegUse(R_di, false);
	}
	else if (8 == this->GetOptType()) {
		// This category implicitly writes to EDX:EAX.
		this->MDAddRegDef(R_dx, false);
		this->MDAddRegDef(R_ax, false);
	} // end else if (8 == GetOptType)
	else if (7 == this->GetOptType()) {
		// Category 7 instructions sometimes write implicitly to EDX:EAX or DX:AX.
		//  DX is the same as EDX to IDA Pro (and SMP); ditto for EAX and AX.
		// DIV, IDIV, and MUL all have hidden EAX or AX operands (hidden in the IDA Pro
		//  sense, because they are not displayed in the disassembly text). For example:
		//  mul ebx means EDX:EAX <-- EAX*EBX, and mul bx means DX:AX <-- AX*BX. If the
		//  source operand is only 8 bits wide, there is room to hold the result in AX
		//  without using DX:  mul bl means AX <-- AL*BL.
		// IMUL has forms with a hidden EAX or AX operand and forms with no implicit
		//  operands:  imul ebx means EDX:EAX <-- EAX*EBX, but imul ebx,edx means that
		//  EBX*EDX gets truncated and the result placed in EBX (no hidden operands).
		for (OpNum = 0; OpNum < UA_MAXOP; ++OpNum) {
			op_t TempUse = SMPcmd.Operands[OpNum];
			if (!TempUse.showed()) { // hidden operand
				if (TempUse.is_reg(R_ax)) { // not R_al, so it is not 8 bits
					if ((NN_div == this->SMPcmd.itype) || (NN_idiv == this->SMPcmd.itype)) {
						this->MDAddRegUse(R_dx, false);
					}
					this->MDAddRegDef(R_ax, false);
					this->MDAddRegDef(R_dx, false);
				}
			}
		}
	} // end else if (7 == OptType)
#if 0
	// The floating point instructions in type categories 14 and 15 often USE and DEF
	//  the floating point register stack, e.g. pushing a value onto that stack is a
	//  massive copy downward of stack locations. We don't really care about the USE of
	//  the stack if the value being pushed came from elsewhere than the stack. For example,
	//  an "fld" opcode pushes its source onto the stack. We build RTLs with a simple
	//  move structure, but the RTL building can be fooled by seeing two "source" operands
	//  in the USE list.
	if ((14 == SMPTypeCategory[this->SMPcmd.itype])
		|| (15 == SMPTypeCategory[this->SMPcmd.itype])) {
	}
#endif

#if 0  // Not true for LOOP instructions that use only the ECX counter register.
	if (this->type == COND_BRANCH) {
		assert(SMPUsesFlags[this->SMPcmd.itype]);
	}
	// The return value register EAX is not quite like a caller-save or callee-save
	//  register (technically, it is caller-save). Within a callee, it might appear
	//  that EAX has become dead by the time a return instruction is reached, but
	//  the USE that would make it not dead is in the caller. To prevent type inference
	//  from mistakenly thinking that all USEs of EAX have been seen in the callee,
	//  we add EAX to the USE list for all return instructions, as well as for all
	//  tail calls, which are essentially returns in terms of data flow analysis.
	// This USE of EAX will always be of type UNINIT unless its DEF has a known type
	//  that propagates to it. Thus, it will prevent an invalid back inference of the
	//  DEF type from "all" USE types that are visible in the callee; even if they
	//  were all NUMERIC, this return USE will be UNINIT and inhibit the invalid
	//  type inference. EAX could be loaded with a pointer from memory, for example,
	//  and USEd only in a comparison instruction, making it falsely appear to be
	//  a NUMERIC, without this extra USE at the return instruction.
	if (this->type == RETURN) {
		this->MDAddRegUse(R_ax, false);
	}

	// Next, add the flags register to the DEFs and USEs for those instructions that
	//  are marked as defining or using flags.
	if (!this->DefsFlags && SMPDefsFlags[this->SMPcmd.itype]) {
		this->MDAddRegDef(X86_FLAGS_REG, false);
	if (!this->UsesFlags && SMPUsesFlags[this->SMPcmd.itype]) {
		this->MDAddRegUse(X86_FLAGS_REG, false);
#if 1
	if (this->MDIsNop()) {
		// Clear the DEFs and USEs for no-ops.
		this->Defs.clear();
		this->Uses.clear();
	}
#endif

	if (DebugFlag) {
		msg("DEBUG after MDFixupDefUseLists:\n");
		this->Dump();
	}
	return;
} // end of SMPInstr::MDFixupDefUseLists()

// If we can definitely identify which part of the addressing expression
//  used in MemOp is the POINTER type, and it is not a STACKPTR or GLOBALPTR
//  immediate, set the USE type for that register to POINTER and return true.
bool SMPInstr::MDFindPointerUse(op_t MemOp, bool UseFP) {
	bool changed = false;
	int BaseReg;
	int IndexReg;
	ushort ScaleFactor;
	ea_t offset;
	set<DefOrUse, LessDefUse>::iterator UseIter;

	if (NN_lea == this->SMPcmd.itype)
		return false;  // lea instruction really has no memory operands
	if (NN_fnop == this->SMPcmd.itype)
		return false;  // SSA marker instruction

	MDExtractAddressFields(MemOp, BaseReg, IndexReg, ScaleFactor, offset);
	if ((R_sp == BaseReg) || (R_sp == IndexReg))
		return false; // stack accesses will get STACKPTR type in SetImmedTypes()
	if (UseFP && ((R_bp == BaseReg) || (R_bp == IndexReg)))
		return false;
	if (IsImmedGlobalAddress(offset))
		return false;  // handled in SetImmedTypes()

	// At this point, we must have a base address in a register.
	if ((0 < ScaleFactor) || (R_none == IndexReg)) {
		// IndexReg is scaled, meaning it is NUMERIC, so BaseReg must
		//  be a POINTER; or IndexReg is not present, so BaseReg is the
		//  only possible holder of an address.
		if (R_none != BaseReg) {
			op_t BaseOp;
			BaseOp.type = o_reg;
			BaseOp.reg = MDCanonicalizeSubReg(BaseReg);
			assert(UseIter != this->GetLastUse());
			if (UNINIT == UseIter->GetType()) {
				changed = true;
				UseIter = this->SetUseType(BaseOp, POINTER);
				assert(UseIter != this->GetLastUse());
			}
		}
	}
	else if (R_none == BaseReg) {
		// We have an unscaled IndexReg and no BaseReg and offset was
		//  not a global offset, so IndexReg must be a POINTER.
		if (R_none != IndexReg) {
			op_t IndexOp;
			IndexOp.type = o_reg;
			IndexOp.reg = MDCanonicalizeSubReg(IndexReg);
			UseIter = this->FindUse(IndexOp);
			assert(UseIter != this->GetLastUse());
			if (UNINIT == UseIter->GetType()) {
				changed = true;
				UseIter = this->SetUseType(IndexOp, POINTER);
				assert(UseIter != this->GetLastUse());
			}
		}
	}
	else { // We have BaseReg and an unscaled IndexReg.
		// The only hope for typing something like [ebx+edx] is for
		//  one register to already be typed NUMERIC, in which case
		//  the other one must be a POINTER.
		op_t IndexOp;
		IndexOp.type = o_reg;
		IndexOp.reg = MDCanonicalizeSubReg(IndexReg);
		op_t BaseOp;
		BaseOp.type = o_reg;
		BaseOp.reg = MDCanonicalizeSubReg(BaseReg);
		UseIter = this->FindUse(BaseOp);
		assert(UseIter != this->GetLastUse());
		if (IsNumeric(UseIter->GetType())) {
			UseIter = this->FindUse(IndexOp);
			assert(UseIter != this->GetLastUse());
			if (UNINIT == UseIter->GetType()) {
				// Set to POINTER or PROF_POINTER
				changed = true;
				UseIter = this->SetUseType(IndexOp, POINTER);
				assert(UseIter != this->GetLastUse());
			}
		}
		else { // BaseReg was not NUMERIC
			if (UNINIT == UseIter->GetType()) { // BaseReg is UNINIT
				UseIter = this->FindUse(IndexOp);
				assert(UseIter != this->GetLastUse());
				if (IsNumeric(UseIter->GetType())) {
					changed = true;
					UseIter = this->SetUseType(BaseOp, POINTER);
					assert(UseIter != this->GetLastUse());
				}
			}
		}
	}

	return changed;
} // end of SMPInstr::MDFindPointerUse()

// Are all DEFs typed to something besides UNINIT?
bool SMPInstr::AllDEFsTyped(void) {
	bool FoundUNINIT = false;
	set<DefOrUse, LessDefUse>::iterator DefIter;
	for (DefIter = this->GetFirstDef(); DefIter != this->GetLastDef(); ++DefIter) {
		if (IsEqType(UNINIT, DefIter->GetType())) {
			FoundUNINIT = true;
			break;
		}
	}
	return (!FoundUNINIT);
} // end of SMPInstr::AllDEFsTyped()

// Are all USEs typed to something besides UNINIT?
bool SMPInstr::AllUSEsTyped(void) {
	bool FoundUNINIT = false;
	set<DefOrUse, LessDefUse>::iterator UseIter;
	for (UseIter = this->GetFirstUse(); UseIter != this->GetLastUse(); ++UseIter) {
		if (IsEqType(UNINIT, UseIter->GetType())) {
			FoundUNINIT = true;
			break;
		}
	}
	return (!FoundUNINIT);
} // end of SMPInstr::AllUSEsTyped()

// Set the type of all immediate operands found in the USE set.
// Set all flags and floating point register USEs and DEFs to NUMERIC also.
void SMPInstr::SetImmedTypes(bool UseFP) {
	set<DefOrUse, LessDefUse>::iterator CurrUse;
	set<DefOrUse, LessDefUse>::iterator CurrDef;
	bool DebugFlag = false;
#if SMP_VERBOSE_DEBUG_BUILD_RTL
	DebugFlag = DebugFlag || (this->address == 0x805cd52) || (this->address == 0x805cd56);
	DebugFlag |= (0 == strncmp("__libc_csu_fini", this->BasicBlock->GetFunc()->GetFuncName(), 15));
#endif

	CurrUse = this->GetFirstUse();
	while (CurrUse != this->GetLastUse()) {
		UseOp = CurrUse->GetOp();
		if (DebugFlag) {
			msg("SetImmedTypes USE: ");
			PrintOperand(UseOp);
			msg("\n");
		}
		if (o_imm == UseOp.type) {
			ImmVal = UseOp.value;
			if (IsImmedGlobalAddress((ea_t) ImmVal)) {
				if (DebugFlag) msg("Setting to GLOBALPTR\n");
				CurrUse = this->SetUseType(UseOp, GLOBALPTR);
			else if (this->Interrupt || IsImmedCodeAddress((ea_t) ImmVal)) {
				if (DebugFlag) msg("Setting to CODEPTR\n");
				CurrUse = this->SetUseType(UseOp, CODEPTR);
				if (DebugFlag) msg("Setting to NUMERIC\n");
				CurrUse = this->SetUseType(UseOp, NUMERIC);
		else if (o_reg == UseOp.type) {
			if (UseOp.is_reg(X86_FLAGS_REG)) {
				if (DebugFlag) msg("Setting flags reg to NUMERIC\n");
				CurrUse = this->SetUseType(UseOp, NUMERIC);
			}
#if 1
			else if (UseOp.is_reg(R_sp) || (UseFP && UseOp.is_reg(R_bp))) {
				if (DebugFlag) msg("Setting reg to STACKPTR\n");
				CurrUse = this->SetUseType(UseOp, STACKPTR);
			}
#endif
		}
#if 0  // could these registers have pointers in them?
		else if ((o_trreg == UseOp.type) ||(o_dbreg == UseOp.type) || (o_crreg == UseOp.type)) {
			if (DebugFlag) msg("Setting special reg to NUMERIC\n");
			CurrUse = this->SetUseType(UseOp, NUMERIC);
		}
#endif
		else if ((o_fpreg == UseOp.type) || (o_mmxreg == UseOp.type) || (o_xmmreg == UseOp.type)) {
			if (DebugFlag) msg("Setting floating point reg to NUMERIC\n");
			CurrUse = this->SetUseType(UseOp, NUMERIC);
		}
		else if ((o_mem == UseOp.type) || (o_phrase == UseOp.type) || (o_displ == UseOp.type)) {
			// For memory operands, we need to identify the POINTER value that
			//  is used in the addressing mode, if possible.
			(void) this->MDFindPointerUse(UseOp, UseFP);
		}
		++CurrUse;
	} // end while all USEs via CurrUse

	CurrDef = this->GetFirstDef();
	while (CurrDef != this->GetLastDef()) {
		DefOp = CurrDef->GetOp();
		if (DebugFlag) {
			msg("SetImmedTypes DEF: ");
			PrintOperand(DefOp);
			msg("\n");
		}
		if (DebugFlag) msg("FuncName: %s\n", this->BasicBlock->GetFunc()->GetFuncName());
		if (o_reg == DefOp.type) {
			if (DefOp.is_reg(X86_FLAGS_REG)) {
				if (DebugFlag) msg("Setting flags reg DEF to NUMERIC\n");
				CurrDef = this->SetDefType(DefOp, NUMERIC);
				// No need to propagate this DEF type, as all flags will become NUMERIC.
			}
#if 1
			else if (DefOp.is_reg(R_sp) || (DefOp.is_reg(R_bp) && UseFP)) {
				if (DebugFlag) msg("Setting reg DEF to STACKPTR\n");
				CurrDef = this->SetDefType(DefOp, STACKPTR);
				assert(CurrDef != this->Defs.GetLastRef());
				// No need to propagate; all stack and frame pointers will become STACKPTR.
		else if ((o_fpreg == DefOp.type) || (o_mmxreg == DefOp.type) || (o_xmmreg == DefOp.type)) {
			if (DebugFlag) msg("Setting floating point reg DEF to NUMERIC\n");
			CurrDef = this->SetDefType(DefOp, NUMERIC);
			// No need to propagate; all FP reg uses will become NUMERIC anyway.
		}
#if 0  // could these registers have pointers in them?
		else if ((o_trreg == DefOp.type) || (o_dbreg == DefOp.type) || (o_crreg == DefOp.type)) {
			if (DebugFlag) msg("Setting special reg DEF to NUMERIC\n");
			CurrDef = this->SetDefType(DefOp, NUMERIC);
		}
#endif	
		else if ((o_mem == DefOp.type) || (o_phrase == DefOp.type) || (o_displ == DefOp.type)) {
			// For memory operands, we need to identify the POINTER value that
			//  is used in the addressing mode, if possible.
			(void) this->MDFindPointerUse(DefOp, UseFP);
		}
		++CurrDef;
	} // end while all DEFs via CurrDef
	return;
} // end of SMPInstr::SetImmedTypes()

// Infer DEF, USE, and RTL SMPoperator types within the instruction based on the type
//  of operator, the type category of the instruction, and the previously known types 
//  of the operands.
bool SMPInstr::InferTypes(void) {
	bool changed = false;
	int TypeCategory = SMPTypeCategory[this->SMPcmd.itype];
	set<DefOrUse, LessDefUse>::iterator CurrDef;
	set<DefOrUse, LessDefUse>::iterator CurrUse;
	op_t DefOp, UseOp;
	bool DebugFlag = false;
	bool UseFP = this->BasicBlock->GetFunc()->UsesFramePointer();
#if SMP_VERBOSE_DEBUG_INFER_TYPES
	DebugFlag |= (0 == strcmp("__libc_csu_fini", this->BasicBlock->GetFunc()->GetFuncName()));
#endif
	if (DebugFlag) {
		msg("opcode: %d TypeCategory: %d\n", this->SMPcmd.itype, TypeCategory);
	}

	// If we are already finished with all types, return false.
	if (this->TypeInferenceComplete)
		return false;

	if (this->AllDEFsTyped() && this->AllUSEsTyped()) {
		this->TypeInferenceComplete = true;
		return false;
	}

	if (this->HasDestMemoryOperand()) {
		changed |= this->MDFindPointerUse(this->MDGetMemDefOp(), UseFP);
	}
	if (this->HasSourceMemoryOperand()) {
		changed |= this->MDFindPointerUse(this->MDGetMemUseOp(), UseFP);
	}

	// The control flow instructions can be handled simply based on their type
	//  and do not need an RTL walk.
	SMPitype DFAType = this->GetDataFlowType();
	if (DebugFlag) {
		msg("DFAType: %d  CategoryInferenceComplete: %d\n",
			DFAType, this->CategoryInferenceComplete);
	if ((DFAType >= JUMP) && (DFAType <= INDIR_CALL)) {
		// All USEs are either the flags (NUMERIC) or the target address (CODEPTR).
		//  The exception is the USE list for interrupt calls, which includes
		//  the caller-saved regs.
		CurrUse = this->GetFirstUse();
		while (CurrUse != this->GetLastUse()) {
			UseOp = CurrUse->GetOp();
			if (UseOp.is_reg(X86_FLAGS_REG))
				CurrUse = this->SetUseType(UseOp, NUMERIC);
			else if ((CurrUse->GetType() != CODEPTR)
				&& (!(this->MDIsInterruptCall() && (o_reg == UseOp.type)))) {
				CurrUse = this->SetUseType(UseOp, CODEPTR);
			++CurrUse;
		}
		this->TypeInferenceComplete = true;
		return true;
	}

	// First, see if we can infer something about DEFs and USEs just from the 
	//  type category of the instruction.
		switch (TypeCategory) {
			case 0: // no inference possible just from type category
			case 1: // no inference possible just from type category
			case 3:  // MOV instructions; inference will come from source to dest in RTL walk.
			case 5:  // binary arithmetic; inference will come in RTL walk.
			case 10:  // binary arithmetic; inference will come in RTL walk.
			case 11:  // push and pop instructions; inference will come in RTL walk.
			case 12:  // exchange instructions; inference will come in RTL walk.
				break;

			case 2: // Result type is always NUMERIC.
			case 7: // Result type is always NUMERIC.
			case 8: // Result type is always NUMERIC.
			case 9: // Result type is always NUMERIC.
			case 13: // Result type is always NUMERIC.
			case 14: // Result type is always NUMERIC.
			case 15: // Result type is always NUMERIC.
				CurrDef = this->GetFirstDef();
				while (CurrDef != this->GetLastDef()) {
					if (NUMERIC != CurrDef->GetType()) {
						DefOp = CurrDef->GetOp();
						SSANum = CurrDef->GetSSANum();
						CurrDef = this->SetDefType(DefOp, NUMERIC);
						changed = true;
						// Be conservative and only propagate register DEFs and SAFE stack locs. We
						//  can improve this in the future. **!!**
						if ((o_reg == DefOp.type)
							|| (FUNC_SAFE == this->BasicBlock->GetFunc()->GetReturnAddressStatus())) {
							if (this->BasicBlock->IsLocalName(DefOp)) {
								(void) this->BasicBlock->PropagateLocalDefType(DefOp, NUMERIC,
							}
							else { // global name
								this->BasicBlock->GetFunc()->ResetProcessedBlocks(); // set Processed to false
								(void) this->BasicBlock->PropagateGlobalDefType(DefOp, NUMERIC,
									SSANum);
							}
			case 4: // Unary INC, DEC, etc.: dest=source, so type remains the same
				assert(1 == this->RTL.GetCount());
				assert(this->RTL.GetRT(0)->HasRightSubTree());
				UseOp = this->RTL.GetRT(0)->GetLeftOperand(); // USE == DEF
				CurrUse = this->Uses.FindRef(UseOp);
				assert(CurrUse != this->GetLastUse());
				if (UNINIT != CurrUse->GetType()) {
					// Only one USE, and it has a type assigned, so assign that type
					// to the DEF.
					CurrDef = this->GetFirstDef();
					while (CurrDef != this->GetLastDef()) {
						// Two DEFs: EFLAGS is NUMERIC, dest==source
						DefOp = CurrDef->GetOp();
						SSANum = CurrDef->GetSSANum();
						if (DefOp.is_reg(X86_FLAGS_REG)) {
							; // SetImmedTypes already made it NUMERIC
							CurrDef = this->SetDefType(DefOp, CurrUse->GetType());
							// Be conservative and only propagate register DEFs and SAFE stack locs. We
							//  can improve this in the future. **!!**
							if ((o_reg == DefOp.type)
								|| (FUNC_SAFE == this->BasicBlock->GetFunc()->GetReturnAddressStatus())) {
								if (this->BasicBlock->IsLocalName(DefOp)) {
									(void) this->BasicBlock->PropagateLocalDefType(DefOp, CurrUse->GetType(),
								}
								else { // global name
									this->BasicBlock->GetFunc()->ResetProcessedBlocks(); // set Processed to false
									(void) this->BasicBlock->PropagateGlobalDefType(DefOp, CurrUse->GetType(),
										SSANum);
								}
					changed = true;
				}
				break;

			case 6: // Result is always POINTER
				DefOp = this->GetFirstDef()->GetOp();
				SSANum = this->GetFirstDef()->GetSSANum();
				CurrDef = this->SetDefType(DefOp, POINTER);
				changed = true;
				// Be conservative and only propagate register DEFs and SAFE stack locs. We
				//  can improve this in the future. **!!**
				if ((o_reg == DefOp.type)
					|| (FUNC_SAFE == this->BasicBlock->GetFunc()->GetReturnAddressStatus()))  {
					if (this->BasicBlock->IsLocalName(DefOp)) {
						(void) this->BasicBlock->PropagateLocalDefType(DefOp, POINTER,
					}
					else { // global name
						this->BasicBlock->GetFunc()->ResetProcessedBlocks(); // set Processed to false
						(void) this->BasicBlock->PropagateGlobalDefType(DefOp, POINTER,
							SSANum);
					}
				break;

			default:
				msg("ERROR: Unknown type category for %s\n", this->GetDisasm());
				break;
		} // end switch on TypeCategory
	} // end if (!CategoryInference)

	// Walk the RTL and infer types based on operators and operands.
	if (DebugFlag) {
		msg("RTcount: %d\n", this->RTL.GetCount());
	}
	for (size_t index = 0; index < this->RTL.GetCount(); ++index) {
		SMPRegTransfer *CurrRT = this->RTL.GetRT(index);
		if (SMP_NULL_OPERATOR == CurrRT->GetOperator()) // nothing to infer
			continue;
		changed |= this->InferOperatorType(CurrRT);
		if (DebugFlag) {
			msg("returned from InferOperatorType\n");
		}
	} // end for all RTs in the RTL
	return changed;
} // end of SMPInstr::InferTypes()

// Infer the type of an operator within an RT based on the types of its operands and
//  based on the operator itself. Recurse down the tree if necessary.
// Return true if the operator type of the RT is updated.
bool SMPInstr::InferOperatorType(SMPRegTransfer *CurrRT) {
	bool updated = false;
	bool LeftNumeric, RightNumeric;
	bool LeftPointer, RightPointer;
	set<DefOrUse, LessDefUse>::iterator CurrDef;
	set<DefOrUse, LessDefUse>::iterator CurrUse;
	set<DefOrUse, LessDefUse>::iterator LeftUse;
	set<DefOrUse, LessDefUse>::iterator RightUse;
	SMPOperandType LeftType = UNINIT;
	SMPOperandType RightType = UNINIT;
	SMPOperandType OperType = UNINIT;
clc5q's avatar
clc5q committed
	op_t UseOp, DefOp, LeftOp, RightOp;
	SMPoperator CurrOp = CurrRT->GetOperator();
	bool DebugFlag = false;
#if SMP_VERBOSE_DEBUG_INFER_TYPES
#if 0
	DebugFlag |= (0 == strcmp("strtok", this->BasicBlock->GetFunc()->GetFuncName()));
#endif
	DebugFlag = DebugFlag || ((this->address == 0x805cd52) || (this->address == 0x805cd56));
#if SMP_VERBOSE_DEBUG_INFER_TYPES
	if (DebugFlag) {
		msg("Entered InferOperatorType for CurrOp: %d\n", CurrOp);
	}
	switch (CurrOp) {
		case SMP_NULL_OPERATOR:
			break;

		case SMP_CALL:  // CALL instruction
			if (UNINIT == CurrRT->GetOperatorType()) {
				CurrRT->SetOperatorType(CODEPTR);
				updated = true;
				UseOp = CurrRT->GetRightOperand();
				CurrUse = this->Uses.FindRef(UseOp);
				assert(CurrUse != this->GetLastUse());
				if (UNINIT == CurrUse->GetType()) {
					CurrUse = this->SetUseType(UseOp, CODEPTR);
				}
				else if (CODEPTR != CurrUse->GetType()) {
					msg("WARNING: call target is type %d, setting to CODEPTR at %x in %s\n",
						CurrUse->GetType(), this->GetAddr(), this->GetDisasm());
					CurrUse = this->SetUseType(UseOp, CODEPTR);
				}
			}
			break;

		case SMP_INPUT:  // input from port
			if (UNINIT == CurrRT->GetOperatorType()) {
				CurrRT->SetOperatorType(UNKNOWN);  // Leave DEF as UNINIT and infer later
				updated = true;
			}
			break;

		case SMP_OUTPUT: // output to port
		case SMP_SIGN_EXTEND:
		case SMP_ZERO_EXTEND:
			break;

		case SMP_ADDRESS_OF: // take effective address
			if (UNINIT == CurrRT->GetOperatorType()) {
				CurrRT->SetOperatorType(POINTER);
				// Left operand is having its address taken, but we cannot infer what its
				//  type is.
				updated = true;
			}
			break;

		case SMP_U_LEFT_SHIFT: // unsigned left shift
		case SMP_S_LEFT_SHIFT: // signed left shift
		case SMP_U_RIGHT_SHIFT: // unsigned right shift
		case SMP_S_RIGHT_SHIFT: // signed right shift
		case SMP_ROTATE_LEFT:
		case SMP_ROTATE_LEFT_CARRY: // rotate left through carry
		case SMP_ROTATE_RIGHT:
		case SMP_ROTATE_RIGHT_CARRY: // rotate right through carry
		case SMP_ADD_CARRY:   // add with carry
		case SMP_SUBTRACT_BORROW:  // subtract with borrow
		case SMP_U_MULTIPLY:
		case SMP_S_MULTIPLY:
		case SMP_U_DIVIDE:
		case SMP_S_DIVIDE:
		case SMP_U_REMAINDER:
		case SMP_BITWISE_NOT: // unary operator
		case SMP_BITWISE_XOR:
		case SMP_NEGATE:    // unary negation
		case SMP_S_COMPARE: // signed compare (subtraction-based)
		case SMP_U_COMPARE: // unsigned compare (AND-based)
		case SMP_LESS_THAN: // boolean test operators
		case SMP_GREATER_THAN:
		case SMP_LESS_EQUAL:
		case SMP_GREATER_EQUAL:
		case SMP_EQUAL:
		case SMP_NOT_EQUAL:
		case SMP_LOGICAL_AND:
		case SMP_LOGICAL_OR:
		case SMP_UNARY_NUMERIC_OPERATION:  // miscellaneous; produces NUMERIC result
		case SMP_BINARY_NUMERIC_OPERATION:  // miscellaneous; produces NUMERIC result
		case SMP_SYSTEM_OPERATION:   // for instructions such as CPUID, RDTSC, etc.; NUMERIC
		case SMP_UNARY_FLOATING_ARITHMETIC:  // all the same to our type system; all NUMERIC
		case SMP_BINARY_FLOATING_ARITHMETIC:  // all the same to our type system; all NUMERIC
			if (UNINIT == CurrRT->GetOperatorType()) {
				CurrRT->SetOperatorType(NUMERIC);
				updated = true;
			}
			// Left operand should be NUMERIC if it exists.
			UseOp = CurrRT->GetLeftOperand();
			if (UseOp.type != o_void) {
				CurrUse = this->Uses.FindRef(UseOp);
				if (CurrUse == this->GetLastUse()) {
					msg("WARNING: Adding missing USE of ");
					PrintOperand(UseOp);
					msg(" in %s\n", this->GetDisasm());
					this->Uses.SetRef(UseOp, NUMERIC, -1);
					updated = true;
				}
				else if (UNINIT == CurrUse->GetType()) {
					CurrUse = this->SetUseType(UseOp, NUMERIC);
					updated = true;
				}
			}
			// Right operand should be NUMERIC if it exists.
			if (CurrRT->HasRightSubTree()) {
				// Recurse into subtree
				updated |= this->InferOperatorType(CurrRT->GetRightTree());
			}
			else {
				UseOp = CurrRT->GetRightOperand();
				if (UseOp.type != o_void) {
					CurrUse = this->Uses.FindRef(UseOp);
					if (CurrUse == this->GetLastUse()) {
						msg("WARNING: Adding missing USE of ");
						PrintOperand(UseOp);
						msg(" in %s\n", this->GetDisasm());
						this->Uses.SetRef(UseOp, NUMERIC, -1);
						updated = true;
					}
					else if (UNINIT == CurrUse->GetType()) {
						CurrUse = this->SetUseType(UseOp, NUMERIC);
						updated = true;
					}
				}
			}
			break;

		case SMP_INCREMENT:
		case SMP_DECREMENT:
			// The type of the right operand is propagated to the operator, or vice
			//  versa, whichever receives a type first.
			assert(!CurrRT->HasRightSubTree());
			UseOp = CurrRT->GetLeftOperand();
			assert(o_void != UseOp.type);
			CurrUse = this->Uses.FindRef(UseOp);
			if (CurrUse == this->GetLastUse()) {
				msg("WARNING: Adding missing USE of ");
				PrintOperand(UseOp);
				msg(" at %x in %s\n", this->GetAddr(), this->GetDisasm());
				this->Uses.SetRef(UseOp);
				updated = true;
				break;
			}
			if (UNINIT == CurrRT->GetOperatorType()) {
				if (UNINIT != CurrUse->GetType()) {
					// Propagate operand type up to the operator.
					CurrRT->SetOperatorType(CurrUse->GetType());
					updated = true;
				}
			}
			else if (UNINIT == CurrUse->GetType()) {
				// Propagate operator type to operand.
				CurrUse = this->SetUseType(UseOp, CurrRT->GetOperatorType());
				updated = true;
			}
			break;

		case SMP_ADD:
		case SMP_BITWISE_AND:
		case SMP_BITWISE_OR:
clc5q's avatar
clc5q committed
			// Extract the current types of right and left operands and the operator.
			LeftOp = CurrRT->GetLeftOperand();
			CurrUse = this->Uses.FindRef(LeftOp);
			assert(CurrUse != this->GetLastUse()); // found it
			LeftType = CurrUse->GetType();
			if (CurrRT->HasRightSubTree()) {
				RightType = CurrRT->GetRightTree()->GetOperatorType();
			}
			else {
				RightOp = CurrRT->GetRightOperand();
				if (o_void == RightOp.type) {
					msg("ERROR: void operand in %s\n", this->GetDisasm());
					return false;
clc5q's avatar
clc5q committed
					CurrUse = this->Uses.FindRef(RightOp);
					if (CurrUse == this->GetLastUse()) {
						msg("WARNING: Adding missing USE of ");
clc5q's avatar
clc5q committed
						PrintOperand(RightOp);
						msg(" in %s\n", this->GetDisasm());
clc5q's avatar
clc5q committed
						this->Uses.SetRef(RightOp);
						RightType = CurrUse->GetType();
clc5q's avatar
clc5q committed
				}
			}

			// We have to know both operand types to infer the operator, or know the
			//  operator type to infer the operand types.
			if ((UNINIT == CurrRT->GetOperatorType()) 
				&& ((UNINIT == LeftType) || (UNINIT == RightType)))
				break;

			// If both operands are NUMERIC, operator and result are NUMERIC.
			// If one operand is NUMERIC and the other is a pointer type,
			//  then the ADD operator and the result will inherit this second type,
			//  while AND and OR operators will remain UNINIT (we don't know what
			//  type "ptr AND 0xfffffff8" has until we see how it is used).
			LeftNumeric = IsEqType(NUMERIC, LeftType);
			RightNumeric = IsEqType(NUMERIC, RightType);
			LeftPointer = IsDataPtr(LeftType);
			RightPointer = IsDataPtr(RightType);
clc5q's avatar
clc5q committed
			if (UNINIT == CurrRT->GetOperatorType()) {
				// Infer operator type from left and right operands.
				if (LeftNumeric && RightNumeric) {
					CurrRT->SetOperatorType(NUMERIC);
					updated = true;
clc5q's avatar
clc5q committed
					break;
				}
				else if (LeftNumeric || RightNumeric) {
					// ADD of NUMERIC to non-NUMERIC preserves non-NUMERIC type.
					// AND and OR operations should leave the operator UNINIT for now.
					if (LeftNumeric && (UNINIT != RightType) 
						&& ((SMP_ADD == CurrOp) || (SMP_ADD_CARRY == CurrOp))) {
						CurrRT->SetOperatorType(RightType);
						updated = true;
clc5q's avatar
clc5q committed
						break;
					else if (RightNumeric && (UNINIT != LeftType) 
						&& ((SMP_ADD == CurrOp) || (SMP_ADD_CARRY == CurrOp))) {
						CurrRT->SetOperatorType(LeftType);
						updated = true;
clc5q's avatar
clc5q committed
						break;
				else if (LeftPointer && RightPointer) {
					// Arithmetic on two pointers
					if ((SMP_ADD == CurrOp) || (SMP_ADD_CARRY == CurrOp)) {
						CurrRT->SetOperatorType(UNKNOWN);
					}
					else { // bitwise AND or OR of two pointers
						msg("WARNING: hash of two pointers at %x in %s\n",
							this->GetAddr(), this->GetDisasm());
						// hash operation? leave operator as UNINIT
clc5q's avatar
clc5q committed
					break;
				else if ((LeftPointer && IsEqType(RightType, PTROFFSET))
					|| (RightPointer && IsEqType(LeftType, PTROFFSET))) {
					// Arithmetic on PTR and PTROFFSET
					if ((SMP_ADD == CurrOp) || (SMP_ADD_CARRY == CurrOp)) {
						// We assume (A-B) is being added to B or vice versa **!!**
						CurrRT->SetOperatorType(POINTER);
					}
					else { // bitwise AND or OR of pointer and pointer difference
						msg("WARNING: hash of PTROFFSET and POINTER at %x in %s\n",
							this->GetAddr(), this->GetDisasm());
						// hash operation? leave operator as UNINIT
clc5q's avatar
clc5q committed
					break;
				}
			} // end if UNINIT operator type
			else { // operator has type other than UNINIT
clc5q's avatar
clc5q committed
				if (UNINIT == LeftType) {
					CurrUse = this->SetUseType(LeftOp, CurrRT->GetOperatorType());
					updated = true;
					assert(CurrUse != this->GetLastUse());
clc5q's avatar
clc5q committed
					break;
				}
				if (CurrRT->HasRightSubTree()) {
					// Must need to iterate through the right tree again, as the operator
					//  has been typed.
					if (UNINIT == RightType) {
						CurrRT->GetRightTree()->SetOperatorType(CurrRT->GetOperatorType());
						updated = true;
					}
					updated |= this->InferOperatorType(CurrRT->GetRightTree());
clc5q's avatar
clc5q committed
					break;
				}
				else { // right operand; propagate operator type if needed
clc5q's avatar
clc5q committed
					if (UNINIT == RightType) {
						CurrUse = this->SetUseType(RightOp, CurrRT->GetOperatorType());
						updated = true;
						assert(CurrUse != this->GetLastUse());
clc5q's avatar
clc5q committed
						break;
		case SMP_SUBTRACT:
			// Extract the current types of right and left operands and the operator.
			OperType = CurrRT->GetOperatorType();
			LeftOp = CurrRT->GetLeftOperand();
			LeftUse = this->Uses.FindRef(LeftOp);
			assert(LeftUse != this->GetLastUse()); // found it
			LeftType = LeftUse->GetType();
			if (CurrRT->HasRightSubTree()) {
				RightType = CurrRT->GetRightTree()->GetOperatorType();
			}
			else {
				RightOp = CurrRT->GetRightOperand();
				if (o_void == RightOp.type) {
					msg("ERROR: void operand in %s\n", this->GetDisasm());
					return false;
				}
				else {
					RightUse = this->Uses.FindRef(RightOp);
					if (RightUse == this->GetLastUse()) {
						msg("WARNING: Adding missing USE of ");
						PrintOperand(RightOp);
						msg(" in %s\n", this->GetDisasm());
						this->Uses.SetRef(RightOp);
						updated = true;
						break;
					}
					else {
						RightType = RightUse->GetType();
					}
				}
			}
			// If left operand is NUMERIC, operator is NUMERIC.
			LeftNumeric = IsEqType(NUMERIC, LeftType);
			RightNumeric = IsEqType(NUMERIC, RightType);
			LeftPointer = IsDataPtr(LeftType);
			RightPointer = IsDataPtr(RightType);
			if (LeftNumeric) {
				// Subtracting anything from a NUMERIC leaves it NUMERIC.
				if (UNINIT == OperType) {
					CurrRT->SetOperatorType(NUMERIC);
					updated = true;
				}
				else if (NUMERIC != OperType) {
					msg("ERROR: SMP_SUBTRACT from NUMERIC should be NUMERIC operator.");
					msg(" Operator type is %d in: %s\n", OperType, this->GetDisasm());
				}
				if (!RightNumeric) {
					// Right operand is being used as a NUMERIC, so propagate NUMERIC to it.
					if (CurrRT->HasRightSubTree()) {
						CurrRT->GetRightTree()->SetOperatorType(NUMERIC);
					}
					else {
						RightUse = this->SetUseType(RightOp, NUMERIC);
					}
					updated = true;
				}
			} // end if LeftNumeric
			else if (LeftPointer) {
				if (UNINIT == OperType) {
					// If we subtract another pointer type, we produce PTROFFSET.
					if (RightPointer) {
						CurrRT->SetOperatorType(PTROFFSET);
						updated = true;
					}
					else if (RightType == PTROFFSET) {
						// We assume B - (B - A) == A    **!!**
						CurrRT->SetOperatorType(POINTER);
						msg("WARNING: PTR - PTROFFSET produces PTR in %s\n", this->GetDisasm());
						updated = true;
					}
					else if (RightNumeric) {
						// pointer minus NUMERIC keeps same pointer type
						CurrRT->SetOperatorType(LeftType);
						updated = true;
					}
				}
				else { // we have an operator type for the SMP_SUBTRACT
					if (CurrRT->HasRightSubTree()) {
						// Must need to iterate through the right tree again, as the operator
						//  has been typed.
						if (UNINIT == RightType) {
							if (OperatorPointer) {
								// PTR := PTR - ?? ==> ?? is NUMERIC
								CurrRT->GetRightTree()->SetOperatorType(NUMERIC);
								updated = true;
							}
							else if (OperType == PTROFFSET) {
								CurrRT->GetRightTree()->SetOperatorType(LeftType);
								updated = true;
							}
						}
						updated |= this->InferOperatorType(CurrRT->GetRightTree());
						break;
					}
					else { // right operand; propagate operator type if needed
						if (UNINIT == RightType) {
							if (OperatorPointer) {
								// PTR := PTR - ?? ==> ?? is NUMERIC
								RightUse = this->SetUseType(RightOp, NUMERIC);
								updated = true;
								assert(RightUse != this->GetLastUse());
							}
							else if (OperType == PTROFFSET) {
								// PTROFFSET := PTR - ?? ==> ?? is PTR
								RightUse = this->SetUseType(RightOp, LeftType);
								updated = true;
							}
							break;
						}
					}
				} // end if OperType is UNINIT ... else ...
			} // end if LeftNumeric ... else if LeftPointer ...
			else if (UNINIT == LeftType) {
				if (UNINIT != OperType) {
					LeftUse = this->SetUseType(LeftOp, OperType);
					assert(LeftUse != this->GetLastUse());
					updated = true;
				}
			}
			break;

		case SMP_ASSIGN:
clc5q's avatar
clc5q committed
			// Extract the current types of right and left operands and SMP_ASSIGN operator.
			OperType = CurrRT->GetOperatorType();
			DefOp = CurrRT->GetLeftOperand();
			CurrDef = this->Defs.FindRef(DefOp);
			assert(CurrDef != this->GetLastDef()); // found it
clc5q's avatar
clc5q committed
			LeftType = CurrDef->GetType();
			if (CurrRT->HasRightSubTree()) {
				RightType = CurrRT->GetRightTree()->GetOperatorType();
			}
			else {
				UseOp = CurrRT->GetRightOperand();
				if (o_void == UseOp.type) {
					msg("ERROR: void operand for SMP_ASSIGN in %s\n", this->GetDisasm());
					return false;
				}
				else {
					CurrUse = this->Uses.FindRef(UseOp);
					if (CurrUse == this->GetLastUse()) {
						msg("WARNING: Adding missing USE of ");
						PrintOperand(UseOp);
						msg(" in %s\n", this->GetDisasm());
						this->Uses.SetRef(UseOp);
						updated = true;
clc5q's avatar
clc5q committed
						break;