[m-dev.] for review: quickcheck user guide

Mark Anthony BROWN dougl at cs.mu.OZ.AU
Thu Feb 15 18:16:44 AEDT 2001


Xiao Chun Simon MEI writes:

...

> Index: quickcheck/tutes/T4.html
> ===================================================================
> RCS file: T4.html
> diff -N T4.html
> --- /dev/null	Wed Nov 15 09:24:47 2000
> +++ T4.html	Mon Feb  5 16:01:53 2001
> @@ -0,0 +1,74 @@
> +<html>
> +<head> 
> +        <TITLE> QuickCheck </TITLE>
> +</head>
> +<H1> QuickCheck Tutorial 4 </H1>
> +
> +<a href="index.html">Back to main</a>
> +<h3> Summary - Invariant Function & Property </h3>
> +
> +<pre>
> +The invariant function is of the form 
> +	:- func XXXXXXXX(T,  T1, T2 ...) = property
> +        :- mode XXXXXXXX(in, in, in ...) = out.
> +The inputs can be of most types (details next tutorial), however only arity 
> +0 to 4 are implemented. The output must be property, defined as :

Be careful that these hard coded numbers are kept consistent with the
actual implementation.  I think you can support higher arities now,
right?

> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +        :- type property == list(flag).
> +
> +        :- type flag 
> +                --->    yes
> +                ;       no      
> +                ;       trivial
> +                ;       info(univ)      
> +                ;       condition.
> +</pre></tr></table>
> +What ever happens inside XXXXXXXX, quickcheck does not care; it only looks
> +at the output property. Any form of property is valid, in the sense that the 
> +qcheck will not abort/crash. However not all forms of property is sensible.   

Mentioning that qcheck is not designed to abort in this circumstance is
ok, but it is obvious that qcheck is not designed to crash ;-)
So I would change "abort/crash" to just "abort".

> +One could return [], or [yes, no, yes, no]. Quickcheck analyzes property in

s/property/the property/

> +the following order:
> +	1	is condition (1 or more) in the list(flag) ?
> +		if yes, increment PRE-CONDITION counter and stop analyze

s/analyze/analyzing/

> +		if no, goto 2
> +	2	is trivial (1 or more) in the list ?
> +		if yes, increment TRIVIAL counter, goto 3
> +		if no, goto 3
> +	3	gets all the info(univ) (if any) in the list, merge that with

s/gets/get/

> +		the master list for distribution, goto 4
> +	4	is no (1 or more) in the list ?
> +		if no, increment YES counter and stop
> +		if yes, increment NO counter and stop, other function will pick

s/other/another/

> +		up that the No counter has been increased, and stops the whole

s/stops/stop/

> +		qcheck.	 
> +So, [] will increase the YES counter, and [yes, no, yes, no] will increase the
> +NO counter.

I think the above list could be improved if the items were written as
complete sentences.

> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- func T  `===` T  = property.
> +:- mode in `===` in = out is det.
> +Left `===` Right		Left == Right	return [yes]
> +				Left != Right	return [no]
> +
> +:- func (pred) `===>` property = property.
> +:- mode in((pred) is semidet) `===>` in = out is det.
> +Left `===>` Right		Left fails	return [condition | Right]
> +				Left Succeeds	return Right

s/Succeeds/succeeds/

> +
> +:- func bool `===>` property = property.
> +:- mode in `===>` in = out is det.
> +Left `===>` Right		Left == no	return [condition | Right]
> +				Left == yes	return Right
> +
> +:- func to_trivial(T, T, property) = property.
> +:- mode to_trivial(in, in, in) = out is det.
> +to_trivial(A, B, C) = D		A == B		return [trivial | C]
> +				A != B		return C

To be consistent with the other examples, you should remove the " = D".

