Update of /cvsroot/aimmath/AIM/WEB-INF/maple/aim
In directory sc8-pr-cvs1:/tmp/cvs-serv16821/WEB-INF/maple/aim
Modified Files:
MatrixQuestion.mpl MultiQuestion.mpl Question.mpl
TextQuestion.mpl
Added Files:
PartialFraction.mpl
Log Message:
--- NEW FILE: PartialFraction.mpl ---
read("Package.mpl"):
Package("aim/PartialFraction","
This package contains a number of useful functions for use in
questions about partial fractions.
"
):
`Package/Assign`(
`type/AffineTerm`::boolean,
"An expression @t@ is of type @AffineTerm(y)@ if it has the form
@ay+b@, where @a@ and @b@ are of type @complexcons@ and
@a<>0@.
The variable used defaults to @x@, so an expression has type
@AffineTerm@ iff it has type @AffineTerm(x)@.
",
proc(term,xx_)
local xx,a,b;
xx := `if`(nargs > 1,xx_,x);
type(term,
{identical(xx),
`&+`(identical(xx),complexcons),
`&+`(complexcons,identical(xx)),
`&*`(complexcons,identical(xx)),
`&+`(`&*`(complexcons,identical(xx)),complexcons),
`&+`(complexcons,`&*`(complexcons,identical(xx)))});
end
):
`Package/Assign`(
`type/QuadraticTerm`::boolean,
"An expression @t@ is of type @QuadraticTerm(y)@ if it has the form
@ay<sup>2</sup>+by+c@, where @a@, @b@ and @c@ are of type
@complexcons@ and @a<>0@.
The variable used defaults to @x@, so an expression has type
@QuadraticTerm@ iff it has type @QuadraticTerm(x)@.
",
proc(term,xx_)
local xx,a,b;
xx := `if`(nargs > 1,xx_,x);
if not(type(term,polynom(complexcons,xx))) then
return(false);
fi;
return(evalb(degree(expand(term),xx) = 2));
end
):
`Package/Assign`(
`type/PartialFractionTerm`::boolean,
"An expression @t@ is of type @PartialFractionTerm(y)@ if it
is a constant multiple of an integer power of @y@, or a
negative integer power of an expression of type @AffineTerm(y)@.
The variable used defaults to @x@, so an expression has type
@PartialFractionTerm@ iff it has type @PartialFractionTerm(x)@.
",
proc(term,xx_)
local xx,u;
xx := `if`(nargs > 1,xx_,x);
u := term;
if type(u,`*`) then
u := remove(type,u,complexcons);
fi;
evalb(
type(u,complexcons) or
type(u,identical(xx)) or
type(u,identical(xx)^integer) or
type(u,AffineTerm(xx)^negint)
)
end
):
`Package/Assign`(
`type/QuadraticPartialFractionTerm`::boolean,
"An expression @t@ is of type @QuadraticPartialFractionTerm(y)@
if it is a constant multiple of an integer power of @y@, or a
negative integer power of an expression of type @AffineTerm(y)@
or @QuadraticTerm(y)@.
The variable used defaults to @x@, so an expression has type
@PartialFractionTerm@ iff it has type @PartialFractionTerm(x)@.
",
proc(term,xx_)
local xx;
xx := `if`(nargs > 1,xx_,x);
evalb(
type(term,complexcons) or
type(term,identical(xx)) or
type(term,identical(xx)^integer) or
type(term,AffineTerm(xx)^negint) or
type(term,QuadraticTerm(xx)^negint)
)
end
):
`Package/Assign`(
`type/PartialFraction`,
"An expression is of type @PartialFraction(y)@ if it is a (possibly
empty) sum of terms of type @PartialFractionTerm(y)@.
The variable used defaults to @x@, so an expression has type
@PartialFraction@ iff it has type @PartialFraction(x)@.
",
proc(expr,xx_)
local xx;
xx := `if`(nargs > 1,xx_,x);
`aim/TestEqual`(expr,0) or
type(expr,PartialFractionTerm(xx)) or
(type(expr,`+`) and
type([op(expr)],list(PartialFractionTerm(xx))));
end
):
`Package/Assign`(
`type/QuadraticPartialFraction`,
"An expression is of type @QuadraticPartialFraction(y)@ if it
is a (possibly empty) sum of terms of type
@QuadraticPartialFractionTerm(y)@.
",
proc(expr,xx_)
local xx;
xx := `if`(nargs > 1,xx_,x);
`aim/TestEqual`(expr,0) or
type(expr,PartialFractionTerm(xx)) or
(type(expr,`+`) and
type([op(expr)],list(QuadraticPartialFractionTerm(xx))));
end
):
`Package/Assign`(
`type/ObviousRational`::boolean,
"An expression is of type @ObviousRational(y)@ if it is a product of
integer powers of polynomials in @y@ with coefficients of type
@complexcons@.
",
proc(expr,xx_)
local xx,u;
xx := `if`(nargs > 1,xx_,x);
if type(expr,polynom(complexcons,xx)) then return(true); fi;
if type(expr,`*`) then
for u in op(expr) do
if not(type(u,{polynom(complexcons,xx),
polynom(complexcons,xx)^negint})) then
return(false);
fi;
od;
return(true);
fi;
return(false);
end
):
`Class/Declare`(
`aim/PartialFraction/Expression`,
"",
['Field','Value'::algebraic,
"The value of the partial fraction, as an ordinary Maple expression."
],
['Field','Variable'::string = "x",
"The name of the variable used in the partial fraction expression."
],
['Field','Poles'::list(complexcons),
"The list of poles of the function. As usual, if @f(x)=p(x)/q(x)@
where @deg(p(x))≥deg(q(x))@, we say that @f(x)@ has a pole of
order @deg(p(x))-deg(q(x))@ at @infinity@.
"
],
['Field','OrderTable'::table,
"This table stores the orders of the poles"
],
['Method','PoleOrder'::integer,
"",
proc(this,a::complexcons)
local n;
n := eval(this['OrderTable'][a]);
`if`(type([n],[integer]),n,0);
end
],
['Field','CoefficientTable'::table,
"This table @t@ is set up so that @t[a,n]@ is the coefficient of
@(x-a)<SUP>-n</SUP>@ for finite @a@ and @n>0@, and @t[infinity,n]@
is the coefficient of @x<SUP>n</SUP>@ for @n≥0@.
"
],
['Method','Coefficient'::complexcons,
"",
proc(this,a::complexcons,n::integer)
local c;
c := eval(this['CoefficientTable'][a,n]);
`if`(type([c],[complexcons]),c,0);
end
],
['Field','BadTerms',""],
['Constructor',
"",
proc(this,f,xx_,prep_::boolean)
local ff,xx,prep,vars,g;
ff := Value(f);
if nargs > 2 then
xx := xx_;
else
vars := remove(type,indets(ff,symbol),complexcons);
if nops(vars) = 1 then
xx := op(1,vars);
else
error(__("Cannot determine variable"));
fi;
fi;
this['Variable'] := convert(xx,string);
prep := `if`(nargs > 3,prep_,false);
if prep then
g := convert(ff,parfrac,xx,{I,sqrt(2),sqrt(3),sqrt(5),sqrt(7)});
else
g := ff;
fi;
this['Value'] := g;
`aim/PartialFraction/Analyze`(this,g,xx);
if prep and (this['BadTerms'] <> []) then
error(__("Could not convert to partial fraction form."));
fi;
end]
):
`Class/Declare`(
`aim/PartialFraction/Problem`,
"",
['IncludedField','Expression'::`aim/PartialFraction/Expression`,""],
['Field','FunctionName'::string,""],
['Field','Question',
"An expression to be presented to the student for conversion
to partial fraction form. This may be an #InertExpr# object.
"
],
['Field','RightAnswer',
"The correct partial fraction form of the question. This may be
an #InertExpr# object.
"
],
['Method','SetRightAnswer',
"",
proc(this)
local xx,poles,orders,cfs,a,i,rightans;
xx := convert(this['Variable'],name);
poles := eval(this['Poles']);
orders := eval(this['OrderTable']);
cfs := eval(this['CoefficientTable']);
rightans := [];
for a in poles do
if a <> infinity then
for i from 1 to orders[a] do
if cfs[a,i] <> 0 then
rightans := [op(rightans),Over(cfs[a,i],ToThe(Plus(xx,-a),i))];
fi;
od;
fi;
od;
if type(orders[infinity],integer) then
if cfs[infinity,0] <> 0 then
rightans := [op(rightans),cfs[infinity,0]];
fi;
if orders[infinity] > 0 and cfs[infinity,1] <> 0 then
rightans := [op(rightans),Times(cfs[infinity,1],xx)];
fi;
for i from 2 to orders[infinity] do
if cfs[infinity,i] <> 0 then
rightans := [op(rightans),Times(cfs[infinity,i],ToThe(xx,i))];
fi;
od;
fi;
this['RightAnswer'] := Plus(op(rightans));
end
],
['Field','GeneralCoefficientTable'::table,""],
['Field','GeneralForm',""],
['Method','SetGeneralForm',
"",
proc(this)
local xx,poles,orders,gcfs,a,i,j,v,vars,nv,nextvar,terms;
vars :=
[`latex/latex/copy`('A'),
`latex/latex/copy`('B'),
`latex/latex/copy`('C'),
`latex/latex/copy`('D '),
`latex/latex/copy`('E'),
`latex/latex/copy`('F'),
`latex/latex/copy`('G'),
`latex/latex/copy`('H'),
`latex/latex/copy`('K'),
`latex/latex/copy`('L'),
`latex/latex/copy`('M'),
`latex/latex/copy`('N'),
`latex/latex/copy`('P'),
`latex/latex/copy`('Q'),
`latex/latex/copy`('R'),
`latex/latex/copy`('S'),
`latex/latex/copy`('T'),
`latex/latex/copy`('U'),
`latex/latex/copy`('V'),
`latex/latex/copy`('W'),
`latex/latex/copy`('X'),
`latex/latex/copy`('Y'),
`latex/latex/copy`('Z')];
nv := nops(vars);
xx := convert(this['Variable'],name);
poles := eval(this['Poles']);
orders := eval(this['OrderTable']);
gcfs := eval(this['GeneralCoefficientTable']);
terms := [];
j := 0;
nextvar :=
proc()
j := j+1;
if j > nv then
error(__("Too many terms"));
fi;
vars[j];
end;
for a in poles do
if a <> infinity then
for i from 1 to orders[a] do
gcfs[a,i] := nextvar();
terms := [op(terms),Over(gcfs[a,i],ToThe(Plus(xx,-a),i))];
od;
fi;
od;
if type(orders[infinity],integer) then
if cfs[infinity,0] <> 0 then
gcfs[infinity,0] := nextvar();
terms := [op(terms),gcfs[infinity,0]];
fi;
if orders[infinity] > 0 and cfs[infinity,1] <> 0 then
gcfs[infinity,1] := nextvar();
terms := [op(terms),Times(gcfs[infinity,1],xx)];
fi;
for i from 2 to orders[infinity] do
if cfs[infinity,i] <> 0 then
gcfs[infinity,i] := nextvar();
terms := [op(terms),Times(gcfs[infinity,i],ToThe(xx,i))];
fi;
od;
fi;
this['GeneralForm'] := terms;
end
],
['Field','Numerator',""],
['Field','Denominator',""],
['Method','SetNumerator',
"",
proc(this)
local f,d,n,terms,rewrite,xx;
f := Value(this['Question']);
xx := convert(this['Variable'],name);
rewrite :=
evalb(not(type(f,ObviousRational(x))));
if rewrite then f := factor(f); fi;
terms := `if`(type(f,`*`),[op(f)],[f]);
d,n := selectremove(type,terms,anything^negint);
d := 1/`*`(op(d));
n := `*`(op(n));
if rewrite then
n := expand(n);
d := expand(d);
fi;
this['Denominator'] := d;
this['Numerator'] := n;
end
],
['Field','FactoredForm',"" ],
['Method','SetFactored',
"",
proc(this)
this['FactoredForm'] := factor(this['Value'],{I,sqrt(2),sqrt(3),sqrt(5),sqrt(7)});
end
],
['Field','Solution'::`HTML/String`,
""
],
['Method','SetSolution',
"",
proc(this)
local poles,poletable,xx,fname,r,infinityterm,d,
gentop,gtcoll,numcoll,eqns,i,cfs,gcfs,sols,p,u,v,oldD;
global D;
oldD := eval(D);
unprotect('D');
unassign('D');
xx := convert(this['Variable'],name);
fname := this['FunctionName'];
poles := this['Poles'];
if poles[-1] = infinity then
poles := poles[1..-2];
fi;
if poles = [] then
poletable := "There are no poles.\n<br>\n";
elif nops(poles) = 1 then
p := poles[1];
poletable :=
sprintf(
__("There is a pole of order $%d$ at $%A = %s$, and no other poles."),
this['PoleOrder',p],xx,`aim/LaTeX`(p));
else
poletable :=
cat(
__("The poles and their orders are as follows:"),"\n",
"\\begin{tabular}{ll}\n",
"{\\bf ",__("Pole"),"} & {\\bf ",__("Order"),"} \\\\ \n",
op(map(p -> sprintf("$%s$ & %d \\\\ \n",`aim/LaTeX`(p),this['PoleOrder',p]),poles)),
"\\end{tabular}\n")
fi;
if member(infinity,this['Poles']) then
r := this['PoleOrder',infinity];
if r = 0 then
infinityterm :=
__("The numerator and denominator have the same degree, so the partial fraction decomposition should include a constant term.");
elif r = 1 then
infinityterm :=
sprintf(__("The degree of the numerator is one more than that of the denominator, so the partial fraction decomposition should include a constant term and a multiple of $%A$."),xx);
else
infinityterm :=
sprintf(__("There is a gap of %d between the degree of the denominator and the degree of the numerator, so the partial fraction decomposition chould contain multiples of $%A^i$ for i from 0 to %d."),r,xx,r);
fi;
else
infinityterm := "";
fi;
d := Value(this['Denominator']);
gentop := [];
for u in this['GeneralForm'] do
v := Value(u)*d;
if not(type(v,polynom(complexcons,xx))) then
v := expand(factor(v));
fi;
gentop := [op(gentop),v];
od;
gtcoll := collect(`+`(op(gentop)),xx);
numcoll := collect(Value(this['Numerator']),xx);
eqns := NULL;
for i from 0 to degree(gtcoll,xx) do
eqns := eqns,
`aim/LaTeX`(coeff(gtcoll,xx,i)),
" & = & ",
`aim/LaTeX`(coeff(numcoll,xx,i)),
" \\\\ \n";
od;
eqns := [eqns][1..-2];
eqns := cat("\\begin{eqnarray*}\n",op(eqns),"\n\\end{eqnarray*}\n");
cfs := eval(this['CoefficientTable']);
gcfs := eval(this['GeneralCoefficientTable']);
sols := NULL;
for p in this['Poles'] do
for i from `if`(p = infinity,0,1) to this['PoleOrder',p] do
sols := sols,
`aim/LaTeX`(gcfs[p,i]),
" & = & ",
`aim/LaTeX`(cfs[p,i]),
" \\\\ \n";
od;
od;
sols := [sols][1..-2];
sols := cat("\\begin{eqnarray*}\n",op(sols),"\n\\end{eqnarray*}\n");
this['Solution'] :=
cat(
"<latex>",
sprintf(__("The function %s can be factored as"),fname),
"\n\\[",`aim/LaTeX`(this['FactoredForm'])," \\]\n",
poletable,"\n\n",
infinityterm,"\n\n",
__("The general form is thus"),
"\n\\[ ",
`if`(fname = "","",cat(fname," = ")),
`aim/LaTeX`(Plus(op(this['GeneralForm']))),
". \\]\n",
__("We set this equal to"),
"\n\\[ ",`aim/LaTeX`(this['FactoredForm'])," \\]\n",
sprintf(__("We then multiply both sides by $%s$, and multiply everything out to get"),
`aim/LaTeX`(this['Denominator'])),
"\n\\begin{eqnarray*}\n ",
`aim/LaTeX`(this['Numerator']), " & = & ", `aim/LaTeX`(Plus(op(gentop))), "\\\\ \n",
`aim/LaTeX`(numcoll), " & = & ", `aim/LaTeX`(gtcoll),"\n",
"\\end{eqnarray*}\n",
__("By comparing coefficients, we see that"),eqns,
__("These equations can be solved to give"),sols,
__("The partial fraction decomposition is thus"),
"\n\\[ ",
`if`(fname = "","",cat(fname," = ")),
`aim/LaTeX`(this['RightAnswer']),
". \\]\n</latex>\n"
);
D := eval(oldD);
protect('D');
this['Solution'];
end
],
['Constructor',
"",
proc(this,f,xx_)
local ff,xx,vars,g;
ff := Value(f);
if nargs > 2 then
xx := xx_;
else
vars := remove(type,indets(ff,symbol),complexcons);
if nops(vars) = 1 then
xx := op(1,vars);
else
error(__("Cannot determine variable"));
fi;
fi;
this['Question'] := eval(f);
this['Expression'] :=
`new/aim/PartialFraction/Expression`(ff,xx,true);
this['GeneralCoefficientTable'] := table([]);
this['SetRightAnswer'];
this['SetNumerator'];
this['SetGeneralForm'];
this['SetFactored'];
end]
):
`Package/Assign`(
`aim/PartialFraction/Analyze`,
"",
proc(tbl::table,g,xx)
local terms,poles,orders,cfs,bad,badterms,
t,u,v,i,n,a,c,d,rightans;
if `aim/TestEqual`(g,0) then
terms := [];
elif type(g,`+`) then
terms := [op(g)];
else
terms := [g];
fi;
poles := NULL;
orders := table([]);
cfs := table([]);
badterms := NULL;
for t in terms do
bad := false;
if type(t,complexcons) then
a := infinity; n := 0; c := 1;
else
if type(t,`*`) then
c,u := selectremove(type,t,complexcons);
else
c := 1; u := t;
fi;
if type(u,identical(xx)) then
a := infinity; n := 1;
elif type(u,identical(xx)^posint) then
a := infinity; n := op(2,u);
elif type(u,AffineTerm(xx)^negint) then
v := op(1,u);
d := coeff(v,xx);
c := c/d;
a := eval(subs(xx = 0,-v/d));
n := -op(2,u);
else
bad := true;
badterms := badterms,t;
fi;
fi;
if not(bad) then
poles := poles,a;
if type([orders[a]],[integer]) then
orders[a] := max(orders[a],n);
else
orders[a] := n;
fi;
if type([cfs[a,n]],[complexcons]) then
cfs[a,n] := cfs[a,n] + c;
else
cfs[a,n] := c;
fi;
fi;
od;
poles := [op({poles})];
poles :=
sort(poles,
(a,b) ->
evalb(is((Re(a) < Re(b)) or ((Re(a) = Re(b)) and (Im(a) < Im(b)))) = true));
for a in poles do
for i from 1 to orders[a] do
if not(type([cfs[a,i]],[complexcons])) then
cfs[a,i] := 0;
fi;
od;
od;
if not(type([cfs[infinity,0]],[complexcons])) then
cfs[infinity,0] := 0;
fi;
tbl['Poles'] := poles;
tbl['OrderTable'] := eval(orders);
tbl['CoefficientTable'] := eval(cfs);
tbl['BadTerms'] := [badterms];
end
):
`Package/Assign`(
`aim/PartialFraction/Test`::[numeric,string,string],
"",
proc(a,
Q::`aim/PartialFraction/Problem`)
local argtype,ans,attempt,xx,t,vars,extravars,extrapoles,missingpoles,
p,polestring,i,quadterms,nastyterms,msg;
if type(a,`aim/Question/Attempt`) then
argtype := "attempt";
ans := a['Answer'];
attempt := eval(a);
elif type(a,`aim/Question/ShortAttempt`) then
argtype := "shortattempt";
ans := a['Answer'];
attempt := `aim/Question/MakeAttempt`(a);
else
argtype := "ordinary";
ans := eval(a);
attempt := `new/aim/Question/Attempt`();
attempt['Answer'] := ans;
fi;
if `aim/TestEqual`(a,Q['Value']) then
attempt['RawMark'] := 1;
return([1,"",""]);
fi;
attempt['RawMark'] := 0;
if length(Q['Variable']) = 1 then
msg := `aim/CheckAlgebraic`(a,{Q['Variable']});
if msg <> "" then
attempt['IsValid'] := false;
attempt['ValidationMessage'] := msg;
attempt['ValidationNote'] := "checkalgebraic";
return([0,msg,"checkalgebraic"]);
fi;
fi;
xx := convert(Q['Variable'],name);
vars := remove(type,indets(a,symbol),complexcons);
extravars := vars minus {xx};
if extravars <> {} then
attempt['AddAnswerNote',__("Extra variables")];
attempt['AddFeedback',
sprintf(__("Your answer depends on the following variable(s): %A.\nIt should only depend on %A."),
extravars,xx)];
return([0,attempt['Feedback'],attempt['AnswerNote']]);
fi;
t := `new/aim/PartialFraction/Expression`(a,xx);
if t['BadTerms'] <> [] then
quadterms,nastyterms :=
selectremove(type,t['BadTerms'],QuadraticPartialFractionTerm(xx));
if nastyterms = {} then
attempt['AddAnswerNote',__("Quadratic terms")];
attempt['AddFeedback',
cat(
sprintf(
__("Your answer is not a valid partial fraction decomposition. Such a decomposition may only contain terms of the form c %A<SUP>n</SUP> (with n ≥ 0) or c(%A - a)<SUP>-n</SUP> (with n > 0). Your answer contains the following terms, which are not of this form:"),xx,xx),
`aim/LaTeX/Display`({op(t['BadTerms'])}),
__("These might be valid in a quadratic partial fraction decomposition, but this question asked for an ordinary partial fraction decomposition.")
)
];
else
attempt['AddAnswerNote',__("Bad terms")];
attempt['AddFeedback',
cat(
sprintf(
__("Your answer is not a valid partial fraction decomposition. Such a decomposition may only contain terms of the form c %A<SUP>n</SUP> (with n ≥ 0) or c(%A - a)<SUP>-n</SUP> (with n > 0). Your answer contains the following terms, which are not of this form:"),xx,xx),
`aim/LaTeX/Display`({op(t['BadTerms'])})
)
];
fi;
return([0,attempt['Feedback'],attempt['AnswerNote']]);
fi;
extrapoles := {op(t['Poles'])} minus {op(Q['Poles'])};
missingpoles := {op(Q['Poles'])} minus {op(t['Poles'])};
if extrapoles <> {} then
attempt['AddAnswerNote',__("Extra poles")];
polestring :=
`Util/CommaJoin`(op(map((p,v) -> sprintf(" $%A=%s$",v,`aim/LaTeX`(p)),extrapoles,xx)));
attempt['AddFeedback',
cat(
sprintf(__("Your answer has poles in the following place(s): <latex>%s</latex>"),polestring),
"<br>",
__("There should not be poles at any of these values, so you must have found the wrong general form for the partial fraction decomposition."))
];
return([0,attempt['Feedback'],attempt['AnswerNote']]);
fi;
if missingpoles <> {} then
attempt['AddAnswerNote',__("Missing poles")];
polestring :=
`Util/CommaJoin`(op(map((p,v) -> sprintf(" $%A=%s$",v,`aim/LaTeX`(p)),t['Poles'],xx)));
attempt['AddFeedback',
sprintf(__("Your answer is missing some terms. You have poles in the following place(s): <latex>%s</latex>. There are some other values of %A where you should also have poles, so you must have found the wrong general form for the partial fraction decomposition."),polestring,xx)
];
return([0,attempt['Feedback'],attempt['AnswerNote']]);
fi;
for p in Q['Poles'] do
if Q['PoleOrder',p] <> t['PoleOrder',p] then
attempt['AddAnswerNote',__("Wrong orders")];
attempt['AddFeedback',
__("Your answer has poles in the right places, but some or all of the poles have the wrong order, so you must have found the wrong general form for the partial fraction decomposition.")
];
return([0,attempt['Feedback'],attempt['AnswerNote']]);
fi;
od;
for p in Q['Poles'] do
for i from `if`(p=infinity,0,1) to Q['PoleOrder',p] do
if Q['Coefficient',p,i] <> t['Coefficient',p,i] then
attempt['AddAnswerNote',__("Wrong coefficients")];
attempt['AddFeedback',
__("Your answer has the right general form (in particular, you have the right poles and the right orders) but some or all of the coefficients are wrong.")];
return([0,attempt['Feedback'],attempt['AnswerNote']]);
fi;
od;
od;
attempt['RawMark'] := 1;
return([1,"",""]);
end
):
EndPackage():
Index: MatrixQuestion.mpl
===================================================================
RCS file: /cvsroot/aimmath/AIM/WEB-INF/maple/aim/MatrixQuestion.mpl,v
retrieving revision 1.3
retrieving revision 1.4
diff -C2 -d -r1.3 -r1.4
*** MatrixQuestion.mpl 25 Aug 2003 21:47:19 -0000 1.3
--- MatrixQuestion.mpl 10 Oct 2003 09:49:31 -0000 1.4
***************
*** 281,285 ****
catch:
attempt['SetMarkingError',
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ))];
--- 281,285 ----
catch:
attempt['SetMarkingError',
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ))];
Index: MultiQuestion.mpl
===================================================================
RCS file: /cvsroot/aimmath/AIM/WEB-INF/maple/aim/MultiQuestion.mpl,v
retrieving revision 1.4
retrieving revision 1.5
diff -C2 -d -r1.4 -r1.5
*** MultiQuestion.mpl 1 Sep 2003 05:55:59 -0000 1.4
--- MultiQuestion.mpl 10 Oct 2003 09:49:31 -0000 1.5
***************
*** 248,252 ****
catch:
err :=
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
--- 248,252 ----
catch:
err :=
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
Index: Question.mpl
===================================================================
RCS file: /cvsroot/aimmath/AIM/WEB-INF/maple/aim/Question.mpl,v
retrieving revision 1.8
retrieving revision 1.9
diff -C2 -d -r1.8 -r1.9
*** Question.mpl 4 Oct 2003 01:21:17 -0000 1.8
--- Question.mpl 10 Oct 2003 09:49:31 -0000 1.9
***************
*** 467,471 ****
catch:
err :=
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
--- 467,471 ----
catch:
err :=
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
***************
*** 550,554 ****
else
attempt['RawMark'] := 0.;
! attempt['BasicFeedbck'] := "";
fi;
RETURN();
--- 550,554 ----
else
attempt['RawMark'] := 0.;
! attempt['BasicFeedback'] := "";
fi;
RETURN();
***************
*** 588,592 ****
catch:
err :=
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
--- 588,592 ----
catch:
err :=
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
***************
*** 658,662 ****
catch:
err :=
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
--- 658,662 ----
catch:
err :=
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
***************
*** 700,704 ****
catch:
err :=
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
--- 700,704 ----
catch:
err :=
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
***************
*** 1806,1810 ****
catch:
err :=
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
--- 1806,1810 ----
catch:
err :=
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
***************
*** 1941,1945 ****
catch:
err :=
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
--- 1941,1945 ----
catch:
err :=
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ));
Index: TextQuestion.mpl
===================================================================
RCS file: /cvsroot/aimmath/AIM/WEB-INF/maple/aim/TextQuestion.mpl,v
retrieving revision 1.8
retrieving revision 1.9
diff -C2 -d -r1.8 -r1.9
*** TextQuestion.mpl 4 Oct 2003 01:21:18 -0000 1.8
--- TextQuestion.mpl 10 Oct 2003 09:49:31 -0000 1.9
***************
*** 215,219 ****
catch:
attempt['SetMarkingError',
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ))];
--- 215,219 ----
catch:
attempt['SetMarkingError',
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ))];
***************
*** 453,457 ****
local vrsion,question,reqtype,floatok,listok,tlimit,
rawans,parsereport,
! status,ans,forbiddenwords,badwords,err,
bracketmsg,starsmsg,minusmsg,msg,t;
--- 453,457 ----
local vrsion,question,reqtype,floatok,listok,tlimit,
rawans,parsereport,
! status,val,ans,forbiddenwords,badwords,err,
bracketmsg,starsmsg,minusmsg,msg,t;
***************
*** 501,504 ****
--- 501,505 ----
parsereport := `aim/SafeParse`(rawans);
status := parsereport['Status'];
+ val := parsereport['Value'];
if (status = "Parse error") then
***************
*** 572,576 ****
try
! ans := timelimit(tlimit,eval(parsereport['Value']));
catch "time expired":
attempt['Answer'] := NULL;
--- 573,577 ----
try
! ans := timelimit(tlimit,eval(val));
catch "time expired":
attempt['Answer'] := NULL;
***************
*** 585,589 ****
attempt['SetValidationError',
! sprintf(__("Error in %s: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ))];
--- 586,590 ----
attempt['SetValidationError',
! sprintf(__("Error in %a: %s"),
lastexception[1],
StringTools[FormatMessage]( lastexception[ 2 .. -1 ] ))];
***************
*** 632,636 ****
fi;
! msg := `aim/CheckArcTrig`(parsereport['Value']);
if msg <> "" then
attempt['AddValidationNote',__("bad inverse trig")];
--- 633,637 ----
fi;
! msg := `aim/CheckArcTrig`(val);
if msg <> "" then
attempt['AddValidationNote',__("bad inverse trig")];
***************
*** 639,643 ****
fi;
! msg := `aim/CheckNames`(ans);
if msg <> "" then
attempt['AddValidationNote',__("dubious names")];
--- 640,644 ----
fi;
! msg := `aim/CheckNames`(val);
if msg <> "" then
attempt['AddValidationNote',__("dubious names")];
***************
*** 650,654 ****
fi;
! msg := `aim/CheckFunnyFunctions`(ans);
if msg <> "" then
attempt['AddValidationNote',__("funny function")];
--- 651,655 ----
fi;
! msg := `aim/CheckFunnyFunctions`(val);
if msg <> "" then
attempt['AddValidationNote',__("funny function")];
***************
*** 658,662 ****
fi;
! msg := `aim/CheckBadIndeterminates`(rawans,ans);
if msg <> "" then
attempt['AddValidationNote',__("bad indeterminates")];
--- 659,663 ----
fi;
! msg := `aim/CheckBadIndeterminates`(rawans,val);
if msg <> "" then
attempt['AddValidationNote',__("bad indeterminates")];
|