[mercury-users] Bug(?) in rotd-1999-10-10

Robert Ernst Johann JESCHOFNIK rejj at cat.cs.mu.OZ.AU
Mon Oct 11 10:51:43 AEST 1999


heya.

Another issue with that (infamous) graphics project of mine.. I just
noticed that when using the rotd-1999-10-10 compiler, mgnuc gives warnings
about variables that may be used uninitialised, but with 0.8 it gives no
such warning.

I've included my code, and shall paste the relevant compiler messages
here.

Rob.
--
mmc --compile-to-c --grade asm_fast.gc     --use-subdirs -O 6
--intermodule-optimization   handle_input.m > handle_input.err 2>&1
mgnuc --grade asm_fast.gc    -DML_OMIT_ARRAY_BOUNDS_CHECKS       -I. -c
Mercury/cs/handle_input.c -o Mercury/os/handle_input.o
Mercury/cs/handle_input.c: In function `handle_input_module':
Mercury/cs/handle_input.c:2648: warning: `Rest' might be used
uninitialized in this function
Mercury/cs/handle_input.c:2710: warning: `Rest' might be used
uninitialized in this function
Mercury/cs/handle_input.c:2770: warning: `Rest' might be used
uninitialized in this function
Mercury/cs/handle_input.c:2829: warning: `Rest' might be used
uninitialized in this function
Mercury/cs/handle_input.c:2878: warning: `Rest' might be used
uninitialized in this function
Mercury/cs/handle_input.c:3504: warning: `Rest' might be used
uninitialized in this function

-------------- next part --------------
%-----------------------------------------------------------------------------%
%
% 433-380 Project, part A
% Robert Jeschofnik (rejj), 55572
%
% handle_input.m
%
% Written in Mercury, because C sucks.
%
% This module handles all the input - it grabs the command line args, and
% parses the scene description (and described .OFF) file(s), returning the
% scene (just the objects for part a)
%
%-----------------------------------------------------------------------------%

:- module handle_input.

:- interface.

:- import_module io, string, list, float, int, array.
:- import_module poly.

:- pred sanity_check_args(list(string), float, int, int).
:- mode sanity_check_args(in, out, out, out) is semidet.

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

:- pred read_scene_desc(world, world, io__state, io__state).
:- mode read_scene_desc(array_di, array_uo, di, uo) is det.

%-----------------------------------------------------------------------------%

:- implementation.

:- import_module char, require, array.
:- import_module poly.

:- pred check_io_result(io__result(list(char)), pred(T), pred(list(char),T), T).
:- mode check_io_result(in, pred(out) is det, pred(in, out) is det, out) is det.

:- pred display_error_handler(T).
:- mode display_error_handler(out) is det.

:- pred display_error is erroneous.

:- pred convert_to_float(list(char), float).
:- mode convert_to_float(in, out) is det.

:- pred convert_to_int(list(char), int).
:- mode convert_to_int(in, out) is det.

:- pred convert_to_string(list(char), string).
:- mode convert_to_string(in, out) is det.

:- pred do_nothing_handler(list(char), int).
:- mode do_nothing_handler(in, out) is det.

:- pred read_off_line(string, transform, io__state, io__state).
:- mode read_off_line(out, out, di, uo) is det.

:- pred read_off_file(string, polyhedron, io__state, io__state).
:- mode read_off_file(in, polyhedron_uo, di, uo) is det.

:- pred read_verticies(io__input_stream, int, int, array(vertex), array(vertex), io__state, io__state).
:- mode read_verticies(in, in, in, array_di, array_uo, di, uo) is det.

:- pred read_faces(io__input_stream, int, int, list(list(int)), list(list(int)), io__state, io__state).
:- mode read_faces(in, in, in, in, out, di, uo) is det.

:- pred read_one_face(io__input_stream, int, int, list(int), list(int),io__state, io__state).
:- mode read_one_face(in, in, in, in, out, di, uo) is det.

%-----------------------------------------------------------------------------%

% Simplistic checking of the command line arguments. Succeeds if there were
% three parameters on the command line, and they were valid representations of
% a float and two ints respectively.
sanity_check_args(Args, Focal, Width, Height) :-
	Args = [S_Focal, S_Width, S_Height],
	string__to_float(S_Focal, Focal),
	string__to_int(S_Width, Width),
	string__to_int(S_Height, Height).

% Displays the usage information for the program. Called if the program was
% invoked with incorrect arguments.
display_usage -->
	io__progname("parta", Name),
	io__print("Usage: "),
	io__print(Name),
	io__print(" focal-length width height"),
	io__nl.

% This is the predicate to read the scene description file from stdin.
% Currently, only lines describing OFF files are valid
read_scene_desc(Scene_in, Scene_out) -->
	io__read_word(Result),
	(
	    { Result = error(Error) },
	    { io__error_message(Error, Msg) },
	    { error(Msg) }
	;
	    { Result = eof },
	    { Scene_out = Scene_in }
	;
	    { Result = ok(Word) },
	    (
		% If the first word is "off", then this is an `off-line'
		{ Word = ['o','f','f'] }
	    ->	
		read_off_line(Name, Trans),
		read_off_file(Name, Poly0),
		{ Trans = transform(_S, _R, T) },
		{ poly__translate(T, Poly0, Poly) },
		{ array__size(Scene_in, Size) },
		{ array__resize(Scene_in, Size + 1, Poly, Scene0) }
	    ;
		{ error("Invalid line in scene description") }
	    ),
	    % continue on, read the next line
	    read_scene_desc(Scene0, Scene_out)
	).