> +
> +:- func T `>>>` property = property. 
> +:- mode in `>>>` in = out is det.
> +Left `>>>` Right				return [ info(univ(Left)) | Right ]
> +</pre></tr></table>
> +
> +
> Index: quickcheck/tutes/T5.html
> ===================================================================
> RCS file: T5.html
> diff -N T5.html
> --- /dev/null	Wed Nov 15 09:24:47 2000
> +++ T5.html	Mon Feb  5 16:01:53 2001
> @@ -0,0 +1,184 @@
> +<html>
> +<head> 
> +        <TITLE> QuickCheck </TITLE>
> +</head>
> +Files : 
> +<a href="use51.m">use51.m</a><BR>
> +<a href="index.html">Back to main</a>
> +<H1> QuickCheck Tutorial 5 </H1>
> +<h3> Generators - Basic </h3>
> +
> +<pre>
> +The invariant function is of the form 
> +	:- func XXXXXXXX(T,  T1, T2 ...) = property
> +        :- mode XXXXXXXX(in, in, in ...) = out.
> +Quickcheck generates random value for each input argument at run time.

s/value/values/

> +Currently quickcheck have default generators for the following types :

s/have/has/

> +	0	equivalent type
> +	1	int
> +	2	char
> +	3	float
> +	4	string
> +	5	discriminated union
> +	6	some functions
> +plus type 7 which is any thing the user has written a generator for.
> +
> +Acutally there is no code written to handle equivalent types. But it works 
> +as if the compiler replaced all the equivalent types with their real type
> +before compiling. So any equivalent type with real type that fits into 
> +types 0-7 will work.
> +

I don't think type 7 really fits under the heading of "default
generator", since it is explicitly given by the user.

Where you say "some functions", it would be useful to either give some
more specific information, or else refer the user to where they could
find more specific information (e.g. tutorial 8).

Overall, I'd prefer it if you gave an inductive definition of which
types have default generators.  By this I mean that you should:

	- List basic types that have generators.
	- List compound types that have generators, provided that the
	  components of that type have generators.

For example, you could say something like:

	The following types have default generators:
	
		- int
		- char
		- float
		- string
		- some functions (see ...)
		- any type defined as a discriminated union, provided
		  that all types in the body of the definition have
		  default generators
		- any type defined as being equivalent to a type with a
		  default generator

I'll leave the precise details up to you.

> +Default for int is rand_int/2, which has distribution (roughly):

s/Default/The default generator/

Similarly for the other examples.

> +50%	even distribution between [-100, 100]
> +50%	even distribution between [-2^31, 2^31]

Why "roughly"?  Isn't this the exact distribution?

> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- func rand_int(rnd, rnd) = int.
> +:- mode rand_int(in, out) = out is det.
> +rand_int(BS0, BS) = Int :-
> +	Temp = rand_allint(BS0, BS1) rem 2,
> +	(if	Temp = 0 
> +	 then
> +		irange(-100, 100, Int, BS1, BS)
> +	 else
> +		Int = rand_allint(BS1, BS)
> +	).  
> +
> +:- func rand_allint(rnd, rnd) = int.
> +:- mode rand_allint(in, out) = out is det.
> +rand_allint(BS0, BS) = Int :-
> +	next(1, Sign, BS0, BS1),
> +	next(31, TempInt, BS1, BS),
> +	( Sign > 0 ->
> +	    Int =  TempInt 
> +	;
> +	    Int = -TempInt
> +	).
> +</pre></tr></table>
> +Default for char is rand_char/2, with even spread over 
> +char__to_int(Char, X) where X is (-1000, 1000).
> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- func rand_char(rnd, rnd) = char.
> +:- mode rand_char(in, out) = out is det.
> +rand_char(RS0, RS) = Char :-
> +       		Int = rand_allint(RS0, RS1) rem 1000,
> +		(if	char__to_int(Char0, Int) 
> +		 then
> +		 	Char = Char0,
> +			RS = RS1
> +		 else
> +		 	Char = rand_char(RS1, RS)
> +		).
> +</pre></tr></table>
> +Default for float is rand_float/2, which has even distribution
> +over all possible value for a float in a 32bits machine.

