[mercury-users] Memory Query

Daryl Essam daryl at cs.adfa.edu.au
Wed Jan 16 14:58:39 AEDT 2002


I've included all the files as attachments. main.m is the main program.
If you look at the parameters.m file at about line 210. There is a term
called pop_size, and one called ind_max_depth... pop = 2000 and depth = 6
works, and pop=100, and depth =10 works, but pop =2000 and depth =100
gives the problem. If you can work it out that would be great, but I
really do think its something about mercury's memory management

On Wed, 16 Jan 2002, Ralph Becket wrote:

> Daryl Essam, Wednesday, 16 January 2002:
> > > 
> > > Also, where was the exception thrown from (backtrace) ?
> > > 
> > > Paul.
> > 
> > 	That really was the only error message I got.. There was no backtrace
> > 	of the methods from where the exception came. Today or tomorrow I will
> > 	try to do a cut-down version of the code and reproduce the error.
> > 	If I still get it, I will send it to this list.. otherwise I'll send
> > 	something saying I've sorted it out. Thanks for your time
> 
> If you compile in a debugging grade you should get a stack trace when
> the program aborts.
> 
> - Ralph
> --------------------------------------------------------------------------
> mercury-users mailing list
> post:  mercury-users at cs.mu.oz.au
> administrative address: owner-mercury-users at cs.mu.oz.au
> unsubscribe: Address: mercury-users-request at cs.mu.oz.au Message: unsubscribe
> subscribe:   Address: mercury-users-request at cs.mu.oz.au Message: subscribe
> --------------------------------------------------------------------------
> 
-------------- next part --------------
%===============================================================================
% File		: general.m
% Author	: Raymee Chau
% Date Created	:
% Last Modified	: 22/2/2001
%
% This is a file for predicates or functions that were called by predicates
% or functions that are in different files.
%===============================================================================

:- module general.

%===============================================================================
:- interface.

:- import_module array, parameters.


% is_exist(T, ArrayT, ArraySize)
%	Used in : init_pop/8		- init_population.m
%	          get_fitness_cases/8	- get_fitness_cases.m
%	This predicate checks whether the element, T, exist in ArrayT.
:- pred is_exist(T, array(T), int).
:- mode is_exist(in, in, in) is semidet.


% count_nodes(Count) = S_expression
%	Used in : cross_individual/6	- cross_individual.m
%	          mutate_individual/4	- mutate_individual.m
%	This function count the number of nodes in the "S_expression",
%	and returns this number as "Count".
:- func count_nodes(int) = s_expression.
:- mode count_nodes(out) = in is det.


% join(S_expression, BreakPoint, Fregment, Count, Point, NewS_expression)
%	Used in : cross_individual/6	- cross_individual.m
%	          mutate_individual/4	- mutate_individual.m
%	This predicate insert the "Fregment" to the "S_expression" at
%	"BreakPoint" to create a "NewS_expression".
:- pred join(s_expression, int, s_expression, int, int, s_expression).
:- mode join(in, in, in, in, out, out) is det.

%===============================================================================
:- implementation.

:- import_module int, array, require.
:- import_module parameters.


is_exist(I, Array, N) :-
	N > 0,
	N1 is N - 1,
	(
		\+(lookup(Array, N1, I)) ->
		is_exist(I, Array, N1)
	;
		!
	).


