[m-rev.] diff: parse excel formulas

Peter Ross pro at missioncriticalit.com
Tue Feb 24 22:18:33 AEDT 2004


Hi,


===================================================================

Add the ability to parse formulas.

Mmakefile:
	Add .PHONY targets where needed.

excel_engine/Mmakefile:
	Include the lex library in the path.
	Add rule to transform the added moose file into a mercury file.

excel_engine/excel_engine.m:
	Add formulas to the cell representation.
	Add the type vexpr (copied from ex_representation.m by rpa)
	which represents a formula in mercury.


excel_engine/excel_engine.parse.formula.m:
	Interface to the formula parser.

excel_engine/excel_engine.parse.formula.lex.m:
	Lex a formula into its lexical tokens.

excel_engine/excel_engine.parse.formula.parse.moo:
	The actual parser for parsing the lexical tokens into vexpr.
	
excel_engine/excel_engine.parse.m:
	Call the formula parser.

excel_engine/excel_engine.parse.xml.m:
	Get the formula from the XML representation.

excel_engine/tests/Mmakefile:
excel_engine/tests/formula/Mmakefile:
excel_engine/tests/formula/references.exp:
excel_engine/tests/formula/references.xls:
excel_engine/tests/formula/references.xml:
	Add a test to test the parsing of cell references.

lex/Mmakefile:
	Include ../Mmake.params.

Index: Mmakefile
===================================================================
RCS file: d:/project/cvsroot/mas-coverone-src/Mmakefile,v
retrieving revision 1.2
diff -u -r1.2 Mmakefile
--- Mmakefile	9 Feb 2004 12:26:20 -0000	1.2
+++ Mmakefile	24 Feb 2004 10:58:38 -0000
@@ -2,28 +2,38 @@
 
 MAIN_TARGET=all
 
-depend:
+.PHONY: depend all clean realclean
+depend: coverone.depend
+all: coverone
+clean: coverone.clean
+realclean: coverone.realclean
+
+.PHONY: coverone.depend
+coverone.depend:
 	+cd concurrency && mmake depend
 	+cd stream && mmake depend
 	+cd net && mmake depend
 	+cd racer && mmake depend
 	+cd coverone && mmake depend
 
-all:
+.PHONY: coverone
+coverone:
 	+cd concurrency && mmake
 	+cd stream && mmake
 	+cd net && mmake
 	+cd racer && mmake
 	+cd coverone && mmake
 
-clean:
+.PHONY: coverone.clean
+coverone.clean:
 	+cd concurrency && mmake clean
 	+cd stream && mmake clean
 	+cd net && mmake clean
 	+cd racer && mmake clean
 	+cd coverone && mmake clean
 
-realclean:
+.PHONY: coverone.realclean
+coverone.realclean:
 	+cd concurrency && mmake realclean
 	+cd stream && mmake realclean
 	+cd net && mmake realclean
Index: excel_engine/Mmakefile
===================================================================
RCS file: d:/project/cvsroot/excel_engine/Mmakefile,v
retrieving revision 1.2
diff -u -r1.2 Mmakefile
--- excel_engine/Mmakefile	20 Feb 2004 10:17:11 -0000	1.2
+++ excel_engine/Mmakefile	24 Feb 2004 10:58:38 -0000
@@ -2,10 +2,16 @@
 
 MAIN_TARGET=libexcel_engine
 
-INCLUDES=-I ../xml
-VPATH=../xml:$(MMAKE_VPATH)
-MLLIBS+=-L../xml -lxml
+INCLUDES=-I ../lex -I ../xml
+VPATH=../lex:../xml:$(MMAKE_VPATH)
+MLLIBS+=-L ../lex -L../xml -lregex -llex -lxml
 MCFLAGS+=$(INCLUDES)
 CFLAGS+=$(INCLUDES)
 
-depend: excel_engine.depend
+depend: excel_engine.parse.formula.parse.m excel_engine.depend
+
+excel_engine.parse.formula.parse.m: excel_engine.parse.formula.parse.moo
+	moose excel_engine.parse.formula.parse.moo
+
+realclean:
+	-rm -f excel_engine.parse.formula.parse.m
Index: excel_engine/excel_engine.m
===================================================================
RCS file: d:/project/cvsroot/excel_engine/excel_engine.m,v
retrieving revision 1.2
diff -u -r1.2 excel_engine.m
--- excel_engine/excel_engine.m	20 Feb 2004 13:29:38 -0000	1.2
+++ excel_engine/excel_engine.m	24 Feb 2004 10:58:38 -0000
@@ -27,10 +27,15 @@
 	% A reference to a cell in the current worksheet.
 :- type local_cell_ref.
 