% Read in one "off" line. Reads in the filename and the transformations to apply
% to the described polyhedron.
read_off_line(Name, Trans) -->
	% Read the file name
	io__read_word(R_Name),
	{ check_io_result(R_Name, display_error_handler, convert_to_string, Name) },

	% Read the six transformations
	io__read_word(R_Sx),
	{ check_io_result(R_Sx, display_error_handler, convert_to_float, Sx) },

	io__read_word(R_Sy),
	{ check_io_result(R_Sy, display_error_handler, convert_to_float, Sy) },
	
	io__read_word(R_Sz),
	{ check_io_result(R_Sz, display_error_handler, convert_to_float, Sz) },
	
	io__read_word(R_Rx),
	{ check_io_result(R_Rx, display_error_handler, convert_to_float, Rx) },
	
	io__read_word(R_Ry),
	{ check_io_result(R_Ry, display_error_handler, convert_to_float, Ry) },
	
	io__read_word(R_Rz),
	{ check_io_result(R_Rz, display_error_handler, convert_to_float, Rz) },
	
	io__read_word(R_Tx),
	{ check_io_result(R_Tx, display_error_handler, convert_to_float, Tx) },
	
	io__read_word(R_Ty),
	{ check_io_result(R_Ty, display_error_handler, convert_to_float, Ty) },
	
	io__read_word(R_Tz),
	{ check_io_result(R_Tz, display_error_handler, convert_to_float, Tz) },

	% Group them together into a transform type
	{ S = scale(Sx, Sy, Sz) },
	{ R = rotate(Rx, Ry, Rz) },
	{ T = translate(Tx, Ty, Tz) },
	{ Trans = transform(S, R, T) }.

% This higher order predicate takes an io__result and predicates to handle the
% eof and ok cases, and performs the correct action. This is to clean up all
% the io error checking throughout this module - it removes the need to have
% this code duplicated wherever a word is read in.
check_io_result(Res, EOF_Handler, OK_Handler, Output) :-
	(
	    Res = error(Error),
	    io__error_message(Error, Msg),
	    error(Msg)
	;
	    Res = eof,
	    EOF_Handler(Output)
	;
	    Res = ok(OK_Word),
	    OK_Handler(OK_Word, Output)
	).


% This predicate has an (unused) output so that it can be used as an EOF_Handler
% in check_io_result/4
display_error_handler(_) :-
	display_error.