count_nodes(C) = I :-
	(
		I = plus(count_nodes(C1), count_nodes(C2)) ->
		C = C1 + C2 + 1
	;
		I = diff(count_nodes(C1), count_nodes(C2)) ->
		C = C1 + C2 + 1
	;
		I = times(count_nodes(C1), count_nodes(C2)) ->
		C = C1 + C2 + 1
	;
		I = divide(count_nodes(C1), count_nodes(C2)) ->
		C = C1 + C2 + 1
	;
		I = aND(count_nodes(C1), count_nodes(C2)) ->
		C = C1 + C2 + 1
	;
		I = nand(count_nodes(C1), count_nodes(C2)) ->
		C = C1 + C2 + 1
	;
		I = oR(count_nodes(C1), count_nodes(C2)) ->
		C = C1 + C2 + 1
	;
		I = nor(count_nodes(C1), count_nodes(C2)) ->
		C = C1 + C2 + 1
	;
		I = sin(count_nodes(C1)) ->
		C = C1 + 1
	;
		I = cos(count_nodes(C1)) ->
		C = C1 + 1
	;
		I = exp(count_nodes(C1)) ->
		C = C1 + 1
	;
		I = rln(count_nodes(C1)) ->
		C = C1 + 1
	;
		I = x1 ->
		C = 1
	;
		I = x2 ->
		C = 1
	;
		I = x3 ->
		C = 1
	;
		I = x4 ->
		C = 1
	;
		I = x5 ->
		C = 1
	;
		I = x6 ->
		C = 1
	;
		I = x ->
		C = 1
	;
		I = one ->
		C = 1
	;
		error("count_nodes failed!")
	).


join(I, N, If, C, Csum, Iout) :-
	(
		I = plus(I1, I2) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = plus(Iout1, Iout2),
			join(I1, N, If, C1, C2, Iout1),
			join(I2, N, If, C2, Csum, Iout2)
		)
	;
		I = diff(I1, I2) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = diff(Iout1, Iout2),
			join(I1, N, If, C1, C2, Iout1),
			join(I2, N, If, C2, Csum, Iout2)
		)
	;
		I = times(I1, I2) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = times(Iout1, Iout2),
			join(I1, N, If, C1, C2, Iout1),
			join(I2, N, If, C2, Csum, Iout2)
		)
	;
		I = divide(I1, I2) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = divide(Iout1, Iout2),
			join(I1, N, If, C1, C2, Iout1),
			join(I2, N, If, C2, Csum, Iout2)
		)
	;
		I = aND(I1, I2) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = aND(Iout1, Iout2),
			join(I1, N, If, C1, C2, Iout1),
			join(I2, N, If, C2, Csum, Iout2)
		)
	;
		I = nand(I1, I2) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = nand(Iout1, Iout2),
			join(I1, N, If, C1, C2, Iout1),
			join(I2, N, If, C2, Csum, Iout2)
		)
	;
		I = oR(I1, I2) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = oR(Iout1, Iout2),
			join(I1, N, If, C1, C2, Iout1),
			join(I2, N, If, C2, Csum, Iout2)
		)
	;
		I = nor(I1, I2) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = nor(Iout1, Iout2),
			join(I1, N, If, C1, C2, Iout1),
			join(I2, N, If, C2, Csum, Iout2)
		)
	;
		I = sin(I1) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = sin(Iout1),
			join(I1, N, If, C1, Csum, Iout1)
		)
	;
		I = cos(I1) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = cos(Iout1),
			join(I1, N, If, C1, Csum, Iout1)
		)
	;
		I = exp(I1) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = exp(Iout1),
			join(I1, N, If, C1, Csum, Iout1)
		)
	;
		I = rln(I1) ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			C1 = C + 1, Iout = rln(Iout1),
			join(I1, N, If, C1, Csum, Iout1)
		)
	;
		I = x1 ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			Csum = C + 1, Iout = I
		)
	;
		I = x2 ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			Csum = C + 1, Iout = I
		)
	;
		I = x3 ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			Csum = C + 1, Iout = I
		)
	;
		I = x4 ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			Csum = C + 1, Iout = I
		)
	;
		I = x5 ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			Csum = C + 1, Iout = I
		)
	;
		I = x6 ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			Csum = C + 1, Iout = I
		)
	;
		I = x ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			Csum = C + 1, Iout = I
		)
	;
		I = one ->
		(
			N = C -> Csum = C, Iout = If, !
		;
			Csum = C + 1, Iout = I
		)
	;
		error("join failed!")
	).