+:- import_module std_util.
 :- type cell
 	--->	cell(
-			value	:: cell_value
-		).
+			value	:: cell_value,
+			formula	:: maybe(vexpr)
+		)
+	.
+
+:- type vexpr.
 	
 :- type cell_value
 	--->	number(float)
@@ -95,6 +100,124 @@
 lookup_cell_value(SS, {WorkSheetName, CellRef}) = Cell ^ value :-
 	WorkSheet = map__lookup(SS ^ worksheet_map, WorkSheetName),
 	Cell = map__lookup(WorkSheet ^ data, CellRef).
+
+%------------------------------------------------------------------------------%
+%------------------------------------------------------------------------------%
+
+% 
+% The superset of all possible value after evaluating a cell.  No
+% function/predicate will ever use this superset. Only an instance
+% vexpr_value or cell_value may be used. This superset is defined to
+% decrease memory usage, because it allows copying vexpr_info
+% variables without constructing/deconstructing "value(Variant)"
+% terms.
+% 
+:- type vexpr_info
+	--->	reference(reference)
+	;	vexpr(vexpr)
+	;	value(cell_value)
+	.
+
+%
+% The representation of a vexpr
+%
+:- type vexpr 
+%  ---> const(cell_variant)
+  % Will always be an inst of "value(Variant)". We store it as a
+  % vexpr_value to avoid a memory allocation when evaluating a
+  % constant into a vexpr_value
+  ---> const(vexpr_info) 
+  % Will always be an inst of "reference(Ref)". We store it as a
+  % vexpr_value to avoid a memory allocation when evaluating a
+  % constant into a vexpr_value
+ ; reference(vexpr_info)
+ ; primitive(primitive).
+
+% :- type vexpr_bool == vexpr.
+% :- type vexpr_string == vexpr.
+% :- type vexpr_int == vexpr.
+% :- type vexpr_date == vexpr.
+
+% 
+% 
+% 
+:- type vexpr_list == list(vexpr).
+  
+
+% 
+% All possible reference types
+% 
+:- type reference
+	--->	simple(cell_reference)			% e.g. "A1"
+	;	range(cell_reference, cell_reference)	% e.g. "A1:B5"
+	%;	col_range(string, string)		% e.g. "A:B"  (NYI)	
+	%;	row_range(int, int)			% e.g. "5:6"  (NYI)	
+	.
+
+:- type cell_reference
+	--->	worksheet(string, reference_type)
+	;	local(reference_type)
+	.
+
+:- type reference_type
+	--->	fixed(string)
+	;	relative(int, int).
+
+
+% 
+% A primitive definition: any expression that is not a constant or a
+% reference.
+% 
+:- type primitive
+	 --->	arithm(arithm_op, vexpr, vexpr)	% a "arithm_op" b
+	 ;	neg(vexpr)			% -a
+	 ;	percent(vexpr)			% a% (i.e. a / 100)
+	 ;	connects(vexpr, vexpr)		% a & b
+	 ;	function(func_op, vexpr_list)	% func_op(a,b,...)	
+	 ;	compare(comp_op, vexpr, vexpr)	% a comp_op b
+	 .
+
+% 
+% Arithmetic operators
+% 
+:- type arithm_op
+  ---> plus; minus; times; divide; exponent.
+
+% 
+% Comparaison operators
+% 
+:- type comp_op
+  ---> lt ; gt ; eq ; neq ; lte ; gte.
+
+% 
+% Function primitives
+% 
+:- type func_op
+  ---> func_min
+ ; func_max
+ ; func_round
+ ; func_roundup
+ ; func_int
+ ; func_sum
+ ; func_if
+ ; func_year
+ ; func_month
+ ; func_weekday
+ ; func_date
+ ; func_today
+ ; func_now
+ ; func_not
+ ; func_and
+ ; func_or
+ ; func_isblank
+ ; func_iserror
+ ; func_right
+ ; func_left
+ ; func_search
+ ; func_text
+ ; func_concatenate
+ ; func_len.
+
 
 %------------------------------------------------------------------------------%
 %------------------------------------------------------------------------------%