% Display an error message due to invalid input, and terminate execution
display_error :-
	error("Invalid line in scene description").

% Convert a list of characters to a float
convert_to_float(Word, F) :-
	string__from_char_list(Word, S_F),
	(   
	    string__to_float(S_F, F0)
	->  
	    F = F0
	;
	    display_error
	).

% Convert a list of characters to a string
% This pred is needed since the library function string__from_char_list/2 has
% multiple modes, and a predicate can only be used as a higher order constant
% if it has exactly one mode.
convert_to_string(Word, S) :-
	string__from_char_list(Word, S).

% Convert a list of characters to an int
convert_to_int(Word, I) :-
	string__from_char_list(Word, S_I),
	(
	    string__to_int(S_I, I0)
	->
	    I = I0
	;
	    display_error
	).

% This is the handler for check_io_result/4 that does nothing.
do_nothing_handler(_, NothingOut) :-
	NothingOut = 0.

% Read in an OFF file, saving the described object in Poly.
% First calls the perl script "stripcom.pl" to remove any comments from the
% file, then parses as normal.
% Note, the optional colour information is ignored if present
read_off_file(Name, Poly) -->
	{ string__append("stripcom.pl < ", Name, Command0) },
	% I think it is fairly safe to assume that there will not be a file
	% called "tempout.tempout" in the current directory
	{ string__append(Command0, " > tempout.tempout", Command) },
	io__call_system(Command, _),
	io__open_input("tempout.tempout", SeeRes),
	(
	    { SeeRes = error(Error) },
	    { io__error_message(Error, Message) },
	    { error(Message) }
	;
	    { SeeRes = ok(File) },
	    
	    % Read in the "OFF" magic header from the file and ignore it
	    io__read_word(File, OFFRes),
	    { check_io_result(OFFRes, display_error_handler, do_nothing_handler, _) },
	    % Read the number of verticies
	    io__read_word(File, NVRes),
	    { check_io_result(NVRes, display_error_handler, convert_to_int, NV) },
	    % Read the number of faces
	    io__read_word(File, NFRes),
	    { check_io_result(NFRes, display_error_handler, convert_to_int, NF) },
	    % Read the number of edges, and ignore it
	    io__read_word(File, NERes),
	    { check_io_result(NERes, display_error_handler, do_nothing_handler, _) },
	    { array__init(NV, vertex(0.0, 0.0, 0.0), Verts_init) },
	    read_verticies(File, NV, 0, Verts_init, Verts),
	    read_faces(File, NF, 0, [[]], Faces),
	    { Poly = polyhedron(Verts, Faces) },

	    % Remove the temporary file created
	    io__call_system("rm -f tempout.tempout", _)
	).

% Read in the verticies from the OFF file. Stores them in an array in the order
% they are read in.
read_verticies(File, NV, CurrV, Verts_in, Verts_out) -->
	(
	    { CurrV < NV }
	->
	    io__read_word(File, XRes),
	    io__read_word(File, YRes),
	    io__read_word(File, ZRes),
	    { check_io_result(XRes, display_error_handler, convert_to_float, X) },
	    { check_io_result(YRes, display_error_handler, convert_to_float, Y) },
	    { check_io_result(ZRes, display_error_handler, convert_to_float, Z) },
	    { array__set(Verts_in, CurrV, vertex(X, Y, Z), Verts0) },
	    read_verticies(File, NV, CurrV + 1, Verts0, Verts_out)
	;
	    { Verts_out = Verts_in }
	).

% Read in the faces from the OFF file. They are stored in a list.
% Any colour information in this section of the file is ignored.
read_faces(File, NF, CurrF, Faces_in, Faces_out) -->
	(
	    { CurrF < NF }
	->
	    io__read_word(File, NumVRes),
	    { check_io_result(NumVRes, display_error_handler, convert_to_int, NumV) },
	    % Read in one face from the file
	    read_one_face(File, NumV, 0, [], Face),
	    
	    % Read the rest of the line and ignore it.
	    io__read_line(File, _),
	    
	    { Faces0 = [Face | Faces_in] },
	    read_faces(File, NF, CurrF + 1, Faces0, Faces_out)
	;
	    { Faces_out = Faces_in }
	).

