Skip to content

Commit d4ffd77

Browse files
authored
Merge pull request #19 from axone-protocol/fix/dict-key-access
Fix/dict key access
2 parents 7be6699 + b1bd213 commit d4ffd77

File tree

3 files changed

+176
-18
lines changed

3 files changed

+176
-18
lines changed

engine/clause.go

Lines changed: 44 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -64,19 +64,19 @@ type clause struct {
6464
}
6565

6666
func compileClause(head Term, body Term, env *Env) (clause, error) {
67-
var c clause
68-
var goals []Term
69-
70-
head, goals = desugar(head, goals)
71-
body, goals = desugar(body, goals)
67+
head, preds := desugarHead(head, env)
68+
body = desugarBody(body, env)
7269

73-
if body != nil {
74-
goals = append(goals, body)
75-
}
76-
if len(goals) > 0 {
77-
body = seq(atomComma, goals...)
70+
if len(preds) > 0 {
71+
predSeq := seq(atomComma, preds...)
72+
if body == nil {
73+
body = predSeq
74+
} else {
75+
body = atomComma.Apply(body, predSeq)
76+
}
7877
}
7978

79+
var c clause
8080
c.compileHead(head, env)
8181

8282
if body != nil {
@@ -86,31 +86,57 @@ func compileClause(head Term, body Term, env *Env) (clause, error) {
8686
}
8787

8888
c.emit(instruction{opcode: OpExit})
89+
8990
return c, nil
9091
}
9192

92-
func desugar(term Term, acc []Term) (Term, []Term) {
93-
switch t := term.(type) {
93+
func desugarHead(head Term, env *Env) (Term, []Term) {
94+
if head, ok := env.Resolve(head).(Compound); ok {
95+
return desugarPred(head, nil, env)
96+
}
97+
return head, nil
98+
}
99+
100+
func desugarBody(body Term, env *Env) Term {
101+
if body == nil {
102+
return body
103+
}
104+
105+
var items []Term
106+
iter := seqIterator{Seq: body, Env: env}
107+
for iter.Next() {
108+
t, preds := desugarPred(iter.Current(), nil, env)
109+
if len(preds) > 0 {
110+
items = append(items, preds...)
111+
}
112+
items = append(items, t)
113+
}
114+
115+
return seq(atomComma, items...)
116+
}
117+
118+
func desugarPred(term Term, acc []Term, env *Env) (Term, []Term) {
119+
switch t := env.Resolve(term).(type) {
94120
case charList, codeList:
95121
return t, acc
96122
case list:
97123
l := make(list, len(t))
98124
for i, e := range t {
99-
l[i], acc = desugar(e, acc)
125+
l[i], acc = desugarPred(e, acc, env)
100126
}
101127
return l, acc
102128
case *partial:
103-
c, acc := desugar(t.Compound, acc)
104-
tail, acc := desugar(*t.tail, acc)
129+
c, acc := desugarPred(t.Compound, acc, env)
130+
tail, acc := desugarPred(*t.tail, acc, env)
105131
return &partial{
106132
Compound: c.(Compound),
107133
tail: &tail,
108134
}, acc
109135
case Compound:
110136
if t.Functor() == atomSpecialDot && t.Arity() == 2 {
111137
tempV := NewVariable()
112-
lhs, acc := desugar(t.Arg(0), acc)
113-
rhs, acc := desugar(t.Arg(1), acc)
138+
lhs, acc := desugarPred(t.Arg(0), acc, env)
139+
rhs, acc := desugarPred(t.Arg(1), acc, env)
114140

115141
return tempV, append(acc, atomDot.Apply(lhs, rhs, tempV))
116142
}
@@ -120,7 +146,7 @@ func desugar(term Term, acc []Term) (Term, []Term) {
120146
args: make([]Term, t.Arity()),
121147
}
122148
for i := 0; i < t.Arity(); i++ {
123-
c.args[i], acc = desugar(t.Arg(i), acc)
149+
c.args[i], acc = desugarPred(t.Arg(i), acc, env)
124150
}
125151

126152
if _, ok := t.(Dict); ok {

engine/text_test.go

Lines changed: 104 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -282,6 +282,58 @@ point(point{x: 5}.x).
282282
},
283283
},
284284
)},
285+
{title: "dict head (3)", text: `
286+
point(point{x: 5}.x) :- true.
287+
`, result: buildOrderedMap(
288+
procedurePair{
289+
Key: procedureIndicator{name: NewAtom("foo"), arity: 1},
290+
Value: &userDefined{
291+
multifile: true,
292+
clauses: clauses{
293+
{
294+
pi: procedureIndicator{name: NewAtom("foo"), arity: 1},
295+
raw: &compound{functor: NewAtom("foo"), args: []Term{NewAtom("c")}},
296+
bytecode: bytecode{
297+
{opcode: OpGetConst, operand: NewAtom("c")},
298+
{opcode: OpExit},
299+
},
300+
},
301+
},
302+
},
303+
},
304+
procedurePair{
305+
Key: procedureIndicator{name: NewAtom("point"), arity: 1},
306+
Value: &userDefined{
307+
clauses: clauses{
308+
{
309+
pi: procedureIndicator{name: NewAtom("point"), arity: 1},
310+
raw: atomIf.Apply(
311+
&compound{functor: "point", args: []Term{
312+
&compound{functor: "$dot", args: []Term{
313+
&dict{compound: compound{functor: "dict", args: []Term{NewAtom("point"), NewAtom("x"), Integer(5)}}},
314+
NewAtom("x"),
315+
}}}},
316+
NewAtom("true")),
317+
vars: []Variable{lastVariable() + 1},
318+
bytecode: bytecode{
319+
{opcode: OpGetVar, operand: Integer(0)},
320+
{opcode: OpEnter},
321+
{opcode: OpCall, operand: procedureIndicator{name: atomTrue, arity: 0}},
322+
{opcode: OpPutDict, operand: Integer(3)},
323+
{opcode: OpPutConst, operand: NewAtom("point")},
324+
{opcode: OpPutConst, operand: NewAtom("x")},
325+
{opcode: OpPutConst, operand: Integer(5)},
326+
{opcode: OpPop},
327+
{opcode: OpPutConst, operand: NewAtom("x")},
328+
{opcode: OpPutVar, operand: Integer(0)},
329+
{opcode: OpCall, operand: procedureIndicator{name: atomDot, arity: Integer(3)}},
330+
{opcode: OpExit},
331+
},
332+
},
333+
},
334+
},
335+
},
336+
)},
285337
{title: "dict body", text: `
286338
p :- foo(point{x: 5}).
287339
`, result: buildOrderedMap(
@@ -328,6 +380,58 @@ p :- foo(point{x: 5}).
328380
},
329381
},
330382
)},
383+
{title: "dict body (2)", text: `
384+
x(X) :- p(P), =(X, P.x).
385+
`, result: buildOrderedMap(
386+
procedurePair{
387+
Key: procedureIndicator{name: NewAtom("foo"), arity: 1},
388+
Value: &userDefined{
389+
multifile: true,
390+
clauses: clauses{
391+
{
392+
pi: procedureIndicator{name: NewAtom("foo"), arity: 1},
393+
raw: &compound{functor: NewAtom("foo"), args: []Term{NewAtom("c")}},
394+
bytecode: bytecode{
395+
{opcode: OpGetConst, operand: NewAtom("c")},
396+
{opcode: OpExit},
397+
},
398+
},
399+
},
400+
},
401+
},
402+
procedurePair{
403+
Key: procedureIndicator{name: NewAtom("x"), arity: 1},
404+
Value: &userDefined{
405+
clauses: clauses{
406+
{
407+
pi: procedureIndicator{name: NewAtom("x"), arity: 1},
408+
raw: atomIf.Apply(
409+
NewAtom("x").Apply(lastVariable()+1),
410+
seq(
411+
atomComma,
412+
NewAtom("p").Apply(lastVariable()+2),
413+
atomEqual.Apply(lastVariable()+1, NewAtom("$dot").Apply(lastVariable()+2, NewAtom("x"))),
414+
)),
415+
vars: []Variable{lastVariable() + 1, lastVariable() + 2, lastVariable() + 3},
416+
bytecode: bytecode{
417+
{opcode: OpGetVar, operand: Integer(0)},
418+
{opcode: OpEnter},
419+
{opcode: OpPutVar, operand: Integer(1)},
420+
{opcode: OpCall, operand: procedureIndicator{name: NewAtom("p"), arity: 1}},
421+
{opcode: OpPutVar, operand: Integer(1)},
422+
{opcode: OpPutConst, operand: NewAtom("x")},
423+
{opcode: OpPutVar, operand: Integer(2)},
424+
{opcode: OpCall, operand: procedureIndicator{name: NewAtom("."), arity: 3}},
425+
{opcode: OpPutVar, operand: Integer(0)},
426+
{opcode: OpPutVar, operand: Integer(2)},
427+
{opcode: OpCall, operand: procedureIndicator{name: NewAtom("="), arity: 2}},
428+
{opcode: OpExit},
429+
},
430+
},
431+
},
432+
},
433+
},
434+
)},
331435
{title: "dynamic", text: `
332436
:- dynamic(foo/1).
333437
foo(a).

interpreter_test.go

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1022,6 +1022,27 @@ func TestDict(t *testing.T) {
10221022
"X": "1",
10231023
}}},
10241024
},
1025+
{
1026+
program: "ok. p(point{x:1}.x) :- ok.",
1027+
query: "p(X).",
1028+
wantResult: []result{{solutions: map[string]TermString{
1029+
"X": "1",
1030+
}}},
1031+
},
1032+
{
1033+
program: "point(point{x: X}.x) :- X = 5.",
1034+
query: "point(X).",
1035+
wantResult: []result{{solutions: map[string]TermString{
1036+
"X": "5",
1037+
}}},
1038+
},
1039+
{
1040+
program: "point(point{x: 5}.X) :- X = x.",
1041+
query: "point(X).",
1042+
wantResult: []result{{solutions: map[string]TermString{
1043+
"X": "5",
1044+
}}},
1045+
},
10251046
// access
10261047
{
10271048
query: "A = point{x:1,y:2}.x.",
@@ -1055,6 +1076,13 @@ func TestDict(t *testing.T) {
10551076
"X": "10",
10561077
}}},
10571078
},
1079+
{
1080+
program: "p(P) :- P = point{x:10, y:20}. x(X) :- p(P), X = P.x.",
1081+
query: "x(X).",
1082+
wantResult: []result{{solutions: map[string]TermString{
1083+
"X": "10",
1084+
}}},
1085+
},
10581086
{
10591087
query: "A = point{x:1,y:2}.z.",
10601088
wantResult: []result{

0 commit comments

Comments
 (0)