Index: excel_engine/excel_engine.parse.formula.lex.m
===================================================================
RCS file: excel_engine/excel_engine.parse.formula.lex.m
diff -N excel_engine/excel_engine.parse.formula.lex.m
--- nul	1 Jan 1970 00:00:00 -0000
+++ excel_engine/excel_engine.parse.formula.lex.m	24 Feb 2004 10:58:38 -0000
@@ -0,0 +1,115 @@
+%----------------------------------------------------------------------------- %
+% Module: excel_engine__parse__formula__lex
+% Author: Peter Ross <pro at missioncriticalit.com>
+%
+% Turn a string representing an excel formula into a list of token which
+% are used by the parser.
+%
+%----------------------------------------------------------------------------- %
+
+:- module excel_engine__parse__formula__lex.
+
+:- interface.
+
+:- pred tokenize(string::in, list(token)::out) is det.
+
+%----------------------------------------------------------------------------- %
+%----------------------------------------------------------------------------- %
+
+:- implementation.
+
+:- import_module std_util, string, int, float, exception, io, list, require.
+:- import_module lex.
+:- import_module excel_engine__parse__formula__parse.
+
+%----------------------------------------------------------------------------- %
+
+tokenize(String, Tokens) :-
+	some [!State] (
+		copy(String, UniqString),
+		Lexer  = lex__init(lexemes, read_from_string, ignore(space)),
+		!:State = lex__start(Lexer, UniqString),
+
+		tokenize(Tokens, !State),
+
+		_ = lex__stop(!.State)
+	).
+
+:- pred tokenize(list(token)::out, lexer_state(token, string)::di,
+		lexer_state(token, string)::uo) is det.
+
+tokenize(Tokens, !State) :-
+	lex__read(Result, !State),
+	( Result = ok(Token),
+		tokenize(RemainingTokens, !State),
+		Tokens = [Token | RemainingTokens]
+	; Result = error(ErrString, _ErrLineNumber),
+		error(ErrString)
+	; Result = eof,
+		Tokens = [eof]
+	).
+
+%----------------------------------------------------------------------------- %
+
+:- func lexemes = list(lexeme(token)).
+
+lexemes = [
+	( "TRUE"	-> return((true)) ),
+	( "FALSE"	-> return((false)) ),
+
+	( string	-> (func(Match) = string(Match)) ),
+
+	( "R"		-> return(row) ),
+	( "C"		-> return(column) ),
+	( "RC"		-> return(rowcolumn) ),
+
+	( identifier	-> (func(Match) = identifier(Match)) ),
+	( real		-> (func(Match) = real(det_string_to_float(Match))) ),
+	( nat		-> (func(Match) = integer(det_to_int(Match))) ),
+
+	( ";"		-> return(';') ),
+	( ":"		-> return(':') ),
+	( "="		-> return('=') ),
+	( "!"		-> return('!') ),
+
+	( "<"		-> return('<') ),
+	( ">"		-> return('>') ),
+	( "<>"		-> return('<>') ),
+	( "<="		-> return('<=') ),
+	( ">="		-> return('>=') ),
+
+	( "&"		-> return('&') ),
+
+	( "-"		-> return('-') ),
+	( "+"		-> return('+') ),
+	( "*"		-> return('*') ),
+	( "/"		-> return('/') ),
+
+	( "^"		-> return('^') ),
+
+	( "%"		-> return('%') ),
+
+	( "("		-> return('(') ),
+	( ")"		-> return(')') ),
+	( "["		-> return('[') ),
+	( "]"		-> return(']') ),
+
+	( whitespace	-> return(space) )
+].
+
+:- func string = regexp.
+string = re("\"") ++ *(string_body) ++ re("\"").
+
+:- func string_body = regexp.
+string_body = *(anybut("\"")) ++ re("\"\"").
+
+:- func det_string_to_float(string) = float.
+
+det_string_to_float(String) =
+    ( if   string__to_float(String, Float)
+      then Float
+      else throw("error in float conversion")
+    ).
+
+%----------------------------------------------------------------------------- %
+%----------------------------------------------------------------------------- %
Index: excel_engine/excel_engine.parse.formula.m
===================================================================
RCS file: excel_engine/excel_engine.parse.formula.m
diff -N excel_engine/excel_engine.parse.formula.m
--- nul	1 Jan 1970 00:00:00 -0000
+++ excel_engine/excel_engine.parse.formula.m	24 Feb 2004 10:58:38 -0000
@@ -0,0 +1,45 @@
+%------------------------------------------------------------------------------%
+% Module: excel_engine.parse.formula.m
+% Author: Peter Ross <pro at missioncriticalit.com>
+%
+% Responsible for parsing the formulas.
+%------------------------------------------------------------------------------%
+
+:- module excel_engine__parse__formula.
+
+:- interface.
+
+:- include_module parse.
+:- include_module lex.
+
+:- pred parse(string::in, vexpr::out) is det.
+
+%------------------------------------------------------------------------------%
+%------------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module excel_engine__parse__formula__parse.
+:- import_module excel_engine__parse__formula__lex.
+
+:- type token_list == list(token).
+
+:- instance parser_state(token_list) where [
+	get_token(eof, [],       []),
+	get_token(T,   [T | Ts], Ts),
+
+	unget_token(T, Ts) = [T | Ts]
+].
+
+parse(String, Expr) :-
+	tokenize(String, Tokens),
+	parse(ParseResult, Tokens, RemainingTokens),
+	( RemainingTokens = [], ParseResult = exprn(Expr0) ->
+		Expr = Expr0
+	;
+		error("Unable to parse: " ++ String)
+	).
+
+
+%------------------------------------------------------------------------------%
+%------------------------------------------------------------------------------%
Index: excel_engine/excel_engine.parse.formula.parse.moo
===================================================================
RCS file: excel_engine/excel_engine.parse.formula.parse.moo
diff -N excel_engine/excel_engine.parse.formula.parse.moo
--- nul	1 Jan 1970 00:00:00 -0000
+++ excel_engine/excel_engine.parse.formula.parse.moo	24 Feb 2004 10:58:38 -0000
@@ -0,0 +1,242 @@
+%----------------------------------------------------------------------------- %
+% Module: excel_engine.parse.formula.parse.moo
+% Author: Peter Ross <pro at missioncriticalit.com>
+%
+% Parse an excel formula.
+%
+%----------------------------------------------------------------------------- %
+:- module excel_engine__parse__formula__parse.
+
+:- interface.
+
+:- type token
+	--->    identifier(string)
+
+	;	row
+	;	column
+	;	rowcolumn
+
+	;	string(string)
+	;       real(float)
+	;       integer(int)
+
+	;	(';')
+	;	(':')
+	;	('=')
+	;	('!')
+
+	;	('>')
+	;	('<')
+	;	('<>')
+	;	('>=')
+	;	('<=')
+
+	;	('&')
+
+	;	('-')
+	;	('+')
+	;	('*')
+	;	('/')
+
+	;	('^')
+
+	;	('%')
+
+	;	(true)
+	;	(false)
+
+	;	('(')
+	;	(')')
+	;	('[')
+	;	(']')
+
+	;	space
+	;	eof
+	.
+
+:- parse(exprn/1, token, eof, unused, in, out).
+
+%----------------------------------------------------------------------------- %
+%----------------------------------------------------------------------------- %
+
+:- implementation.
+
+:- import_module bool, float, int, list, string.
+
+:- rule exprn(vexpr).
+exprn(E)		--->	[('=')], vexpr(E).
+
+:- rule vexpr(vexpr).
+vexpr(E)		--->	vexpr_arithm(E).
+
+:- rule vexpr_arithm(vexpr).
+vexpr_arithm(E)		--->	vexpr_compare(E).
+
+:- rule vexpr_compare(vexpr).
+vexpr_compare(E) 	--->	vexpr_concat(E).
+vexpr_compare(E)	--->	vexpr_concat(E1),
+				vexpr_comparison_op(C),
+				vexpr_compare(E2),
+				{ E = primitive(compare(C, E1, E2)) }.
+
+:- rule vexpr_comparison_op(comp_op).
+vexpr_comparison_op(C)	--->	['<'], { C = lt }.
+vexpr_comparison_op(C)	--->	['>'], { C = gt }.
+vexpr_comparison_op(C)	--->	['='], { C = eq }.
+vexpr_comparison_op(C)	--->	['<>'], { C = neq }.
+vexpr_comparison_op(C)	--->	['<='], { C = lte }.
+vexpr_comparison_op(C)	--->	['>='], { C = gte }.
+
+:- rule vexpr_concat(vexpr).
+vexpr_concat(E)		--->	vexpr_addition(E).
+vexpr_concat(E)		--->	vexpr_addition(E1), ['&'], vexpr_concat(E2),
+				{ E = primitive(connects(E1, E2)) }.
+			
+:- rule vexpr_addition(vexpr).
+vexpr_addition(E)	--->	vexpr_product(E).
+vexpr_addition(E)	--->	vexpr_product(E1), ['+'], vexpr_addition(E2),
+				{ E = primitive(arithm(plus, E1, E2)) }.
+vexpr_addition(E)	--->	vexpr_product(E1), ['-'], vexpr_addition(E2),
+				{ E = primitive(arithm(minus, E1, E2)) }.
+
+:- rule vexpr_product(vexpr).
+vexpr_product(E)	--->	vexpr_exponent(E).
+vexpr_product(E)	--->	vexpr_exponent(E1), ['*'], vexpr_product(E2),
+				{ E = primitive(arithm(times, E1, E2)) }.
+vexpr_product(E)	--->	vexpr_exponent(E1), ['/'], vexpr_product(E2),
+				{ E = primitive(arithm(divide, E1, E2)) }.
+
+:- rule vexpr_exponent(vexpr).
+vexpr_exponent(E)	--->	vexpr_percent(E).
+vexpr_exponent(E)	--->	vexpr_percent(E1), ['^'], vexpr_exponent(E2),
+				{ E = primitive(arithm(exponent, E1, E2)) }.
+
+:- rule vexpr_percent(vexpr).
+vexpr_percent(E)	--->	vexpr_negation(E).
+vexpr_percent(E)	--->	vexpr_percent(E1), ['%'],
+				{ E = primitive(percent(E1)) }.
+
+:- rule vexpr_negation(vexpr).
+vexpr_negation(E)	--->	vexpr_atomic(E).
+vexpr_negation(E)	--->	['-'], vexpr_negation(E1),
+				{ E = primitive(neg(E1)) }.
+
+:- rule vexpr_atomic(vexpr).
+vexpr_atomic(E)		--->	vexpr_boolean(E).
+vexpr_atomic(E)		--->	vexpr_string(E).
+vexpr_atomic(E)		--->	vexpr_parent(E).
+vexpr_atomic(E)		--->	vexpr_func(E).
+vexpr_atomic(E)		--->	vexpr_reference(E).
+vexpr_atomic(E)		--->	vexpr_number(E).
+
+:- rule vexpr_boolean(vexpr).
+vexpr_boolean(E)	--->	[(true)], { E = const(value(boolean(yes))) }.
+vexpr_boolean(E)	--->	[(false)], { E = const(value(boolean(no))) }.
+
+:- rule vexpr_string(vexpr).
+vexpr_string(E)		--->	[string(S)],
+				{ E = const(value(string(unquote(S)))) }.
+
+:- rule vexpr_parent(vexpr).
+vexpr_parent(E)		--->	['('], vexpr(E), [')'].
+
+:- rule vexpr_func(vexpr).
+vexpr_func(E)		--->	[identifier(F), '('], vexpr_list(L), [')'],
+				{ is_func_op(F, Op) ->
+					E = primitive(function(Op, L))
+				;
+					error("unknown function: " ++ F)
+				}.
+
+:- rule vexpr_list(list(vexpr)).
+vexpr_list([E])		--->	vexpr(E).
+vexpr_list([E | Es])	--->	vexpr(E), [';'], vexpr_list(Es).
+
+:- rule vexpr_reference(vexpr).
+vexpr_reference(E)	--->	vexpr_cell_reference(R),
+				{ E = reference(reference(simple(R))) }.
+vexpr_reference(E)	--->	vexpr_cell_reference(R1), [':'],
+				vexpr_cell_reference(R2),
+				{ E = reference(reference(range(R1, R2))) }.
+
+:- rule vexpr_cell_reference(cell_reference).
+vexpr_cell_reference(E)	--->	vexpr_ref_type(R), { E = local(R) }.
+vexpr_cell_reference(E)	--->	[identifier(S), '!'], vexpr_ref_type(R),
+				{ E = worksheet(S, R) }.
+
+:- rule vexpr_ref_type(reference_type).
+vexpr_ref_type(RT)	--->	vexpr_rel_ref_type(RT).
+vexpr_ref_type(RT)	--->	vexpr_fixed_ref_type(RT).
+
+:- rule vexpr_rel_ref_type(reference_type).
+vexpr_rel_ref_type(RT)	--->	[rowcolumn], { RT = relative(0, 0) }.
+vexpr_rel_ref_type(RT)	--->	[row], relative(R), [column],
+				{ RT = relative(R, 0) }.
+vexpr_rel_ref_type(RT)	--->	[rowcolumn], relative(C),
+				{ RT = relative(0, C) }.
+vexpr_rel_ref_type(RT)	--->	[row], relative(R),
+				[column], relative(C),
+				{ RT = relative(R, C) }.
+
+:- rule relative(int).
+relative(I)		--->	['[', integer(I), ']'].
+relative(-I)		--->	['[', '-', integer(I), ']'].
+
+:- rule vexpr_fixed_ref_type(reference_type).
+vexpr_fixed_ref_type(RT) --->	[identifier(R)], { RT = fixed(R) }.
+
+:- rule vexpr_number(vexpr).
+vexpr_number(E)		--->	[real(R)], { E = const(value(number(R))) }.
+vexpr_number(E)		--->	[integer(I)],
+				{ E = const(value(number(float(I)))) }.
+				
+%----------------------------------------------------------------------------- %
+
+:- func unquote(string) = string.
+
+unquote(InitialStr) = Str :-
+	Length = string__length(InitialStr),
+	% Drop the initial and final "
+	Str0 = string__left(string__right(InitialStr, Length - 1), Length - 2),
+	% Replace "" with "
+	string__replace_all(Str0, "\"\"", "\"", Str).
+
+:- pred is_func_op(string, func_op).
+:- mode is_func_op(in, out) is semidet.
+:- mode is_func_op(out, in) is det.	% Ensure that we handle all possible
+					% functions.
+
+is_func_op("MIN", func_min).
+is_func_op("MAX", func_max).
+is_func_op("ROUND", func_round).
+is_func_op("ROUNDUP", func_roundup).
+is_func_op("INT", func_int).
+is_func_op("SUM", func_sum).
+is_func_op("IF", func_if).
+is_func_op("YEAR", func_year).
+is_func_op("MONTH", func_month).
+is_func_op("WEEKDAY", func_weekday).
+is_func_op("DATE", func_date).
+is_func_op("TODAY", func_today).
+is_func_op("NOW", func_now).
+is_func_op("NOT", func_not).
+is_func_op("AND", func_and).
+is_func_op("OR", func_or).
+is_func_op("ISBLANK", func_isblank).
+is_func_op("ISERROR", func_iserror).
+is_func_op("RIGHT", func_right).
+is_func_op("LEFT", func_left).
+is_func_op("SEARCH", func_search).
+is_func_op("TEXT", func_text).
+is_func_op("CONCATENATE", func_concatenate).
+is_func_op("LEN", func_len).
+
+%----------------------------------------------------------------------------- %
+%----------------------------------------------------------------------------- %
+
+:- interface.
+% Avoid a warning.
+:- type dummy == list(int).
+
+%----------------------------------------------------------------------------- %
+%----------------------------------------------------------------------------- %
Index: excel_engine/excel_engine.parse.m
===================================================================
RCS file: d:/project/cvsroot/excel_engine/excel_engine.parse.m,v
retrieving revision 1.3
diff -u -r1.3 excel_engine.parse.m
--- excel_engine/excel_engine.parse.m	20 Feb 2004 13:29:38 -0000	1.3
+++ excel_engine/excel_engine.parse.m	24 Feb 2004 10:58:38 -0000
@@ -11,6 +11,7 @@
 :- interface.
 
 :- include_module xml.