% Read in one face from the file. The faces are read number by number, and
% stored in a list.
read_one_face(File, NumV, CurrV, Face_in, Face_out) -->
	(
	    { CurrV < NumV }
	->
	    io__read_word(File, VRes),
	    { check_io_result(VRes, display_error_handler, convert_to_int, V) },
	    { list__append(Face_in, [V], Face0) },
	    read_one_face(File, NumV, CurrV + 1, Face0, Face_out)
	;
	    { Face_out = Face_in }
	).
-------------- next part --------------
%-----------------------------------------------------------------------------%
%
% 433-380 Project, part A.
% Robert Jeschofnik (rejj), 55572
%
% parta.m
%
% Written in Mercury, because C sucks.
%
% Reads in a scene description, and all the objects described therein.
% The objects are then rendered to an image buffer, which is then output
% to stdout in PPM format.
%
% The method of choice for rendering polygons in this program is by forming
% horizontal scanlines for each face, then drawing each of these in turn.
%
%-----------------------------------------------------------------------------%

:- module parta.

:- interface.

:- import_module io.

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

%-----------------------------------------------------------------------------%

:- implementation.

:- import_module char, int, float, string, list, array, require.
:- import_module poly, handle_input.

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

%-----------------------------------------------------------------------------%

main -->
	io__command_line_arguments(Args),
	(
	    {sanity_check_args(Args, Focal, Width, Height)}
	->  
	    perform_rendering(Focal, Width, Height)
	;
	    display_usage
	).

% Read in the scene description, and then draw the scene.
perform_rendering(Focal, Width, Height) -->
	{ array__make_empty_array(Scene0) },
	read_scene_desc(Scene0, Scene),
	{ poly__image_init(Width, Height, Image0) },
	poly__draw_scene(Focal, Width, Height, Scene, Image0, _Image).








-------------- next part --------------
%-----------------------------------------------------------------------------$
%
% 433-380 Project, part A
% Robert Jeschofnik (rejj), 55572
%
% poly.m
%
% Written in Mercury, because C sucks.
%
% This module contains all the predicates dealing with drawing the polys.
% (basically, everything except for input, which is in handle_input.m)
%
% Polys are projected into 2D, then clipped to the image plane. Then the
% scanlines for each face are generated, and drawn into the image buffer.
% Finally, the image is flushed to stdout.
%
%-----------------------------------------------------------------------------%

:- module poly.

:- interface.

:- import_module float, int, list, array, io.

% The instantiation for a unique polyhedron
:- inst uniq_polyhedron == unique(polyhedron(uniq_array, ground)).

:- mode polyhedron_di == di(uniq_polyhedron).
:- mode polyhedron_uo == out(uniq_polyhedron).
:- mode polyhedron_ui == in(uniq_polyhedron).

% The instantiation for a world of unique polyhedrons (The entire scene)
:- inst world_uniq_polys == uniq_array(uniq_polyhedron).

:- mode world_di == di(world_uniq_polys).
:- mode world_uo == out(world_uniq_polys).
:- mode world_ui == in(world_uniq_polys).

% The type for a vertex in 3D space. Holds it's X, Y, Z coordinates.
% NOTE: Make this an ADT, in it's own module.
% or just put all the polyhedron stuff in it's own module.. vertex, face, etc
%
% vertex(X, Y, Z)
:- type vertex --->
	vertex(float, float, float).

% A polehedron is made up of a group of verticies, organised into faces. The
% verticies are stored in an array.
% :- type vertex_array == array(vertex).

% A face of the polyhedron is a list of the verticies, given as indicies into
% the vertex_array.
:- type face == list(int).

% The type for the polyhedron itself. Groups together the verticies and the
% faces.
% polyhedron(Verts, Faces)
:- type polyhedron --->
	polyhedron(array(vertex), list(face)).