I was a bit misled by this, since I would think an "even" distribution
would have just as much chance of picking a number between 0 and 1 as it
would have of picking a number between 1000000 and 1000001.  But this is
not the distribution you are using.  I think it would be better to say
"... which has an even distribution over all discrete values for a
32-bit float."

In any case, this is not completely accurate because you don't appear to
ever produce NaN, +Inf or -Inf, and it also appears that there would be
greater chance of producing 0.0 than anything else.  So I think it would
be preferable to say "roughly an even distribution ...".

> +If machine is less then 32bits, overfloat occurs. It should still
> +cover all possible values, but may alter distribution.
> +If machine is more than 32bits, rand_float/2 will miss some values 
> +but retains even distribution. 
> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- func rand_float(rnd, rnd) = float. 
> +:- mode rand_float(in, out) = out is det.
> +rand_float(BS0, BS) = Flt :-
> +	next(31, Mant0, BS0, BS1),
> +        next(1, Sign, BS1, BS2),
> +        ( Sign > 0 ->
> +            Mant = Mant0
> +        ;
> +            Mant = -Mant0
> +        ),
> +        next(7, Exp, BS2, BS3),
> +        next(1, ExpSign, BS3, BS),
> +        Flt0 = float(Mant) * pow(2.0, Exp),
> +        ( ExpSign > 0, Flt0 \= 0.0 ->
> +            Flt = 1.0/Flt0
> +        ;
> +            Flt = Flt0
> +        ).
> +</pre></tr></table>
> +Default for string is rand_string/2, each element is generated by 
> +rand_char/2. 
> +0.9^0 * 0.1	chance being string length == 0
> +0.9^1 * 0.1	chance being string length == 1
> +0.9^2 * 0.1	chance being string length == 2 
> +...etc... 	
> +so the average string length is Sum(0.1* 0.9^N * N) where N <- {0, infinity} 

So the average string length is 10?

> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre> 
> +:- func rand_string(rnd, rnd) = string.
> +:- mode rand_string(in, out) = out is det.
> +rand_string(RS0, RS) = X :-
> +	     	gen(Charlist,[],[{type_of(['A']),[{10,[]},{90,[]}]}],[],RS0,RS),
> +		string__from_char_list(Charlist,X).
> +</pre></tr></table>
> +A sample qcheck which use types 0-4 (use51.m):
> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- module use51.
> +
> +:- interface.
> +
> +:- type marks == int.
> +
> +:- use_module io.
> +
> +:- pred main(io__state, io__state).
> +:- mode main(di, uo) is det.
> +
> +%---------------------------------------------------------------------------%
> +
> +:- implementation.
> +
> +:- import_module int, char, float, string, list.
> +:- import_module qcheck.
> +
> +%---------------------------------------------------------------------------%
> +
> +main -->
> +     	qcheck(qcheck__f(junk), "just to show the inputs", 5, [], []).
> +
> +:- func junk(marks, char, float, string) = property.
> +junk(A, B, C, D) = 
> +	{A,B,C,D} `>>>` [yes].
> +</pre></tr></table>
> +Few thing to note in use51.m :

"There are a few things to note about use51.m:"

> +<h4>
> +	qcheck(qcheck__f(junk), "just to show the inputs", 5, [], []).
> +</h4>
> +qcheck/7 takes more parameters than qcheck/4.

That is self-evident.

The 3rd argument is an int, 
> +which specify how many times to run,

s/specify/specifies/

> 5 in use51.m (default is 100).

I would make that a separate sentence and say:

	In this example 5 tests are run, but the default is 100.

Ignore
> +other auguments.

It would be better to say "The other arguments will be described later."