+:- include_module formula.
 
 :- import_module list.
 
@@ -39,7 +40,8 @@
 	func cell_row(T) = int,
 
 	func cell_value(T) = string,
-	func cell_type(T) = cell_parse_type
+	func cell_type(T) = cell_parse_type,
+	func cell_formula(T) = string
 ].
 
 :- func create_spreadsheet(T) = spreadsheet <= spreadsheet(T).
@@ -50,6 +52,7 @@
 :- implementation.
 
 :- import_module require, string.
+:- import_module excel_engine__parse__formula.
 
 %------------------------------------------------------------------------------%
 
@@ -83,7 +86,16 @@
 
 		CellValue = to_cell_value(WorkSheet ^ cell_type,
 				WorkSheet ^ cell_value),
-		Value = cell(CellValue),
+
+		Formula = WorkSheet ^ cell_formula,
+		( Formula = "" ->
+			MaybeFormula = no
+		;
+			parse(Formula, Expr),
+			MaybeFormula = yes(Expr)
+		),
+
+		Value = cell(CellValue, MaybeFormula),
 
 		!:CellMap = map__det_insert(!.CellMap, Ref, Value),
 
Index: excel_engine/excel_engine.parse.xml.m
===================================================================
RCS file: d:/project/cvsroot/excel_engine/excel_engine.parse.xml.m,v
retrieving revision 1.2
diff -u -r1.2 excel_engine.parse.xml.m
--- excel_engine/excel_engine.parse.xml.m	20 Feb 2004 13:29:38 -0000	1.2
+++ excel_engine/excel_engine.parse.xml.m	24 Feb 2004 10:58:38 -0000
@@ -221,19 +221,16 @@
 	Row = Cell ^ row
     ),
 