-------------- next part --------------
%===============================================================================
% File		: init_individual.m
% Author	: Raymee Chau
% Date Created	:
% Last Modified	: 22/2/2001
%
% The predicates in this file create a tree randomly with
% different types (i.e. full and grow trees) and different depths.
%===============================================================================

:- module init_individual.

%===============================================================================
:- interface.

:- import_module random, parameters.


% init_individual(TreeType, Depth, Tree, RandomSupplyI, RandomSupplyO)
%	This predicate builts a "Tree" in type "TreeType", with a
%	set "Depth".
%	TreeType defines the type of the "Tree", 0 means full tree, and 1
%	means grow tree.  Depth sets the maximum depth of the "Tree".
:- pred init_individual(int, int, s_expression, supply, supply).
:- mode init_individual(in, in, out, mdi, muo) is det.

%===============================================================================
:- implementation.

:- import_module int, random, require.
:- import_module random_select, parameters.


init_individual(TreeType, Depth, I, RSI, RSO) :-
	(
		TreeType = 0 ->
		num_of_func_set(FuncSetAmt),
		my_random(FuncSetAmt, R, RSI, RSI1),
		I = init(TreeType, Depth - 1, R, RSI1, RSO)
	;
		num_of_func_set(FuncSetAmt),
		my_random(FuncSetAmt, R, RSI, RSI1),
		I = init(TreeType, Depth - 1, R, RSI1, RSO)
	).


% init(TreeType, Depth, RandomNumber, RandomSupplyI, RandomSupplyO) = Tree
%	This function picks a node of the "Tree" according to the
%	RandomNumber given.
:- func init(int, int, int, supply, supply) = s_expression.
:- mode init(in, in, in, mdi, muo) = out is det.

init(TreeType, Depth, R, RSI, RSO) = I :-
	(
		R = 0 ->
		I = aND(init(TreeType, Depth, RSI, RSI1),
			init(TreeType, Depth, RSI1, RSO))
	;
		R = 1 ->
		I = nand(init(TreeType, Depth, RSI, RSI1),
			init(TreeType, Depth, RSI1, RSO))
	;
		R = 2 ->
		I = x1,
		RSO = RSI
	;
		R = 3 ->
		I = x2,
		RSO = RSI
	;
		error("init failed!")
	).


% init(TreeType, Depth, RandomSupplyI, RandomSupplyO) = Tree
%	This function builds the "Tree" until the maximum depth, "Depth",
%	is reached.
:- func init(int, int, supply, supply) = s_expression.
:- mode init(in, in, mdi, muo) = out is det.

init(TreeType, Depth, RSI, RSO) = I :-
	(
		TreeType = 0 ->
		num_of_func_set(FuncSetAmt),
		(
			Depth > 0 ->
			my_random(FuncSetAmt, R, RSI, RSI1),
			I = init(TreeType, Depth - 1, R, RSI1, RSO)
		;
			num_of_term_set(TermSetAmt),
			my_random(TermSetAmt, R, RSI, RSO),
			( R = 0 -> I = x1 ;
			   I = x2 
			)
		)
	;
		num_of_func_set(FuncSetAmt),
		num_of_term_set(TermSetAmt),
		(
			Depth > 0 ->
			my_random(FuncSetAmt + TermSetAmt, R, RSI, RSI1),
			I = init(Depth - 1, R, RSI1, RSO)
		;
			my_random(TermSetAmt, R, RSI, RSO),
			( R = 0 -> I = x1 ;
			           I = x2 )
		)
	).

-------------- next part --------------
%===============================================================================
% File		: init_population.m
% Author	: Raymee Chau
% Date Created	:
% Last Modified	: 22/2/2001
%
% The predicates in this file initialises the first population using the
% "ramped half-and-half" generative method.
%===============================================================================

:- module init_population.

%===============================================================================
:- interface.

:- import_module array, random.


% init_population(Init_individual, Population, RandomSupplyI, RandomSupplyO)
%	This predicate initialises the "Population".
:- pred init_population(pred(int, int, T, supply, supply),
		array(T), supply, supply).