% The type that encapsulates the entire world. For part a, this is just a list
% of all the polyhedrons in it. This will be expanded to include light sources
% and the ambient light level in part b.
:- type world == array(polyhedron).


% Types handy for passing around the scale, rotate, and translate transforms
% for each object as listed in the scene description format.


% scale(Sx, Sy, Sz)
:- type scale --->
	scale(float, float, float).

% rotate(Rx, Ry, Rz)
:- type rotate --->
	rotate(float, float, float).

% translate(Tx, Ty, Tz)
:- type translate --->
	translate(float, float, float).

% Type to bundle all the transforms together. Encapsulates all the 3D
% transforms to be applied to any given object.
% transform(Scale factor, Rotation, Translation)
:- type transform --->
	transform(scale, rotate, translate).

% Type to represent the image that is being drawn. It is a two dimensional
% array of integers, representing the X and Y locations for every pixel
% (and their value)
%:- type image == array(array(colour)).
:- type image == array(colour).

% colour(Red, Green, Blue)
:- type colour --->
	colour(int, int, int).

%-----------------------------------------------------------------------------%

:- pred poly__translate(translate, polyhedron, polyhedron).
:- mode poly__translate(in, polyhedron_di, polyhedron_uo) is det.

:- pred poly__project(float, int, int, polyhedron, polyhedron).
:- mode poly__project(in, in, in, polyhedron_di, polyhedron_uo) is det.

:- pred poly__draw(int, int, polyhedron, image, image).
:- mode poly__draw(in, in, polyhedron_ui, array_di, array_uo) is det.

:- pred poly__image_init(int, int, image).
:- mode poly__image_init(in, in, array_uo) is det.

:- pred poly__image_draw(int, int, image, io__state, io__state).
:- mode poly__image_draw(in, in, array_ui, di, uo) is det.

:- pred poly__draw_scene(float, int, int, world, image, image, io__state, io__state).
:- mode poly__draw_scene(in, in, in, array_ui, array_di, array_uo, di, uo) is det.

%-----------------------------------------------------------------------------%

:- implementation.

:- import_module require, string.


:- pred do_trans(float, float, float, int, int, array(vertex), array(vertex)).
:- mode do_trans(in, in, in, in, in, array_di, array_uo) is det.

:- pred do_proj(int, int, int, int, float, int, int, array(vertex), array(vertex)).
:- mode do_proj(in, in, in, in, in, in, in, array_di, array_uo) is det.

:- pred clip(int, int, float, float, float, float).
:- mode clip(in, in, in, in, out, out) is det.

:- pred make_scanlines(array(vertex), int, int, array(list(int)), array(list(int))).
:- mode make_scanlines(array_ui, in, in, array_di, array_uo) is det.

:- pred trace_edge(int, int, int, int, int, array(list(int)), array(list(int))).
:- mode trace_edge(in, in, in, in, in, array_di, array_uo) is det.

:- pred draw_hline(int, int, int, int, image, image).
:- mode draw_hline(in, in, in, in, array_di, array_uo) is det.

:- pred make_face(array(vertex), list(int), int, array(vertex), array(vertex)).
:- mode make_face(array_ui, in, in, array_di, array_uo) is det.

:- pred draw_scanlines(int, int, array(list(int)), int, image, image).
:- mode draw_scanlines(in, in, array_ui, in, array_di, array_uo) is det.

:- pred draw_one_scanline(list(int), int, int, image, image).
:- mode draw_one_scanline(in, in, in, array_di, array_uo) is det.

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

:- pred do_draw_scene(float, int, int, int, int, world, image, image, io__state, io__state).
:- mode do_draw_scene(in, in, in, in, in, array_ui, array_di, array_uo, di, uo) is det.

% Perform a translation on a polyhedron, giving back the new polyhedron.
% Utilises destructive update to minimise memory usage.
poly__translate(translate(Tx, Ty, Tz), polyhedron(Vs_in, Fs), polyhedron(Vs_out, Fs)) :-
	array__size(Vs_in, NV),
	do_trans(Tx, Ty, Tz, NV, 0, Vs_in, Vs_out).