> +<h4>
> +	junk(A, B, C, D) = 
> +		{A,B,C,D} `>>>` [yes].
> +</h4>
> +the invariant function doesn't do any testing, it always succeeds. But 
> +`>>>` collects all the inputs.
> +A Sample output 
> +<h4>
> +	Test Description : just to show the inputs
> +	Number of test cases that succeeded : 5
> +	Number of trivial tests : 0
> +	Number of tests cases which failed the pre-condition : 0
> +	Distributions of selected argument(s) : 
> +	1     {-50, '4', -3.55475907854864e+25, "\241r\371~~\316\002LJ~\204\246"}
> +	1     {27, '\342', -311727734390784., "\377g.\001"}
> +	1     {1389908257, '8', 2.63071847153664e+15, "\342"}
> +	1     {-90973704, '<', -2.10559053720692e-22, ""}
> +	1     {-896549770, 's', 7.72155851221736e+30, "[\230m\304\2561\254Q"}
> +</h4>
> +The char and string output doesn't look pretty, since most are not printable,
> +eg: \342, \254 
> +
> +

I'm not sure it's worth mentioning the following point here, unless you
give some rationale as to why the proposed change would be better.

> +Possible improvement of rand_float/2 & rand_int/2 which will give higher chance 
> +of generating 0, or small numbers.
> +
> +
> +
> +
> +
> +
> +
> Index: quickcheck/tutes/T6.html
> ===================================================================
> RCS file: T6.html
> diff -N T6.html
> --- /dev/null	Wed Nov 15 09:24:47 2000
> +++ T6.html	Mon Feb  5 16:01:53 2001
> @@ -0,0 +1,330 @@
> +<html>
> +<head> 
> +        <TITLE> QuickCheck </TITLE>
> +</head>
> +Files : 
> +<a href="use62.m">use62.m</a><BR>
> +<a href="index.html">Back to main</a>
> +<H1> QuickCheck Tutorial 6 </H1>
> +<h3> Generators - Discriminated union &  Specific Frequency</h3>
> +<pre>
> +
> +Default generator is able to generate discriminated unions which are composed 
> +of any thing that fits into types 0-7. In default frequency mode, all branches 
> +at each level has the same chance of being selected.

s/has/have/

> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- func rand_union(type_desc, list(frequency), list({type_desc, 
> +		   list(frequency)}), list(user_gen_type), rnd, rnd) = univ.
> +:- mode rand_union(in,in,in,list_skel_in(user_gen_inst),in,out) = out is det.
> +</pre></tr></table>
> +use61.m shows the randomly generated value for the type bullet, with default
> +frequency : 
> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- module use61.
> +
> +:- interface.
> +
> +:- use_module io.
> +
> +:- pred main(io__state, io__state).
> +:- mode main(di, uo) is det.
> +
> +%---------------------------------------------------------------------------%
> +
> +:- implementation.
> +
> +:- import_module list.
> +:- import_module qcheck.
> +
> +%---------------------------------------------------------------------------%
> +%	arbitrary user-defined types for testing purposes
> +%---------------------------------------------------------------------------%
> +
> +:- type bullet 
> +        --->    good(color) 
> +        ;       inaccurate(color) 
> +        ;      	defective(color).
> +
> +:- type color
> +	--->	black
> +	;	white.	
> +
> +%---------------------------------------------------------------------------%
> +main -->
> +        qcheck(qcheck__f(prop1), "even distribution", 1000, [], []).
> +
> +:- func prop1(bullet) = property.
> +prop1(X) = X `>>>` [yes].
> +</pre></tr></table>
> +Sample output shows the expected distribution :
> +<h4>
> +	Test Description : even distribution
> +	Number of test cases that succeeded : 1000
> +	Number of trivial tests : 0
> +	Number of tests cases which failed the pre-condition : 0
> +	Distributions of selected argument(s) : 
> +	150     inaccurate(white)
> +	153     defective(black)
> +	165     inaccurate(black)
> +	176     good(white)
> +	178     defective(white)
> +	178     good(black)
> +</h4>
> +
> +<h3> Specific Frequency</h3>
> +Specific Frequency changes the a term's default frequency (which is evenly spread) 