:- mode init_population(pred(in, in, out, mdi, muo) is det,
		out, mdi, muo) is det.

%===============================================================================
:- implementation.

:- import_module int, array, require.
:- import_module parameters, general, init_individual.


init_population(Init_individual, Population) -->
	{ pop_size(PopSize) },
	{ ind_min_depth(MinDepth) },
	{ ind_max_depth(MaxDepth) },
	{ PopSizeForEachDepth = div(PopSize, (MaxDepth - MinDepth + 1)) },
	(
		{ PopSize = 0 } ->
		{ make_empty_array(Population) }
	;
		call(Init_individual, 0, MinDepth, I),
		{ init(PopSize, I, Array0) },
		init_population(Init_individual, 1, MinDepth,
			PopSize, 1, PopSizeForEachDepth, 1, Array0, P) ->
		{ Population = P }
	;
		{ error("init_population/4 failed!") }
	).


% init_population(Init_individual, TreeType, TreeDepth, PopSize,
%    PopSizeCount, PopSizeForEachDepth, PopSizeForEachDepthCount,
%    CurrentPopulation, FinalPopulation, RandomSupplyI, RandomSupplyO)
%	This predicate implements the "ramped half-and-half" generative
%	method to initialise the population.
%	Note : the commented lines are used to ensure that all the
%	       individuals in the population are different.
:- pred init_population(pred(int, int, T, supply, supply), int, int, int,
		int, int, int, array(T), array(T), supply, supply).
:- mode init_population(pred(in, in, out, mdi, muo) is det, in, in, in,
		in, in, in, array_di, array_uo, mdi, muo) is det.

init_population(Init_individual, TreeType, Depth, PopSize, PopSizeCount,
	PopSizeForEachDepth, Count, Array0, Population) -->
	(
		{ PopSizeCount = PopSize },
		{ Count = PopSizeForEachDepth } ->
		{ Population = Array0 }
	;
		{ PopSizeCount = PopSize - 1 } ->
		call(Init_individual, TreeType, Depth, I),
%		(
%			{ is_exist(I, Array0, PopSizeCount) } ->
%			init_population(Init_individual, TreeType,
%				Depth, PopSize, PopSizeCount,
%				PopSizeForEachDepth, Count,
%				Array0, Population)
%		;
			{ set(Array0, PopSizeCount, I, Array1) },
			{ Population = Array1 }
%		)
	;
		{ PopSizeCount < PopSize },
		{ Count = PopSizeForEachDepth } ->
		init_population(Init_individual, TreeType, Depth + 1,
			PopSize, PopSizeCount, PopSizeForEachDepth,
			0, Array0, Population)
	;
		{ PopSizeCount < PopSize },
		{ Count = PopSizeForEachDepth - 1 } ->
		call(Init_individual, TreeType, Depth, I),
%		(
%			{ is_exist(I, Array0, PopSizeCount) } ->
%			repeat_init_individual(
%				Init_individual, TreeType, Depth,
%				Array0, PopSizeCount, I1_1),
%			{ TreeType1 is (TreeType + 1) mod 2 },
%			{ set(Array0, PopSizeCount, I1_1, Array1) },
%			{ PopSizeCount1 is PopSizeCount + 1 },
%			{ Count1 is Count + 1 }
%		;
			{ TreeType1 is (TreeType + 1) mod 2 },
			{ set(Array0, PopSizeCount, I, Array1) },
			{ PopSizeCount1 is PopSizeCount + 1 },
			{ Count1 is Count + 1 }
			,
%		),
		init_population(Init_individual, TreeType1, Depth + 1,
			PopSize, PopSizeCount1, PopSizeForEachDepth,
			Count1, Array1, Population)
	;
		{ Count < PopSizeForEachDepth } ->
		call(Init_individual, TreeType, Depth, I1),
%		(
%			{ is_exist(I1, Array0, PopSizeCount) } ->
%			repeat_init_individual(
%				Init_individual, TreeType, Depth,
%				Array0, PopSizeCount, I1_1),
%			{ TreeType1 is (TreeType + 1) mod 2 },
%			{ set(Array0, PopSizeCount, I1_1, Array1) },
%			{ PopSizeCount1 is PopSizeCount + 1 },
%			{ Count1 is Count + 1 }
%		;
			{ TreeType1 is (TreeType + 1) mod 2 },
			{ set(Array0, PopSizeCount, I1, Array1) },
			{ PopSizeCount1 is PopSizeCount + 1 },
			{ Count1 is Count + 1 }
			,
%		),
		call(Init_individual, TreeType1, Depth, I2),
%		(
%			{ is_exist(I2, Array1, PopSizeCount) } ->
%			repeat_init_individual(
%				Init_individual, TreeType1, Depth,
%				Array1, PopSizeCount, I2_1),
%			{ set(Array1, PopSizeCount1, I2_1, Array2) },
%			{ PopSizeCount2 is PopSizeCount1 + 1 },
%			{ Count2 is Count1 + 1 }
%		;
			{ set(Array1, PopSizeCount1, I2, Array2) },
			{ PopSizeCount2 is PopSizeCount1 + 1 },
			{ Count2 is Count1 + 1 }
			,
%		),
		init_population(Init_individual, TreeType,
			Depth, PopSize, PopSizeCount2,
			PopSizeForEachDepth, Count2,
			Array2, Population)
	;
		{ error("init_population/11 failed!") }
	).