% Recursively translate each vertex in the given array of verticies.
do_trans(Tx, Ty, Tz, NV, Elem, Vs_in, Vs_out) :-
	(
	    Elem < NV
	->
	    array__lookup(Vs_in, Elem, vertex(X0, Y0, Z0)),
	    X = X0 + Tx,
	    Y = Y0 + Ty,
	    Z = Z0 + Tz,
	    array__set(Vs_in, Elem, vertex(X, Y, Z), Vs_in0),
	    do_trans(Tx, Ty, Tz, NV, Elem + 1, Vs_in0, Vs_out)
	;
	    Vs_out = Vs_in
	).

% Project a polygon from 3D to 2D.
poly__project(Focal, Width, Height, polyhedron(Vs_3D, Fs), polyhedron(Vs_2D, Fs)) :-
	Xoff = Width div 2,
	Yoff = Height div 2,
	Vs0 = Vs_3D,
	array__size(Vs0, NV),
	do_proj(Xoff, Yoff, Width, Height, Focal, NV, 0, Vs0, Vs_2D).

% Recursively project each vertex in the given array of vertices from 3D to
% 2D
do_proj(Xoff, Yoff, Width, Height, Focal, NV, Elem, Vs_3D, Vs_2D) :-
	(
	    Elem < NV
	->
	    array__lookup(Vs_3D, Elem, vertex(X0, Y0, Z)),
	    X_proj0 = (X0 * Focal) / Z,
	    X_proj = X_proj0 * -1.0,
	    X1 = float(Xoff) + X_proj,
	    Y1 = float(Yoff) + ((Y0 * Focal) / Z),

	    clip(Width, Height, X1, Y1, X, Y),
	    
	    % The projected coordinates lie in the Z = 1 plane, but the
	    % original depth is still needed for other calculations, (in part
	    % b) so it is maintained. Drawing will only look at the X and Y
	    % elements.
	    array__set(Vs_3D, Elem, vertex(X, Y, Z), Vs0),
	    do_proj(Xoff, Yoff, Width, Height, Focal, NV, Elem + 1, Vs0, Vs_2D)
	;
	    Vs_2D = Vs_3D
	).

% Clip X0 and Y0 to the image plane.
clip(Width, Height, X0, Y0, X, Y) :-
	W = float(Width),
	H = float(Height),
	(   
	    X0 < 0.0
	->
	    X = 0.0
	;
	    (
		X0 > W
	    ->
		X = W
	    ;
		X = X0
	    )
	),

	(
	    Y0 < 0.0
	->
	    Y = 0.0
	;
	    (
		Y0 > H
	    ->
		Y = H
	    ;
		Y = Y0
	    )
	).

% Draws the projected polyhedron into the image
poly__draw(Width, Height, polyhedron(Vs, Fs), Image_in, Image_out) :-
	(
	    Fs = [],
	    Image_out = Image_in
	;
	    Fs = [Face | Faces],
	    list__length(Face, Length),
	    array__init(Height, [0, 0], ScanLines_init),
	    array__init(Length, vertex(0.0, 0.0, 0.0), Poly_init),

	    % Generate the face
	    make_face(Vs, Face, 0, Poly_init, Poly),

	    % Generate the scanlines for this face
	    make_scanlines(Poly, Length, 0, ScanLines_init, ScanLines),

	    % Render the face into the image buffer
	    draw_scanlines(Width, Height, ScanLines, 0, Image_in, Image0),

	    % Recursively draw the rest of the faces in this polyhedron
	    poly__draw(Width, Height, polyhedron(Vs, Faces), Image0, Image_out)
	).