s/the a term's/a type's/

> +to one the user have provided. An example :

s/have/has/

> +Suppose there are two bullet manufacturer. 

s/manufacturer/manufacturers/

> +Company_W 's bullet are painted black, and 50% good ones, 10% inaccurate, 40% defective.    
> +Company_B 's bullet are painted white, and 40% good ones, 30% inaccurate, 30% defective.
> +A good bullet always hits its target, inaccurate one misses 50% of time, defective bullet
> +always misses. And color does affect performance.
> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- type frequency
> +	--->	{int, list(list(frequency))}.
> +</pre></tr></table>
> +frequency defines the relative chance of a branch being selected, plus information of that
> +branch's sub-branches.

s/information of/gives information about/

> +list(frequency) contains distribution information about 1 discrimated union, ie: the list 
> +should contain frequencies for all possible branches.

I would suggest "should contain a frequency for each possible branch."

> +list(list(frequency)) contains distribution information about a list of discrimated unions.
> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>

In the other tutorials, a table like this is used to display Mercury
code, but this table contains a written example.  This is a bit
inconsistent -- I think you should display this example normally (i.e.
not in a table).

> +Let's try to describe Company_W's bullet, Bullet is discrimated union, so the right format is :
> +	list(frequency)
> +There are 3 top level branches for Type Bullet, so the list is 3 length long :

I would say "so the list has length 3".

> +	[frequency_good, frequency_inaccurate, frequency_defective] 
> +
> +	:- type frequency 	= {int, list(list(frequency))}.
> +	frequency_good		= {50,  ...something_good...}
> +	frequency_inaccurate 	= {10,  ...something_inaccurate...}
> +	frequency_defective 	= {40,  ...something_defective...}
> +
> +<a href="numbers.html">Click here to see what the numbers mean</a>

Why a separate page?  It would be better to explain here what the numbers
mean.

> +
> +...something_good... has format list(list(frequency)), and should describe the argument(s) of good/1.
> +good/1 only has 1 arguments, thus the list of 1 element, 
> +	[ info_color ]
> +info_color has format list(frequency), color has 2 branches, thus this list is of 2 elements.
> +	[ frequency_black, frequency_white ] 
> +
> +	:- type frequency 	= {int, list(list(frequency))}.
> +	frequency_black		= {100, ...something_black...}
> +	frequency_white 	= {0,   ...something_white...}
> +
> +something_black has format list(list(frequency)), and should describe the argument(s) of black/0.
> +black/0 has no argument, thus the list is [], likewise for white/0
> +(if instead of black/0, it's black/4 then the list would be length 4. OR [] when you get sick of 
> +specifying frequency and just want to use the default)

It would be worth making more of a point of this way of using defaults,
rather than just as a remark in parentheses.