% repeat_init_individual(Init_individual, TreeType, TreeDepth,
%    CurrentPopulation, CurrentPopulationPointer, Individual,
%    RandomSupplyI, RandomSupplyO)
%	This predicate ensures that the new "Individual" that will be added
%	to the "CurrentPopulation" is not in the "CurrentPopulation.
:- pred repeat_init_individual(pred(int, int, T, supply, supply),
		int, int, array(T), int, T, supply, supply).
:- mode repeat_init_individual(pred(in, in, out, mdi, muo) is det,
		in, in, in, in, out, mdi, muo) is det.

repeat_init_individual(Init_individual, TreeType, Depth, Array, N, I) -->
	call(Init_individual, TreeType, Depth, Ind),
	(
		{ is_exist(Ind, Array, N) } ->
		repeat_init_individual(
			Init_individual, TreeType, Depth, Array, N, I)
	;
		{ I = Ind }
	).
-------------- next part --------------
%===============================================================================
% File		: main.m
% Author	: Raymee Chau
% Date Created	: 
% Last Modified	: 21/2/2001
%
% This file is the start of the GP for Koza's "Simple Symbolic Regression".
% It initialises the seed for generating random numbers, chooses the
% fitness cases randomly, initilises the population, and call the solve
% predicate to find the solution.
%===============================================================================

:- module main.

%===============================================================================
:- interface.

:- import_module io.


:- pred main(io__state, io__state).
:- mode main(di, uo) is det.

:- pred genloop(int, io__state, io__state).
:- mode genloop(in, di, uo) is det.

:- pred oneGen(int, io__state, io__state).
:- mode oneGen(in, di, uo) is det.

%===============================================================================
:- implementation.

:- import_module io, random, require.
:- import_module time, float, std_util, int.
:- import_module parameters.
:- import_module init_population, init_individual.

main(A, B) :-
	noruns(Runs),
        genloop(Runs, A,B ).

genloop(Runs, A, B) :-
        ( Runs > 1 ->
            oneGen(Runs, A, C),
            R1 is Runs - 1,
            genloop(R1, C, B)
          ; 
	    oneGen(Runs, A, B)

		
        ).