% Generate the face given by the list of verticies (Face)
make_face(ObjVs, Face, Elem, PolyVs_in, PolyVs_out) :-
	(
	    Face = [],
	    PolyVs_in = PolyVs_out
	;
	    Face = [Vert | Verts],
	    array__lookup(ObjVs, Vert, V),
	    array__set(PolyVs_in, Elem, V, PolyVs0),
	    make_face(ObjVs, Verts, Elem + 1, PolyVs0, PolyVs_out)
	).
	    

% Generate the horizontal lines that make up one face.
% If part of the polygon lies behind or at Z = 0, the scanlines at that
% position are not generated.
make_scanlines(Poly, Size, Elem, ScanLines0, ScanLines) :-
	(
	    Elem < (Size -1)
	->
	    array__lookup(Poly, Elem, vertex(X1, Y1, Z1)),
	    array__lookup(Poly, Elem + 1, vertex(X2, Y2, Z2)),
	    (
		Z1 >= 0.0
	    ->
		ScanLines = ScanLines0
	    ;
		(
		    Z2 >= 0.0
		->
		    ScanLines = ScanLines0
		;
		    round_to_int(X1) = X1i,
		    round_to_int(Y1) = Y1i,
		    round_to_int(X2) = X2i,
		    round_to_int(Y2) = Y2i,
		    (	
			Y1i < Y2i
		    ->	
			trace_edge(X1i, Y1i, X2i, Y2i, Y1i, ScanLines0, ScanLines1)
		    ;	
			trace_edge(X2i, Y2i, X1i, Y1i, Y2i, ScanLines0, ScanLines1)
		    ),
		    make_scanlines(Poly, Size, Elem + 1, ScanLines1, ScanLines) 
		)
	    )
	;
	    (	
		Elem = (Size - 1)
	    ->	
		% The final egde is between the last and the first verticies
		array__lookup(Poly, Elem, vertex(X1, Y1, Z1)),
		array__lookup(Poly, 0, vertex(X2, Y2, Z2)),
		(   
		    Z1 >= 0.0
		->  
		    ScanLines = ScanLines0
		;   
		    (	
			Z2 >= 0.0
		    ->	
			ScanLines = ScanLines0
		    ;	
			round_to_int(X1) = X1i,
			round_to_int(Y1) = Y1i,
			round_to_int(X2) = X2i,
			round_to_int(Y2) = Y2i,
			(   
			    Y1i < Y2i
			->  
			    trace_edge(X1i, Y1i, X2i, Y2i, Y1i, ScanLines0, ScanLines)
			;   
			    trace_edge(X2i, Y2i, X1i, Y1i, Y2i, ScanLines0, ScanLines)
			)
		    )
		)
	    ;	
		% There are no more edges to trace
		ScanLines = ScanLines0
	    )
	).
		
% Trace along the line from (X1, Y1) to (X2, Y2) finding the X intersections
% for each integer value of Y along the line. These are used as the endpoints
% for the scanlines
trace_edge(X1, Y1, X2, Y2, CurrY, ScanLines0, ScanLines) :-
	(   
	    % Check if the edge is horizontal. If it is, don't bother tracing
	    % along it.
	    Y2 = Y1
	->
	    ScanLines = ScanLines0
	;
	    (
		CurrY < Y2
	    ->
		% Find the X for the current Y
		X = ((CurrY - Y1) * (X2 - X1) div (Y2 - Y1)) + X1,
		
		array__lookup(ScanLines0, CurrY, Line),
		array__set(ScanLines0, CurrY, [X | Line], ScanLines1),
		trace_edge(X1, Y1, X2, Y2, CurrY + 1, ScanLines1, ScanLines)
	    ;
		ScanLines = ScanLines0
	    )
	).

% Render the scanlines into the image buffer.
draw_scanlines(Width, Height, ScanLines, Y, Image_in, Image_out) :-
	(   
	    Y < Height
	->
	    array__lookup(ScanLines, Y, ScanLine0),
	    list__sort(ScanLine0, ScanLine),
	    draw_one_scanline(ScanLine, Y, Width, Image_in, Image0),
	    draw_scanlines(Width, Height, ScanLines, Y + 1, Image0, Image_out)
	;
	    Image_out = Image_in
	).