> +	
> +So far:	     info_color	= [ frequency_black, frequency_white ]
> +			= [ {100, []}, 	{0, []}	]
> +Then:	 frequency_good = {50,  ...something_good...}	
> +			= {50,  [ info_color ] }
> +			= {50,  [ [ {100, []}, 	{0, []}	] ] }
> +
> +in this case ...something_good..., ...something_inaccurate... and ...something_defective are the same, 
> +since they all describe a list which contains Color that has the same distribution.
> +
> +So:	frequency_good 		= {50, [ [ {100, []}, {0, []} ] ] }
> +	frequency_inaccurate 	= {10, [ [ {100, []}, {0, []} ] ] }
> +	frequency_defective  	= {40, [ [ {100, []}, {0, []} ] ] }
> +
> +Then:		[frequency_good, frequency_inaccurate, frequency_defective] 
> +	=	[ {50, [ [ {100, []}, {0, []} ] ] },
> +		  {10, [ [ {100, []}, {0, []} ] ] },
> +		  {40, [ [ {100, []}, {0, []} ] ] }
> +		]
> +  			
> +For Company_W 's bullet , it's list(frequency) would be :
> +		[frequency_good, frequency_inaccurate, frequency_defective] 
> +	=	[ {40, [ [ {0, []}, {100, []} ] ] },
> +		  {30, [ [ {0, []}, {100, []} ] ] },
> +		  {30, [ [ {0, []}, {100, []} ] ] }
> +		]
> +</pre></tr></table>
> +The complete code (use62.m) :
> +<P>
> +<table border=0 width=100% bgcolor=#eeeee0><tr><td><pre>
> +:- module use62.
> +
> +:- interface.
> +
> +:- use_module io.
> +
> +:- pred main(io__state, io__state).
> +:- mode main(di, uo) is det.
> +
> +%---------------------------------------------------------------------------%
> +
> +:- implementation.
> +
> +:- import_module int, list, string.
> +:- import_module qcheck, rnd.
> +
> +%---------------------------------------------------------------------------%
> +%	arbitrary user-defined types for testing purposes
> +%---------------------------------------------------------------------------%
> +
> +:- type bullet 
> +        --->    good(color) 
> +        ;       inaccurate(color) 
> +        ;      	defective(color).
> +
> +:- type color
> +	--->	black
> +	;	white.	
> +
> +%---------------------------------------------------------------------------%
> +
> +main -->
> +	{ freq_B(B) },
> +	{ freq_W(W) },
> +        qcheck(qcheck__f(prop2), "bullet fight", 10000, [[],B,W], []).
> +
> +:- pred freq_B(list(frequency)).
> +:- mode freq_B(out) is det.
> +freq_B(Out) :-
> +	Out = [ {50, [ [ {100, []}, {0, []} ] ] },
> +                {10, [ [ {100, []}, {0, []} ] ] },
> +                {40, [ [ {100, []}, {0, []} ] ] }
> +              ].
> +
> +:- pred freq_W(list(frequency)).
> +:- mode freq_W(out) is det.
> +freq_W(Out) :-
> +	Out = [ {40, [ [ {0, []}, {100, []} ] ] },
> +                {30, [ [ {0, []}, {100, []} ] ] },
> +                {30, [ [ {0, []}, {100, []} ] ] }
> +              ].
> +
> +:- func prop2(int, bullet, bullet) = property.
> +prop2(Seed, B, W) = fight(Seed, B, W) `>>>` 
> +			({"ComB",B} `>>>` 
> +				({"ComW", W} `>>>` [yes])
> +			).
> +
> +:- func fight(int, bullet, bullet) = string.
> +:- mode fight(in, in, in) = out is det.
> +fight(Seed, B, W) = String :-
> +	rnd__init(Seed, RS0),
> +	B_hit = is_hit(B, RS0, RS1),
> +	W_hit = is_hit(W, RS1, _),
> +	(if		B_hit = W_hit
> +	 then
> +			String = "draw"
> +	 else if	B_hit > W_hit
> +	      then
> +			String = "B win"
> +	 else
> +			String = "W win"
> +	).
> +
> +:- func is_hit(bullet, rnd, rnd) = int.
> +:- mode is_hit(in, in, out) = out is det.
> +is_hit(Bullet, RS0, RS) = Int :-
> +	Temp = rand_allint(RS0, RS) rem 2,
> +	(
> +		Bullet = good(_),
> +		Int = 1
> +	;
> +		Bullet = inaccurate(_),
> +		(if	Temp = 0	
> +		 then		
> +			Int = 1
> +		 else
> +			Int = 0
> +		)
> +	;
> +		Bullet = defective(_),
> +		Int = 0
> +	).
> +</pre></tr></table>
> +In use62.m 
> +<h4>
> +main -->
> +         { freq_B(B) },
> +         { freq_W(W) },
> +         qcheck(qcheck__f(prop2), "bullet fight", 10000, [[],B,W], []).
> +</h4>
> +The 4th argument of qcheck/7 is for passing Specific Frequency. Because the
> +invariant function has three input arguments, qcheck/7 's 4th argument must
> +be list of 3.
> +	[[],B,W]
> +The 1st element [] of type list(frequency) is for type int, which doesn't make 
> +sense, since type int is not a discriminated union. That [] will be ignore when 
> +generating int, but it's presence is required.