oneGen(Runs) -->
	% Initialise a random number using either a seed created manually
	% or a seed created by time.
	(
		{ seed_typ(manual, Seed) } ->
		{ init(Seed, I) }
	;
		{ seed_typ(random, _) } ->
		time(T),
		print("Runs : "), nl,
		print(Runs), nl, nl,
		print("Time : "), nl,
		print(gmtime(T)), nl, nl,
		{ F_to_I = round_to_int(difftime(mktime(
			tm(0,0,0,0,0,0,0,yes(standard_time))), T)) },
		{ init(F_to_I, I) },
		print("Seed : "), nl,
		print(F_to_I), nl, nl
	;
		{ error("no default seed yet!") }
	),


	{ Init_individual = init_individual },
	{ init_population(Init_individual, P, I, _) },
	print("Input : "), nl,
	print(P), nl, nl,
	nl.
-------------- next part --------------
%===============================================================================
% File		: parameters.m
% Author	: Raymee Chau
% Date Created	: 
% Last Modified	: 20/2/2001
%
% This file contains all the parameters required for Koza's "Simple Symbolic
% Regression".  It also conatins the functions of function set.
%===============================================================================

:- module parameters.

%===============================================================================
:- interface.

%-------------------------------------------------------------------------------
% rand_typ defines the type of seed for the random generator.
:- type rand_typ
	--->	default		% not implemented
	;	random		% uses timer to create seed
	;	manual.		% insert your own seed integer


% s_expression holds the s-expression of a tree.
:- type s_expression
	--->	plus(s_expression, s_expression)	% function
	;	diff(s_expression, s_expression)	% function
	;	times(s_expression, s_expression)	% function
	;	divide(s_expression, s_expression)	% function
	;	aND(s_expression, s_expression)		% function
	;	nand(s_expression, s_expression)	% function
	;	oR(s_expression, s_expression)		% function
	;	nor(s_expression, s_expression)		% function
	;	sin(s_expression)			% function
	;	cos(s_expression)			% function
	;	exp(s_expression)			% function
	;	rln(s_expression)			% function
	;	x1					% terminal
	;	x2					% terminal
	;	x3					% terminal
	;	x4					% terminal
	;	x5					% terminal
	;	x6					% terminal
	;	x					% terminal
	;	one.					% terminal

%-------------------------------------------------------------------------------
% seed_typ(T, Seed)
%	T = random -> system would use its timer to create the seed
%	T = manual -> an integer, Seed, will be the seed integer
:- pred seed_typ(rand_typ, int).
:- mode seed_typ(out, out) is det.


% gen_run(MaxGenerations)
%	Specifies the maximum number of generations that the program is
%	going to run.
:- pred gen_run(int).
:- mode gen_run(out) is det.

%values(X1,X2,X3,X4,X5,X6)
% Specifies the boolean test cases
:- type values
	---> values(
		x1 :: int,
		x2 :: int,
		x3 :: int,
		x4 :: int,
		x5 :: int,
		x6 :: int
	).

% pop_size(Size)
%	Specifies the population size of each generation.
:- pred pop_size(int).
:- mode pop_size(out) is det.


% num_of_fitness_cases(N)
%	Set the amount of data points (x, y) it is using for calculating
%	fitness.
:- pred num_of_fitness_cases(int).
:- mode num_of_fitness_cases(out) is det.


% num_of_func_set(N)
%	Specifies the size of the function set.
%	In this case, the function set has a size of 8, i.e. N = 8, as
%	Function set = { +, -, *, /, sin, cos, exp, log }
:- pred num_of_func_set(int).
:- mode num_of_func_set(out) is det.


% num_of_term_set(N)
%	Specifies the size of the terminal set.
%	In this case, N = 1, as Terminal set = { x }
:- pred num_of_term_set(int).
:- mode num_of_term_set(out) is det.


% ind_min_depth(N)
%	Set the minimum depth of the trees for initiating the population.
:- pred ind_min_depth(int).
:- mode ind_min_depth(out) is det.


% ind_max_depth(N)
%	Set the maximum depth for initialisating the population or generating
%	a branch for mutation.
:- pred ind_max_depth(int).
:- mode ind_max_depth(out) is det.


