Skip to content

Commit 6b77ef9

Browse files
committed
fix: avoid nil pointer reference on WriteOptions operators
1 parent cfc8a8b commit 6b77ef9

File tree

6 files changed

+28
-21
lines changed

6 files changed

+28
-21
lines changed

engine/atom.go

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -241,7 +241,7 @@ func NewAtom(name string) Atom {
241241
// WriteTerm outputs the Atom to an io.Writer.
242242
func (a Atom) WriteTerm(w io.Writer, opts *WriteOptions, _ *Env) error {
243243
ew := errWriter{w: w}
244-
openClose := (opts.left != (operator{}) || opts.right != (operator{})) && opts.ops.defined(a)
244+
openClose := (opts.left != (operator{}) || opts.right != (operator{})) && opts.getOps().defined(a)
245245

246246
if openClose {
247247
if opts.left.name != 0 && opts.left.specifier.class() == operatorClassPrefix {

engine/atom_test.go

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,8 +24,8 @@ func TestAtom_WriteTerm(t *testing.T) {
2424
{name: `{}`, opts: WriteOptions{quoted: false}, output: `{}`},
2525
{name: `{}`, opts: WriteOptions{quoted: true}, output: `{}`},
2626
{name: `-`, output: `-`},
27-
{name: `-`, opts: WriteOptions{ops: &operators{OrderedMap: orderedmap.New[Atom, [_operatorClassLen]operator](orderedmap.WithInitialData(orderedmap.Pair[Atom, [_operatorClassLen]operator]{Key: atomPlus, Value: [3]operator{}}, orderedmap.Pair[Atom, [_operatorClassLen]operator]{Key: atomMinus, Value: [3]operator{}}))}, left: operator{specifier: operatorSpecifierFY, name: atomPlus}}, output: ` (-)`},
28-
{name: `-`, opts: WriteOptions{ops: &operators{OrderedMap: orderedmap.New[Atom, [_operatorClassLen]operator](orderedmap.WithInitialData(orderedmap.Pair[Atom, [_operatorClassLen]operator]{Key: atomPlus, Value: [3]operator{}}, orderedmap.Pair[Atom, [_operatorClassLen]operator]{Key: atomMinus, Value: [3]operator{}}))}, right: operator{name: atomPlus}}, output: `(-)`},
27+
{name: `-`, opts: WriteOptions{_ops: &operators{OrderedMap: orderedmap.New[Atom, [_operatorClassLen]operator](orderedmap.WithInitialData(orderedmap.Pair[Atom, [_operatorClassLen]operator]{Key: atomPlus, Value: [3]operator{}}, orderedmap.Pair[Atom, [_operatorClassLen]operator]{Key: atomMinus, Value: [3]operator{}}))}, left: operator{specifier: operatorSpecifierFY, name: atomPlus}}, output: ` (-)`},
28+
{name: `-`, opts: WriteOptions{_ops: &operators{OrderedMap: orderedmap.New[Atom, [_operatorClassLen]operator](orderedmap.WithInitialData(orderedmap.Pair[Atom, [_operatorClassLen]operator]{Key: atomPlus, Value: [3]operator{}}, orderedmap.Pair[Atom, [_operatorClassLen]operator]{Key: atomMinus, Value: [3]operator{}}))}, right: operator{name: atomPlus}}, output: `(-)`},
2929
{name: `X`, opts: WriteOptions{quoted: true, left: operator{name: NewAtom(`F`)}}, output: ` 'X'`}, // So that it won't be 'F''X'.
3030
{name: `X`, opts: WriteOptions{quoted: true, right: operator{name: NewAtom(`F`)}}, output: `'X' `}, // So that it won't be 'X''F'.
3131
{name: `foo`, opts: WriteOptions{left: operator{name: NewAtom(`bar`)}}, output: ` foo`}, // So that it won't be barfoo.

engine/builtin.go

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1463,7 +1463,7 @@ func WriteTerm(vm *VM, streamOrAlias, t, options Term, k Cont, env *Env) *Promis
14631463
}
14641464

14651465
opts := WriteOptions{
1466-
ops: vm.getOperators(),
1466+
_ops: vm.getOperators(),
14671467
priority: 1200,
14681468
}
14691469
iter := ListIterator{List: options, Env: env}

engine/compound.go

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ func WriteCompound(w io.Writer, c Compound, opts *WriteOptions, env *Env) error
4545
return writeCompoundFunctionalNotation(w, c, opts, env)
4646
}
4747

48-
if ops, ok := opts.ops.Get(c.Functor()); ok {
48+
if ops, ok := opts.getOps().Get(c.Functor()); ok {
4949
for _, o := range ops {
5050
if o.specifier.arity() == c.Arity() {
5151
return writeCompoundOp(w, c, opts, env, &o)

engine/compound_test.go

Lines changed: 14 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -37,20 +37,20 @@ func TestWriteCompound(t *testing.T) {
3737
{title: "list-ish", term: PartialList(NewAtom(`rest`), NewAtom(`a`), NewAtom(`b`)), output: `[a,b|rest]`},
3838
{title: "circular list", term: l, output: `[a,b,a|...]`},
3939
{title: "curly brackets", term: atomEmptyBlock.Apply(NewAtom(`foo`)), output: `{foo}`},
40-
{title: "fx", term: atomIf.Apply(atomIf.Apply(NewAtom(`foo`))), opts: WriteOptions{ops: ops, priority: 1201}, output: `:- (:-foo)`},
41-
{title: "fy", term: atomNegation.Apply(atomMinus.Apply(atomNegation.Apply(NewAtom(`foo`)))), opts: WriteOptions{ops: ops, priority: 1201}, output: `\+ - (\+foo)`},
42-
{title: "xf", term: NewAtom(`-:`).Apply(NewAtom(`-:`).Apply(NewAtom(`foo`))), opts: WriteOptions{ops: ops, priority: 1201}, output: `(foo-:)-:`},
43-
{title: "yf", term: NewAtom(`+/`).Apply(NewAtom(`--`).Apply(NewAtom(`+/`).Apply(NewAtom(`foo`)))), opts: WriteOptions{ops: ops, priority: 1201}, output: `(foo+/)-- +/`},
44-
{title: "xfx", term: atomIf.Apply(NewAtom("foo"), atomIf.Apply(NewAtom("bar"), NewAtom("baz"))), opts: WriteOptions{ops: ops, priority: 1201}, output: `foo:-(bar:-baz)`},
45-
{title: "yfx", term: atomAsterisk.Apply(Integer(2), atomPlus.Apply(Integer(2), Integer(2))), opts: WriteOptions{ops: ops, priority: 1201}, output: `2*(2+2)`},
46-
{title: "xfy", term: atomComma.Apply(Integer(2), atomBar.Apply(Integer(2), Integer(2))), opts: WriteOptions{ops: ops, priority: 1201}, output: `2,(2|2)`},
47-
{title: "ignore_ops(false)", term: atomPlus.Apply(Integer(2), Integer(-2)), opts: WriteOptions{ignoreOps: false, ops: ops, priority: 1201}, output: `2+ -2`},
48-
{title: "ignore_ops(true)", term: atomPlus.Apply(Integer(2), Integer(-2)), opts: WriteOptions{ignoreOps: true, ops: ops, priority: 1201}, output: `+(2,-2)`},
49-
{title: "number_vars(false)", term: f.Apply(atomVar.Apply(Integer(0)), atomVar.Apply(Integer(1)), atomVar.Apply(Integer(25)), atomVar.Apply(Integer(26)), atomVar.Apply(Integer(27))), opts: WriteOptions{quoted: true, numberVars: false, ops: ops, priority: 1201}, output: `f('$VAR'(0),'$VAR'(1),'$VAR'(25),'$VAR'(26),'$VAR'(27))`},
50-
{title: "number_vars(true)", term: f.Apply(atomVar.Apply(Integer(0)), atomVar.Apply(Integer(1)), atomVar.Apply(Integer(25)), atomVar.Apply(Integer(26)), atomVar.Apply(Integer(27))), opts: WriteOptions{quoted: true, numberVars: true, ops: ops, priority: 1201}, output: `f(A,B,Z,A1,B1)`},
51-
{title: "prefix: spacing between operators", term: atomAsterisk.Apply(NewAtom("a"), atomMinus.Apply(NewAtom("b"))), opts: WriteOptions{ops: ops, priority: 1201}, output: `a* -b`},
52-
{title: "postfix: spacing between unary minus and open/close", term: atomMinus.Apply(NewAtom(`+/`).Apply(NewAtom("a"))), opts: WriteOptions{ops: ops, priority: 1201}, output: `- (a+/)`},
53-
{title: "infix: spacing between unary minus and open/close", term: atomMinus.Apply(atomAsterisk.Apply(NewAtom("a"), NewAtom("b"))), opts: WriteOptions{ops: ops, priority: 1201}, output: `- (a*b)`},
40+
{title: "fx", term: atomIf.Apply(atomIf.Apply(NewAtom(`foo`))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `:- (:-foo)`},
41+
{title: "fy", term: atomNegation.Apply(atomMinus.Apply(atomNegation.Apply(NewAtom(`foo`)))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `\+ - (\+foo)`},
42+
{title: "xf", term: NewAtom(`-:`).Apply(NewAtom(`-:`).Apply(NewAtom(`foo`))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `(foo-:)-:`},
43+
{title: "yf", term: NewAtom(`+/`).Apply(NewAtom(`--`).Apply(NewAtom(`+/`).Apply(NewAtom(`foo`)))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `(foo+/)-- +/`},
44+
{title: "xfx", term: atomIf.Apply(NewAtom("foo"), atomIf.Apply(NewAtom("bar"), NewAtom("baz"))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `foo:-(bar:-baz)`},
45+
{title: "yfx", term: atomAsterisk.Apply(Integer(2), atomPlus.Apply(Integer(2), Integer(2))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `2*(2+2)`},
46+
{title: "xfy", term: atomComma.Apply(Integer(2), atomBar.Apply(Integer(2), Integer(2))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `2,(2|2)`},
47+
{title: "ignore_ops(false)", term: atomPlus.Apply(Integer(2), Integer(-2)), opts: WriteOptions{ignoreOps: false, _ops: ops, priority: 1201}, output: `2+ -2`},
48+
{title: "ignore_ops(true)", term: atomPlus.Apply(Integer(2), Integer(-2)), opts: WriteOptions{ignoreOps: true, _ops: ops, priority: 1201}, output: `+(2,-2)`},
49+
{title: "number_vars(false)", term: f.Apply(atomVar.Apply(Integer(0)), atomVar.Apply(Integer(1)), atomVar.Apply(Integer(25)), atomVar.Apply(Integer(26)), atomVar.Apply(Integer(27))), opts: WriteOptions{quoted: true, numberVars: false, _ops: ops, priority: 1201}, output: `f('$VAR'(0),'$VAR'(1),'$VAR'(25),'$VAR'(26),'$VAR'(27))`},
50+
{title: "number_vars(true)", term: f.Apply(atomVar.Apply(Integer(0)), atomVar.Apply(Integer(1)), atomVar.Apply(Integer(25)), atomVar.Apply(Integer(26)), atomVar.Apply(Integer(27))), opts: WriteOptions{quoted: true, numberVars: true, _ops: ops, priority: 1201}, output: `f(A,B,Z,A1,B1)`},
51+
{title: "prefix: spacing between operators", term: atomAsterisk.Apply(NewAtom("a"), atomMinus.Apply(NewAtom("b"))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `a* -b`},
52+
{title: "postfix: spacing between unary minus and open/close", term: atomMinus.Apply(NewAtom(`+/`).Apply(NewAtom("a"))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `- (a+/)`},
53+
{title: "infix: spacing between unary minus and open/close", term: atomMinus.Apply(atomAsterisk.Apply(NewAtom("a"), NewAtom("b"))), opts: WriteOptions{_ops: ops, priority: 1201}, output: `- (a*b)`},
5454
{title: "recursive", term: r, output: `f(...)`},
5555
}
5656

engine/term.go

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ type WriteOptions struct {
2020
variableNames map[Variable]Atom
2121
numberVars bool
2222

23-
ops *operators
23+
_ops *operators
2424
priority Integer
2525
visited map[termID]struct{}
2626
prefixMinus bool
@@ -58,8 +58,15 @@ func (o WriteOptions) withRight(op operator) *WriteOptions {
5858
return &o
5959
}
6060

61+
func (o WriteOptions) getOps() *operators {
62+
if o._ops == nil {
63+
o._ops = newOperators()
64+
}
65+
return o._ops
66+
}
67+
6168
var defaultWriteOptions = WriteOptions{
62-
ops: &operators{
69+
_ops: &operators{
6370
OrderedMap: orderedmap.New[Atom, [_operatorClassLen]operator](
6471
orderedmap.WithInitialData(
6572
orderedmap.Pair[Atom, [_operatorClassLen]operator]{

0 commit comments

Comments
 (0)