I think that could be phrased better.  For example:

	The first argument of prop2/3 is of type int, so we wish to use
	the default rather than supply a specific frequency.  We
	therefore pass [] as the first element of the list, which tells
	qcheck to use the default generator for that type.

> +
> +A sample output:
> +<h4>
> +	Test Description : bullet fight
> +	Number of test cases that succeeded : 10000
> +	Number of trivial tests : 0
> +	Number of tests cases which failed the pre-condition : 0
> +	Distributions of selected argument(s) : 
> +	909     {"ComB", inaccurate(black)}
> +	2403     "B win"
> +	2533   	 "W win"
> +	2949     {"ComW", defective(white)}
> +	3012     {"ComW", inaccurate(white)}
> +	4017     {"ComB", defective(black)}
> +	4039     {"ComW", good(white)}
> +	5064     "draw"
> +	5074     {"ComB", good(black)}
> +</h4>
> +Regroup the output to make comparison :
> +
> +5074     {"ComB", good(black)
> +909      {"ComB", inaccurate(black)}
> +4017     {"ComB", defective(black)}
> +
> +4039     {"ComW", good(white)}
> +3012     {"ComW", inaccurate(white)}
> +2949     {"ComW", defective(white)}
> +
> +Note that ComB only makes black bullet; ComW only white. And their bullet quality is 
> +what was expected of them.
> +
> +2403     "B win"
> +2533   	 "W win"
> +5064     "draw"
> +
> +I was hoping to run 100000 or more tests to find which bullet is better. However the
> +stack overflowed at 100000 tests. The sample output is for only 10000 tests. At 10000
> +tests, both bullets performs relatively the same.
> +(Will look into this, make more effecient code)
> +(or default compiler no garbage collection)

I don't think it is worth mentioning these details here, except maybe to
say that for these frequencies, there is not much difference after 10000
tests.

If you want a better example, you could always change the frequencies in
the example program so that the outcome is a bit more obvious.

Incidentally, if you wish to increase the stack size, you can set it in
the MERCURY_OPTIONS environment variable when you run the executable.
See the user's guide for details on this.

> +
> +The key advantage of Specific Frequency over General Frequency is that it allows 
> +different frequency for the same type, where SF don't allow.  

s/frequency/frequencies/

I don't understand what you are trying to say with "where SF don't allow".

> +The draw back is that the frequency only goes as deep (down the branches) as the user
> +defines it, and amount of work blows up as levels of branches increases.

s/amount/the amount/
s/levels of branches/the depth/

> +
> +Walk through in generating a Company_B 's bullet :  
> +
> +	1	Enter generator with 
> +		SF = [ 	{50, [ [ {100, []}, {0, []} ] ] },
> +                	{10, [ [ {100, []}, {0, []} ] ] },
> +                	{40, [ [ {100, []}, {0, []} ] ] }
> +              	     ].
> +
> +	2	suppose 3rd branch is selected (40% chance of happening)
> +		the 3rd branch has only 1 term, extract  [ {100, []}, {0, []} ]
> +		from {40, [ [ {100, []}, {0, []} ] ] }
> +
> +	3	call generator that term with SF =  [ {100, []}, {0, []} ] 
> +
> +	4	Enter generator for the sub-branch (fot color) with 
> +		SF = [ {100, []}, {0, []} ]
> +		
> +	5	suppose 1st branch is selected, extract [] from {100, []}
> +
> +	6	since constructor black/0 has no argument, the generator stops
> +		the recursive call.
> +

I think the above list could be improved if the items were written as
sentences.

To be continued ...

--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list