% crossover_rate(N)
%	Defines the percentate of the population that will be crossovered.
%	0.0 <= N <= 1.0
:- pred crossover_rate(float).
:- mode crossover_rate(out) is det.


% mutation_rate(N)
%	Defines the percentage of the population that will be mutated.
%	0.0 <= N <= 1.0
:- pred mutation_rate(float).
:- mode mutation_rate(out) is det.


% tournament_selection_size(N)
%	Defines the size of the tournament selection.
:- pred tournament_selection_size(int).
:- mode tournament_selection_size(out) is det.


% target_value(N)
%	Defines the value that the generations has to reach to be determined
%	as the solution.
:- pred target_value(float).
:- mode target_value(out) is det.

%noruns(R)
:- pred noruns(int).
:- mode noruns(out) is det.

% hit_definition(N) - not used!
%	Defines the closeness that the curve is required to reach to
%	score a hit.
:- pred hit_definition(float).
:- mode hit_definition(out) is det.


% hit_score(N) - not used!
%	Defines the score that the program is required to get to,
%	in order for it to stop and print out the result. 
:- pred hit_score(int).
:- mode hit_score(out) is det.


% curve_interval(Low, High)
%	Defines the boundaries of the curve you want to fit.
:- pred curve_interval(float, float).
:- mode curve_interval(out, out) is det.


% plus(A, B) = Soln
%	This function does a normal sum : A + B = Soln
:- func plus(float, float) = float.
:- mode plus(in, in) = out is det.


% diff(A, B) = Soln
%	This function does a subtraction : A - B = Soln
:- func diff(float, float) = float.
:- mode diff(in, in) = out is det.


% times(A, B) = Soln
%	This function mutiplies : A * B = Soln
:- func times(float, float) = float.
:- mode times(in, in) = out is det.


% divide(A, B) = Soln
%	This function does a division : A / B = Soln
%	However for this division function, if B = 0 -> Soln = 1.
:- func divide(float, float) = float.
:- mode divide(in, in) = out is det.


% rln(A) = Soln
%	This function finds the log of the absolute value of A :
%		ln(|A|) = Soln
%	But when A = 0, Soln = 0
:- func rln(float) = float.
:- mode rln(in) = out is det.


%===============================================================================
:- implementation.

:- import_module float, math.

seed_typ(random, -981435622).		% random
%seed_typ(manual, -982910377).

gen_run(50).

pop_size(2000).

num_of_fitness_cases(16).

num_of_func_set(2).

num_of_term_set(2).

ind_min_depth(2).

ind_max_depth(10).

crossover_rate(0.90).

mutation_rate(0.10).

tournament_selection_size(3).

target_value(0.01).

hit_definition(0.01).

hit_score(20).

curve_interval(-1.0, 1.0).

noruns(50).

plus(N1, N2) = N1 + N2.

diff(N1, N2) = N1 - N2.

times(N1, N2) = S :-
	(
		( abs(N1) = 0.0; abs(N2) = 0.0 ) ->
		S = 0.0
	;
		S = N1 * N2
	).

divide(N1, N2) = S :-
	(
		abs(N2) = 0.0 ->
		S = 1.0
	;
		S = N1 / N2
	).

rln(N1) = S :-
	(
		abs(N1) = 0.0 ->
		S = 0.0
	;
		S = ln(abs(N1))
	).
-------------- next part --------------
%===============================================================================
% File		: random_select.m
% Author	: Raymee Chau
% Date Created	:
% Last Modified	: 22/2/2001
%
% The predicates in this file generates random number, and does random
% selections from an array.
%===============================================================================

:- module random_select.

%===============================================================================
:- interface.

:- import_module array, random.


% my_random(Num, Random, RandomSupplyI, RandomSupplyO)
%	This predicate generates a random integer, "Random", between 0
%	and Num.
:- pred my_random(int, int, supply, supply).
:- mode my_random(in, out, mdi, muo) is det.