% Draw a single scanline into the image. If there are (at least) two
% coordinates stored in the list, a horizontal line is drawn between these
% two points.
draw_one_scanline(ScanLine, Y, Width, Image_in, Image_out) :-
	(   
	    ScanLine = [],
	    Image_out = Image_in
	;
	    ScanLine = [X1 | Xs0],
	    (
		Xs0 = [],
		Image_out = Image_in
	    ;
		Xs0 = [X2 | Xs],
		draw_hline(X1, X2, Y, Width, Image_in, Image0),
		draw_one_scanline(Xs, Y, Width, Image0, Image_out)
	    )
	).

% Draw a horizontal line between X1 and X2, at height Y
draw_hline(X1, X2, Y, Width, Image_in, Image_out) :-
	(   
	    X1 < X2
	->
	    array__set(Image_in, (Y * Width) + X1, colour(255, 255, 255), Image0),
	    draw_hline(X1 + 1, X2, Y, Width, Image0, Image_out)
	;
	    Image_in = Image_out
	).

% Create the empty image buffer
poly__image_init(Width, Height, Image) :-
	array__init(Width * Height, colour(0, 0, 0), Image).

% Print out the header information for the PPM format, then output the image
% buffer.
poly__image_draw(Width, Height, Image) -->
	io__print("P6"),
	io__print(" "),
	io__write(Width),
	io__print(" "),
	io__write(Height),
	io__print(" "),
	io__write(255),
	io__nl,
	do_image_draw(Width, Height, 0, 0, Image).

% Output the image buffer in binary format. There are three bytes for every
% pixel (Red, Green, Blue). These bytes are just streamed to stdout.
do_image_draw(Width, Height, X, Y, Image) -->
	(   
	    { Y < Height }
	->
	    (
		{ X < Width }
	    ->
		{ array__lookup(Image, (Y * Width) + X, colour(R, G, B)) },
		io__write_byte(R),
		io__write_byte(G),
		io__write_byte(B),
		do_image_draw(Width, Height, X + 1, Y, Image)
	    ;
		do_image_draw(Width, Height, 0, Y + 1, Image)
	    )
	;
	    % The empty list is used to represent an empty clause in a DCG
	    []
	).

% Draw the whole scene.
poly__draw_scene(Focal, Width, Height, Scene, Image_in, Image_out) -->
	{ array__size(Scene, NumPolys) },
	do_draw_scene(Focal, Width, Height, NumPolys, 0, Scene, Image_in, Image_out),
	poly__image_draw(Width, Height, Image_out).


% Recursively draw each polyhedron into the image buffer.
do_draw_scene(Focal, Width, Height, NumPolys, CurrPoly, Scene, Image_in, Image_out) -->
	(
	    { CurrPoly < NumPolys }
	->
	    { array__lookup(Scene, CurrPoly, Poly3D) },
	    { poly__project(Focal, Width, Height, u_p(Poly3D), Poly2D) },
	    { poly__draw(Width, Height, Poly2D, Image_in, Image0) },
	    do_draw_scene(Focal, Width, Height, NumPolys, CurrPoly + 1, Scene, Image0, Image_out)
	;
	    { Image_out = Image_in }
	).


% This is a nasty hack to ensure uniqueness of an array. This is required
% because nested unique modes are currently not supported by the Mercury
% compiler.
% Thanks to Tom Conway for this.
:- func u(array(T)) = array(T).
:- mode (u(in) = array_uo) is det.

:- pragma c_code(u(A::in) = (B::array_uo),
		 [will_not_call_mercury, thread_safe],
		 "B = A;"
		 ).

% Same as above, but for polyhedrons.
:- func u_p(polyhedron) = polyhedron.
:- mode (u_p(in) = polyhedron_uo) is det.

:- pragma c_code(u_p(A::in) = (B::polyhedron_uo),
		 [will_not_call_mercury, thread_safe],
		 "B = A;"
		 ).


More information about the users mailing list