-    /*
-    (cell_formula(Formula, Xml, Xml) :-
+    (cell_value(Xml) = get_current_cell(Xml) ^ value),
+    (cell_type(Xml) = get_current_cell(Xml) ^ (type)),
+    (cell_formula(Xml) = Formula :-
     	Cell = get_current_cell(Xml),
 	( Cell ^ formula = yes(F) ->
 		Formula = F
 	;
 		Formula = ""
 	)
-    ),
-    */
-
-    (cell_value(Xml) = get_current_cell(Xml) ^ value),
-    (cell_type(Xml) = get_current_cell(Xml) ^ (type))
+    )
 
     /*
     (cell_label(Label, Xml, Xml) :-
Index: excel_engine/tests/Mmakefile
===================================================================
RCS file: d:/project/cvsroot/excel_engine/tests/Mmakefile,v
retrieving revision 1.2
diff -u -r1.2 Mmakefile
--- excel_engine/tests/Mmakefile	20 Feb 2004 13:45:12 -0000	1.2
+++ excel_engine/tests/Mmakefile	24 Feb 2004 10:58:38 -0000
@@ -1,7 +1,7 @@
 #-----------------------------------------------------------------------------#
 
 TESTS=
-SUBDIRS=simple
+SUBDIRS=simple formula
 
 include Mmake.common
 
@@ -9,12 +9,12 @@
 
 -include ../../Mmake.params
 
-INCLUDES=-I .. -I ../../xml
+INCLUDES=-I .. -I ../../xml -I ../../lex
 VPATH=..:../../xml:$(MMAKE_VPATH)
-MLLIBS+=-L.. -L../../xml -lexcel_engine -lxml
+MLLIBS+=-L.. -L ../../lex -L../../xml -lexcel_engine -lxml -llex -lregex
 MCFLAGS+=$(INCLUDES)
 CFLAGS+=$(INCLUDES)
-C2INITARGS+=../excel_engine.init ../../xml/xml.init
+C2INITARGS+=../excel_engine.init ../../xml/xml.init ../../lex/lex.init
 
 runtests: test_excel
 
Index: excel_engine/tests/formula/Mmakefile
===================================================================
RCS file: excel_engine/tests/formula/Mmakefile
diff -N excel_engine/tests/formula/Mmakefile
--- nul	1 Jan 1970 00:00:00 -0000
+++ excel_engine/tests/formula/Mmakefile	24 Feb 2004 10:58:38 -0000
@@ -0,0 +1,7 @@
+ROOTDIR=..
+THIS_DIR=formula
+SUBDIRS=
+TESTS=\
+	references
+
+include $(ROOTDIR)/Mmake.common
Index: excel_engine/tests/formula/references.exp
===================================================================
RCS file: excel_engine/tests/formula/references.exp
diff -N excel_engine/tests/formula/references.exp
--- nul	1 Jan 1970 00:00:00 -0000
+++ excel_engine/tests/formula/references.exp	24 Feb 2004 10:58:38 -0000
@@ -0,0 +1,18 @@
+Sheet1!C3:	number(1.00000000000000)
+Sheet1!C2:	number(1.00000000000000)
+Sheet1!C1:	number(1.00000000000000)
+Sheet1!B3:	number(1.00000000000000)
+Sheet1!B2:	number(1.00000000000000)
+Sheet1!B1:	number(1.00000000000000)
+Sheet1!A3:	number(1.00000000000000)
+Sheet1!A2:	number(1.00000000000000)
+Sheet1!A1:	number(1.00000000000000)
+Sheet2!C3:	number(1.00000000000000)
+Sheet2!C2:	number(1.00000000000000)
+Sheet2!C1:	number(1.00000000000000)
+Sheet2!B3:	number(1.00000000000000)
+Sheet2!B2:	number(1.00000000000000)
+Sheet2!B1:	number(1.00000000000000)
+Sheet2!A3:	number(1.00000000000000)
+Sheet2!A2:	number(1.00000000000000)
+Sheet2!A1:	number(1.00000000000000)
Index: excel_engine/tests/formula/references.xls
===================================================================
RCS file: excel_engine/tests/formula/references.xls
diff -N excel_engine/tests/formula/references.xls
Binary files nul and references.xls differ
Index: excel_engine/tests/formula/references.xml
===================================================================
RCS file: excel_engine/tests/formula/references.xml
diff -N excel_engine/tests/formula/references.xml
--- nul	1 Jan 1970 00:00:00 -0000
+++ excel_engine/tests/formula/references.xml	24 Feb 2004 10:58:38 -0000
@@ -0,0 +1,105 @@
+<?xml version="1.0"?>
+<Workbook xmlns="urn:schemas-microsoft-com:office:spreadsheet"
+ xmlns:o="urn:schemas-microsoft-com:office:office"
+ xmlns:x="urn:schemas-microsoft-com:office:excel"
+ xmlns:ss="urn:schemas-microsoft-com:office:spreadsheet"
+ xmlns:html="http://www.w3.org/TR/REC-html40">
+ <DocumentProperties xmlns="urn:schemas-microsoft-com:office:office">
+  <LastAuthor>Peter Ross</LastAuthor>
+  <Created>1996-10-14T23:33:28Z</Created>
+  <LastSaved>2004-02-24T11:00:55Z</LastSaved>
+  <Version>10.3501</Version>
+ </DocumentProperties>
+ <OfficeDocumentSettings xmlns="urn:schemas-microsoft-com:office:office">
+  <DownloadComponents/>
+  <LocationOfComponents HRef="file:///F:\"/>
+ </OfficeDocumentSettings>
+ <ExcelWorkbook xmlns="urn:schemas-microsoft-com:office:excel">
+  <WindowHeight>9300</WindowHeight>
+  <WindowWidth>15135</WindowWidth>
+  <WindowTopX>120</WindowTopX>
+  <WindowTopY>120</WindowTopY>
+  <ActiveSheet>1</ActiveSheet>
+  <AcceptLabelsInFormulas/>
+  <ProtectStructure>False</ProtectStructure>
+  <ProtectWindows>False</ProtectWindows>
+ </ExcelWorkbook>
+ <Styles>
+  <Style ss:ID="Default" ss:Name="Normal">
+   <Alignment ss:Vertical="Bottom"/>
+   <Borders/>
+   <Font/>
+   <Interior/>
+   <NumberFormat/>
+   <Protection/>
+  </Style>
+ </Styles>
+ <Worksheet ss:Name="Sheet1">
+  <Table ss:ExpandedColumnCount="3" ss:ExpandedRowCount="3" x:FullColumns="1"
+   x:FullRows="1">
+   <Row>
+    <Cell ss:Formula="=R[1]C[1]"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=R[1]C"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=R[1]C[-1]"><Data ss:Type="Number">1</Data></Cell>
+   </Row>
+   <Row>
+    <Cell ss:Formula="=RC[1]"><Data ss:Type="Number">1</Data></Cell>
+    <Cell><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=RC[-1]"><Data ss:Type="Number">1</Data></Cell>
+   </Row>
+   <Row>
+    <Cell ss:Formula="=R[-1]C[1]"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=R[-1]C"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=R[-1]C[-1]"><Data ss:Type="Number">1</Data></Cell>
+   </Row>
+  </Table>
+  <WorksheetOptions xmlns="urn:schemas-microsoft-com:office:excel">
+   <Panes>
+    <Pane>
+     <Number>3</Number>
+     <ActiveCol>2</ActiveCol>
+    </Pane>
+   </Panes>
+   <ProtectObjects>False</ProtectObjects>
+   <ProtectScenarios>False</ProtectScenarios>
+  </WorksheetOptions>
+ </Worksheet>
+ <Worksheet ss:Name="Sheet2">
+  <Table ss:ExpandedColumnCount="3" ss:ExpandedRowCount="3" x:FullColumns="1"
+   x:FullRows="1">
+   <Row>
+    <Cell ss:Formula="=Sheet1!R[1]C[1]"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=Sheet1!R[1]C"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=Sheet1!R[1]C[-1]"><Data ss:Type="Number">1</Data></Cell>
+   </Row>
+   <Row>
+    <Cell ss:Formula="=Sheet1!RC[1]"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=Sheet1!RC"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=Sheet1!RC[-1]"><Data ss:Type="Number">1</Data></Cell>
+   </Row>
+   <Row>
+    <Cell ss:Formula="=Sheet1!R[-1]C[1]"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=Sheet1!R[-1]C"><Data ss:Type="Number">1</Data></Cell>
+    <Cell ss:Formula="=Sheet1!R[-1]C[-1]"><Data ss:Type="Number">1</Data></Cell>
+   </Row>
+  </Table>
+  <WorksheetOptions xmlns="urn:schemas-microsoft-com:office:excel">
+   <Selected/>
+   <Panes>
+    <Pane>
+     <Number>3</Number>
+     <ActiveRow>2</ActiveRow>
+     <ActiveCol>2</ActiveCol>
+    </Pane>
+   </Panes>
+   <ProtectObjects>False</ProtectObjects>
+   <ProtectScenarios>False</ProtectScenarios>
+  </WorksheetOptions>
+ </Worksheet>
+ <Worksheet ss:Name="Sheet3">
+  <WorksheetOptions xmlns="urn:schemas-microsoft-com:office:excel">
+   <ProtectObjects>False</ProtectObjects>
+   <ProtectScenarios>False</ProtectScenarios>
+  </WorksheetOptions>
+ </Worksheet>
+</Workbook>
Index: lex/Mmakefile
===================================================================
RCS file: d:/project/cvsroot/lex/Mmakefile,v
retrieving revision 1.1.1.1
diff -u -r1.1.1.1 Mmakefile
--- lex/Mmakefile	24 Feb 2004 10:08:53 -0000	1.1.1.1
+++ lex/Mmakefile	24 Feb 2004 10:58:38 -0000
@@ -1,6 +1,8 @@
 # Copyright (C) 2001 Ralph Becket <rbeck at microsoft.com>
 # Copyright (C) 2002 The University of Melbourne
 
+-include ../Mmake.params
+
 # To build, do the following:
 #
 # $ mmake depend


-- 
Peter Ross		
Software Engineer                                (Work)   +32 2 757 10 15
Mission Critical                                 (Mobile) +32 485 482 559
--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list