% my_random_float(Num, Random, RandomSupplyI, RandomSupplyO)
%	This predicate returns a random float, "Random", between 0 and Num.
:- pred my_random_float(float, float, supply, supply).
:- mode my_random_float(in, out, mdi, muo) is det.


% random_select(Array1, Array2, Element1, Element2, N,
%    RandomSupplyI, RandomSupplyO)
%	This predicate selects a random, Nth, element, Element1, from 
%	an array, Array1, and the Nth Element2 from Array2.
:- pred random_select(array(T), array(T1), T, T1, int, supply, supply).
:- mode random_select(in, in, out, out, out, mdi, muo) is det.


% random_select_n is not used in this program!
%	This predicate selects n elements from the arrays.
:- pred random_select_n(array(T), array(T1), int,
		array(T), array(T1), supply, supply).
:- mode random_select_n(in, in, in, out, out, mdi, muo) is det.

%===============================================================================
:- implementation.

:- import_module int, float, array, random, std_util, require.


my_random(Num, Random) -->
	random(R),
	{ to_float(R, R_float) },
	randmax(RandMax),
	{ to_float(RandMax + 1, RandMax_float) },
	{ to_float(Num, Num_float) },
	{ Rand_float = (R_float / RandMax_float) * Num_float },
	{ Random = floor_to_int(Rand_float), ! }.


my_random_float(Num, Random) -->
	random(R),
	{ to_float(R, R_float) },
	randmax(RandMax),
	{ to_float(RandMax + 1, RandMax_float) },
	{ Random = (R_float / RandMax_float) * Num, ! }.


random_select(Array, Array_val, SelectedE, SelectedE_val, RanE) -->
	{ size(Array, Size) },
	my_random(Size, RanE),
	{ lookup(Array, RanE, SelectedE) },
	{ lookup(Array_val, RanE, SelectedE_val) }.


random_select_n(Array, Array_val, N, Selected, Selected_val) -->
	(
		{ size(Array, Size) },
		{ N >= 0 },
		{ N =< Size } ->
		random_select_with_replace(Array, Array_val,
			N, Selected, Selected_val)
	;
		{ error("random_select_n failed!") }
	).


:- pred random_select_with_replace(array(T), array(T1), int,
		array(T), array(T1), supply, supply).
:- mode random_select_with_replace(in, in, in, array_uo, array_uo,
		mdi, muo) is det.

random_select_with_replace(Array, Array_val, N, Selected, Selected_val) -->
	(
		{ N = 0 } ->
		{ make_empty_array(Selected) },
		{ make_empty_array(Selected_val) }
	;
		random_select(Array, Array_val, S, S_val, _),
		{ init(N, S, Array0) },
		{ init(N, S_val, Array_val0) },
		{ N1 is N - 1 },
		random_select_with_replace2(Array, Array_val, N1, 1, 
			Array0, Array_val0, Sel, Sel_val) ->
		{ Selected = Sel },
		{ Selected_val = Sel_val }
	;
		{ error("random_select_with_replace failed!") }
	).


:- pred random_select_with_replace2(array(T), array(T1), int, int,
		array(T), array(T1), array(T), array(T1), supply, supply).
:- mode random_select_with_replace2(in, in, in, in,
		array_di, array_di, array_uo, array_uo, mdi, muo) is semidet.

random_select_with_replace2(Array, Array_val, Len, N, 
	Array0, Array_val0, Selected, Selected_val) -->
	(
		{ N >= Len } ->
		{ Selected = Array0 },
		{ Selected_val = Array_val0 }
	;
		random_select(Array, Array_val, S, S_val, _),
		{ set(Array0, N, S, Array1) },
		{ set(Array_val0, N, S_val, Array_val1) },
		{ N1 is N + 1 },
		random_select_with_replace2(Array, Array_val,
			Len, N1, Array1, Array_val1, Selected, Selected_val)
	).



More information about the users mailing list