Skip to content

Commit 0e87b1e

Browse files
authored
Merge pull request #1 from axone-protocol/feat/float-as-decimal
2 parents 03d3d3d + bf4ef2a commit 0e87b1e

19 files changed

+573
-596
lines changed

engine/atom_test.go

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ func TestAtom_Compare(t *testing.T) {
5151
o int
5252
}{
5353
{title: `a > X`, a: NewAtom("a"), t: x, o: 1},
54-
{title: `a > 1.0`, a: NewAtom("a"), t: Float(1), o: 1},
54+
{title: `a > 1.0`, a: NewAtom("a"), t: NewFloatFromInt64(1), o: 1},
5555
{title: `a > 1`, a: NewAtom("a"), t: Integer(1), o: 1},
5656
{title: `a > 'Z'`, a: NewAtom("a"), t: NewAtom("Z"), o: 1},
5757
{title: `a = a`, a: NewAtom("a"), t: NewAtom("a"), o: 0},

engine/builtin_test.go

Lines changed: 25 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -399,7 +399,7 @@ func TestUnify(t *testing.T) {
399399
y: NewAtom("def"),
400400
}},
401401
{title: `'='(1, 2).`, x: Integer(1), y: Integer(2), ok: false},
402-
{title: `'='(1, 1.0).`, x: Integer(1), y: Float(1), ok: false},
402+
{title: `'='(1, 1.0).`, x: Integer(1), y: NewFloatFromInt64(1), ok: false},
403403
{title: `'='(g(X), f(f(X))).`, x: NewAtom("g").Apply(x), y: NewAtom("f").Apply(NewAtom("f").Apply(x)), ok: false},
404404
{title: `'='(f(X, 1), f(a(X))).`, x: NewAtom("f").Apply(x, Integer(1)), y: NewAtom("f").Apply(NewAtom("a").Apply(x)), ok: false},
405405
{title: `'='(f(X, Y, X), f(a(X), a(Y), Y, 2)).`, x: NewAtom("f").Apply(x, y, x), y: NewAtom("f").Apply(NewAtom("a").Apply(x), NewAtom("a").Apply(y), y, Integer(2)), ok: false},
@@ -453,7 +453,7 @@ func TestUnifyWithOccursCheck(t *testing.T) {
453453
y: NewAtom("def"),
454454
}},
455455
{title: `unify_with_occurs_check(1, 2).`, x: Integer(1), y: Integer(2), ok: false},
456-
{title: `unify_with_occurs_check(1, 1.0).`, x: Integer(1), y: Float(1), ok: false},
456+
{title: `unify_with_occurs_check(1, 1.0).`, x: Integer(1), y: NewFloatFromInt64(1), ok: false},
457457
{title: `unify_with_occurs_check(g(X), f(f(X))).`, x: NewAtom("g").Apply(x), y: NewAtom("f").Apply(NewAtom("f").Apply(x)), ok: false},
458458
{title: `unify_with_occurs_check(f(X, 1), f(a(X))).`, x: NewAtom("f").Apply(x, Integer(1)), y: NewAtom("f").Apply(NewAtom("a").Apply(x)), ok: false},
459459
{title: `unify_with_occurs_check(f(X, Y, X), f(a(X), a(Y), Y, 2)).`, x: NewAtom("f").Apply(x, y, x), y: NewAtom("f").Apply(NewAtom("a").Apply(x), NewAtom("a").Apply(y), y, Integer(2)), ok: false},
@@ -515,7 +515,7 @@ func TestTypeVar(t *testing.T) {
515515

516516
func TestTypeFloat(t *testing.T) {
517517
t.Run("float", func(t *testing.T) {
518-
ok, err := TypeFloat(nil, Float(1.0), Success, nil).Force(context.Background())
518+
ok, err := TypeFloat(nil, newFloatFromFloat64Must(1.0), Success, nil).Force(context.Background())
519519
assert.NoError(t, err)
520520
assert.True(t, ok)
521521
})
@@ -632,15 +632,15 @@ func TestFunctor(t *testing.T) {
632632
x: Integer(1),
633633
y: Integer(0),
634634
}},
635-
{title: `functor(X, 1.1, 0).`, term: x, name: Float(1.1), arity: Integer(0), ok: true, env: map[Variable]Term{
636-
x: Float(1.1),
635+
{title: `functor(X, 1.1, 0).`, term: x, name: newFloatFromFloat64Must(1.1), arity: Integer(0), ok: true, env: map[Variable]Term{
636+
x: newFloatFromFloat64Must(1.1),
637637
}},
638638
{title: `functor([_|_], '.', 2).`, term: Cons(NewVariable(), NewVariable()), name: atomDot, arity: Integer(2), ok: true},
639639
{title: `functor([], [], 0).`, term: atomEmptyList, name: atomEmptyList, arity: Integer(0), ok: true},
640640
{title: `functor(X, Y, 3).`, term: x, name: y, arity: Integer(3), err: InstantiationError(nil)},
641641
{title: `functor(X, foo, N).`, term: x, name: NewAtom("foo"), arity: n, err: InstantiationError(nil)},
642642
{title: `functor(X, foo, a).`, term: x, name: NewAtom("foo"), arity: NewAtom("a"), err: typeError(validTypeInteger, NewAtom("a"), nil)},
643-
{title: `functor(F, 1.5, 1).`, term: f, name: Float(1.5), arity: Integer(1), err: typeError(validTypeAtom, Float(1.5), nil)},
643+
{title: `functor(F, 1.5, 1).`, term: f, name: newFloatFromFloat64Must(1.5), arity: Integer(1), err: typeError(validTypeAtom, newFloatFromFloat64Must(1.5), nil)},
644644
{title: `functor(F, foo(a), 1).`, term: f, name: NewAtom("foo").Apply(NewAtom("a")), arity: Integer(1), err: typeError(validTypeAtomic, NewAtom("foo").Apply(NewAtom("a")), nil)},
645645
// {title: `current_prolog_flag(max_arity, A), X is A + 1, functor(T, foo, X).`}
646646
{title: `Minus_1 is 0 - 1, functor(F, foo, Minus_1).`, term: f, name: NewAtom("foo"), arity: Integer(-1), err: domainError(validDomainNotLessThanZero, Integer(-1), nil)},
@@ -782,7 +782,7 @@ func TestUniv(t *testing.T) {
782782
{title: "9", term: x, list: PartialList(NewAtom("bar"), NewAtom("foo")), err: typeError(validTypeList, PartialList(NewAtom("bar"), NewAtom("foo")), nil)},
783783
{title: "10", term: x, list: List(foo, NewAtom("bar")), err: InstantiationError(nil)},
784784
{title: "11", term: x, list: List(Integer(3), Integer(1)), err: typeError(validTypeAtom, Integer(3), nil)},
785-
{title: "12", term: x, list: List(Float(1.1), NewAtom("foo")), err: typeError(validTypeAtom, Float(1.1), nil)},
785+
{title: "12", term: x, list: List(newFloatFromFloat64Must(1.1), NewAtom("foo")), err: typeError(validTypeAtom, newFloatFromFloat64Must(1.1), nil)},
786786
{title: "13", term: x, list: List(NewAtom("a").Apply(NewAtom("b")), Integer(1)), err: typeError(validTypeAtom, NewAtom("a").Apply(NewAtom("b")), nil)},
787787
{title: "14", term: x, list: Integer(4), err: typeError(validTypeList, Integer(4), nil)},
788788
{title: "15", term: NewAtom("f").Apply(x), list: List(NewAtom("f"), NewAtom("u").Apply(x)), ok: true, env: map[Variable]Term{
@@ -2104,8 +2104,8 @@ func TestCompare(t *testing.T) {
21042104
order: atomLessThan,
21052105
}},
21062106
{title: `compare(<, <, <).`, order: atomLessThan, x: atomLessThan, y: atomLessThan, ok: false},
2107-
{title: `compare(1+2, 3, 3.0).`, order: atomPlus.Apply(Integer(1), Integer(2)), x: Integer(3), y: Float(3.0), ok: false, err: typeError(validTypeAtom, atomPlus.Apply(Integer(1), Integer(2)), nil)},
2108-
{title: `compare(>=, 3, 3.0).`, order: NewAtom(">="), x: Integer(3), y: Float(3.0), ok: false, err: domainError(validDomainOrder, NewAtom(">="), nil)},
2107+
{title: `compare(1+2, 3, 3.0).`, order: atomPlus.Apply(Integer(1), Integer(2)), x: Integer(3), y: newFloatFromFloat64Must(3.0), ok: false, err: typeError(validTypeAtom, atomPlus.Apply(Integer(1), Integer(2)), nil)},
2108+
{title: `compare(>=, 3, 3.0).`, order: NewAtom(">="), x: Integer(3), y: newFloatFromFloat64Must(3.0), ok: false, err: domainError(validDomainOrder, NewAtom(">="), nil)},
21092109

21102110
{title: `missing case for >`, order: atomGreaterThan, x: Integer(2), y: Integer(1), ok: true},
21112111
}
@@ -5523,7 +5523,7 @@ func TestAtomLength(t *testing.T) {
55235523
}},
55245524
{title: "atom_length('scarlet', 5).", atom: NewAtom("scarlet"), length: Integer(5), ok: false},
55255525
{title: "atom_length(Atom, 4).", atom: NewVariable(), length: Integer(4), err: InstantiationError(nil)},
5526-
{title: "atom_length(1.23, 4).", atom: Float(1.23), length: Integer(4), err: typeError(validTypeAtom, Float(1.23), nil)},
5526+
{title: "atom_length(1.23, 4).", atom: newFloatFromFloat64Must(1.23), length: Integer(4), err: typeError(validTypeAtom, newFloatFromFloat64Must(1.23), nil)},
55275527
{title: "atom_length(atom, '4').", atom: NewAtom("atom"), length: NewAtom("4"), err: typeError(validTypeInteger, NewAtom("4"), nil)},
55285528

55295529
// 8.16.1.3 Errors
@@ -5868,7 +5868,7 @@ func TestNumberChars(t *testing.T) {
58685868
t.Run("chars is a partial list", func(t *testing.T) {
58695869
chars := NewVariable()
58705870

5871-
ok, err := NumberChars(nil, Float(23.4), chars, func(env *Env) *Promise {
5871+
ok, err := NumberChars(nil, newFloatFromFloat64Must(23.4), chars, func(env *Env) *Promise {
58725872
assert.Equal(t, List(NewAtom("2"), NewAtom("3"), atomDot, NewAtom("4")), env.Resolve(chars))
58735873
return Bool(true)
58745874
}, nil).Force(context.Background())
@@ -5879,7 +5879,7 @@ func TestNumberChars(t *testing.T) {
58795879
t.Run("chars is a list with variables", func(t *testing.T) {
58805880
char := NewVariable()
58815881

5882-
ok, err := NumberChars(nil, Float(23.4), List(char, NewAtom("3"), atomDot, NewAtom("4")), func(env *Env) *Promise {
5882+
ok, err := NumberChars(nil, newFloatFromFloat64Must(23.4), List(char, NewAtom("3"), atomDot, NewAtom("4")), func(env *Env) *Promise {
58835883
assert.Equal(t, NewAtom("2"), env.Resolve(char))
58845884
return Bool(true)
58855885
}, nil).Force(context.Background())
@@ -5892,7 +5892,7 @@ func TestNumberChars(t *testing.T) {
58925892
num := NewVariable()
58935893

58945894
ok, err := NumberChars(nil, num, List(NewAtom("2"), NewAtom("3"), atomDot, NewAtom("4")), func(env *Env) *Promise {
5895-
assert.Equal(t, Float(23.4), env.Resolve(num))
5895+
assert.Equal(t, newFloatFromFloat64Must(23.4), env.Resolve(num))
58965896
return Bool(true)
58975897
}, nil).Force(context.Background())
58985898
assert.NoError(t, err)
@@ -5901,13 +5901,13 @@ func TestNumberChars(t *testing.T) {
59015901

59025902
t.Run("both provided", func(t *testing.T) {
59035903
t.Run("3.3", func(t *testing.T) {
5904-
ok, err := NumberChars(nil, Float(3.3), List(NewAtom("3"), atomDot, NewAtom("3")), Success, nil).Force(context.Background())
5904+
ok, err := NumberChars(nil, newFloatFromFloat64Must(3.3), List(NewAtom("3"), atomDot, NewAtom("3")), Success, nil).Force(context.Background())
59055905
assert.NoError(t, err)
59065906
assert.True(t, ok)
59075907
})
59085908

59095909
t.Run("3.3E+0", func(t *testing.T) {
5910-
ok, err := NumberChars(nil, Float(3.3), List(NewAtom("3"), atomDot, NewAtom("3"), NewAtom("E"), atomPlus, NewAtom("0")), Success, nil).Force(context.Background())
5910+
ok, err := NumberChars(nil, newFloatFromFloat64Must(3.3), List(NewAtom("3"), atomDot, NewAtom("3"), NewAtom("E"), atomPlus, NewAtom("0")), Success, nil).Force(context.Background())
59115911
assert.NoError(t, err)
59125912
assert.True(t, ok)
59135913
})
@@ -6017,10 +6017,10 @@ func TestNumberCodes(t *testing.T) {
60176017
l: List(Integer('3'), Integer('3')),
60186018
}},
60196019
{title: "number_codes(33, [0'3, 0'3]).", number: Integer(33), list: List(Integer('3'), Integer('3')), ok: true},
6020-
{title: "number_codes(33.0, L).", number: Float(33.0), list: l, ok: true, env: map[Variable]Term{
6020+
{title: "number_codes(33.0, L).", number: newFloatFromFloat64Must(33.0), list: l, ok: true, env: map[Variable]Term{
60216021
l: List(Integer('3'), Integer('3'), Integer('.'), Integer('0')),
60226022
}},
6023-
{title: "number_codes(33.0, [0'3, 0'., 0'3, 0'E, 0'+, 0'0, 0'1]).", number: Float(33.0), list: List(Integer('3'), Integer('.'), Integer('3'), Integer('E'), Integer('+'), Integer('0'), Integer('1')), ok: true},
6023+
{title: "number_codes(33.0, [0'3, 0'., 0'3, 0'E, 0'+, 0'0, 0'1]).", number: newFloatFromFloat64Must(33.0), list: List(Integer('3'), Integer('.'), Integer('3'), Integer('E'), Integer('+'), Integer('0'), Integer('1')), ok: true},
60246024
{title: "number_codes(A, [0'-, 0'2, 0'5]).", number: a, list: List(Integer('-'), Integer('2'), Integer('5')), ok: true, env: map[Variable]Term{
60256025
a: Integer(-25),
60266026
}},
@@ -6034,10 +6034,10 @@ func TestNumberCodes(t *testing.T) {
60346034
a: Integer('a'),
60356035
}},
60366036
{title: "number_codes(A, [0'4, 0'., 0'2]).", number: a, list: List(Integer('4'), Integer('.'), Integer('2')), ok: true, env: map[Variable]Term{
6037-
a: Float(4.2),
6037+
a: newFloatFromFloat64Must(4.2),
60386038
}},
60396039
{title: "number_codes(A, [0'4, 0'2, 0'., 0'0, 0'e, 0'-, 0'1]).", number: a, list: List(Integer('4'), Integer('2'), Integer('.'), Integer('0'), Integer('e'), Integer('-'), Integer('1')), ok: true, env: map[Variable]Term{
6040-
a: Float(4.2),
6040+
a: newFloatFromFloat64Must(4.2),
60416041
}},
60426042

60436043
// 8.16.8.3 Errors
@@ -7162,8 +7162,8 @@ func TestSucc(t *testing.T) {
71627162
})
71637163

71647164
t.Run("s is neither a variable nor an integer", func(t *testing.T) {
7165-
_, err := Succ(nil, NewVariable(), Float(1), Success, nil).Force(context.Background())
7166-
assert.Equal(t, typeError(validTypeInteger, Float(1), nil), err)
7165+
_, err := Succ(nil, NewVariable(), NewFloatFromInt64(1), Success, nil).Force(context.Background())
7166+
assert.Equal(t, typeError(validTypeInteger, NewFloatFromInt64(1), nil), err)
71677167
})
71687168
})
71697169

@@ -7185,8 +7185,8 @@ func TestSucc(t *testing.T) {
71857185
})
71867186

71877187
t.Run("s is neither a variable nor an integer", func(t *testing.T) {
7188-
_, err := Succ(nil, Integer(0), Float(1), Success, nil).Force(context.Background())
7189-
assert.Equal(t, typeError(validTypeInteger, Float(1), nil), err)
7188+
_, err := Succ(nil, Integer(0), NewFloatFromInt64(1), Success, nil).Force(context.Background())
7189+
assert.Equal(t, typeError(validTypeInteger, NewFloatFromInt64(1), nil), err)
71907190
})
71917191

71927192
t.Run("x is negative", func(t *testing.T) {
@@ -7206,8 +7206,8 @@ func TestSucc(t *testing.T) {
72067206
})
72077207

72087208
t.Run("x is neither a variable nor an integer", func(t *testing.T) {
7209-
_, err := Succ(nil, Float(0), NewVariable(), Success, nil).Force(context.Background())
7210-
assert.Equal(t, typeError(validTypeInteger, Float(0), nil), err)
7209+
_, err := Succ(nil, newFloatFromFloat64Must(0), NewVariable(), Success, nil).Force(context.Background())
7210+
assert.Equal(t, typeError(validTypeInteger, newFloatFromFloat64Must(0), nil), err)
72117211
})
72127212
}
72137213

engine/compound_test.go

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ func TestCompareCompound(t *testing.T) {
7373
o int
7474
}{
7575
{title: `f(a) > X`, x: NewAtom("f").Apply(NewAtom("a")), y: x, o: 1},
76-
{title: `f(a) > 1.0`, x: NewAtom("f").Apply(NewAtom("a")), y: Float(1), o: 1},
76+
{title: `f(a) > 1.0`, x: NewAtom("f").Apply(NewAtom("a")), y: NewFloatFromInt64(1), o: 1},
7777
{title: `f(a) > 1`, x: NewAtom("f").Apply(NewAtom("a")), y: Integer(1), o: 1},
7878
{title: `f(a) > a`, x: NewAtom("f").Apply(NewAtom("a")), y: NewAtom("a"), o: 1}, {title: `f(a) > f('Z')`, x: NewAtom("f").Apply(NewAtom("a")), y: NewAtom("f").Apply(NewAtom("Z")), o: 1},
7979
{title: `f(a) > e(a)`, x: NewAtom("f").Apply(NewAtom("a")), y: NewAtom("e").Apply(NewAtom("a")), o: 1},

engine/env.go

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -306,6 +306,16 @@ func (e *Env) unify(x, y Term, occursCheck bool) (*Env, bool) {
306306
switch y := y.(type) {
307307
case Variable:
308308
return e.unify(y, x, occursCheck)
309+
case Float:
310+
if x, ok := x.(Float); ok {
311+
return e, y.Eq(x)
312+
}
313+
return e, false
314+
case Integer:
315+
if x, ok := x.(Integer); ok {
316+
return e, y == x
317+
}
318+
return e, false
309319
default:
310320
return e, x == y
311321
}

engine/float.go

Lines changed: 101 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,30 +1,89 @@
11
package engine
22

33
import (
4+
"fmt"
5+
"github.com/cockroachdb/apd"
46
"io"
5-
"strconv"
67
"strings"
78
)
89

910
// Float is a prolog floating-point number.
10-
type Float float64
11+
// The underlying implementation is not based on floating-point, it's a [GDA](https://speleotrove.com/decimal/)
12+
// compatible implementation to avoid approximation and determinism issues.
13+
// It uses under the hood a decimal128 with 34 precision digits.
14+
type Float struct {
15+
dec *apd.Decimal
16+
}
17+
18+
// The context that must be used for operations on Float.
19+
var decimal128Ctx = apd.Context{
20+
Precision: 34,
21+
MaxExponent: 6144,
22+
MinExponent: -6143,
23+
Traps: apd.DefaultTraps,
24+
}
25+
26+
func NewFloatFromString(s string) (Float, error) {
27+
dec, c, err := decimal128Ctx.NewFromString(s)
28+
if err != nil {
29+
return Float{}, decimalConditionAsErr(c)
30+
}
31+
32+
return Float{dec: dec}, nil
33+
}
34+
35+
func NewFloatFromInt64(i int64) Float {
36+
var dec apd.Decimal
37+
dec.SetInt64(i)
38+
39+
return Float{dec: &dec}
40+
}
41+
42+
func decimalConditionAsErr(flags apd.Condition) error {
43+
e := flags & decimal128Ctx.Traps
44+
if e == 0 {
45+
return exceptionalValueUndefined
46+
}
47+
48+
for m := apd.Condition(1); m > 0; m <<= 1 {
49+
err := e & m
50+
if err == 0 {
51+
continue
52+
}
53+
54+
switch err {
55+
case apd.Overflow:
56+
return exceptionalValueFloatOverflow
57+
case apd.Underflow:
58+
return exceptionalValueUnderflow
59+
case apd.Subnormal:
60+
return exceptionalValueUnderflow
61+
case apd.DivisionByZero:
62+
return exceptionalValueZeroDivisor
63+
default:
64+
return exceptionalValueUndefined
65+
}
66+
}
67+
68+
return exceptionalValueUndefined
69+
}
1170

1271
func (f Float) number() {}
1372

1473
// WriteTerm outputs the Float to an io.Writer.
1574
func (f Float) WriteTerm(w io.Writer, opts *WriteOptions, _ *Env) error {
1675
ew := errWriter{w: w}
17-
openClose := opts.left.name == atomMinus && opts.left.specifier.class() == operatorClassPrefix && f > 0
76+
openClose := opts.left.name == atomMinus && opts.left.specifier.class() == operatorClassPrefix && !f.Negative()
1877

19-
if openClose || (f < 0 && opts.left != operator{}) {
78+
if openClose || (f.Negative() && opts.left != operator{}) {
2079
_, _ = ew.Write([]byte(" "))
2180
}
2281

2382
if openClose {
2483
_, _ = ew.Write([]byte("("))
2584
}
2685

27-
s := strconv.FormatFloat(float64(f), 'g', -1, 64)
86+
s := fmt.Sprintf("%g", f.dec)
2887
if !strings.ContainsRune(s, '.') {
2988
if strings.ContainsRune(s, 'e') {
3089
s = strings.Replace(s, "e", ".0e", 1)
@@ -51,15 +110,44 @@ func (f Float) Compare(t Term, env *Env) int {
51110
case Variable:
52111
return 1
53112
case Float:
54-
switch {
55-
case f > t:
56-
return 1
57-
case f < t:
58-
return -1
59-
default:
60-
return 0
61-
}
113+
return f.dec.Cmp(t.dec)
62114
default: // Integer, Atom, custom atomic terms, Compound.
63115
return -1
64116
}
65117
}
118+
119+
func (f Float) String() string {
120+
return fmt.Sprintf("%g", f.dec)
121+
}
122+
123+
func (f Float) Negative() bool {
124+
return f.dec.Sign() < 0
125+
}
126+
127+
func (f Float) Positive() bool {
128+
return f.dec.Sign() > 0
129+
}
130+
131+
func (f Float) Zero() bool {
132+
return f.dec.Sign() == 0
133+
}
134+
135+
func (f Float) Eq(other Float) bool {
136+
return f.dec.Cmp(other.dec) == 0
137+
}
138+
139+
func (f Float) Gt(other Float) bool {
140+
return f.dec.Cmp(other.dec) == 1
141+
}
142+
143+
func (f Float) Gte(other Float) bool {
144+
return f.dec.Cmp(other.dec) >= 0
145+
}
146+
147+
func (f Float) Lt(other Float) bool {
148+
return f.dec.Cmp(other.dec) == -1
149+
}
150+
151+
func (f Float) Lte(other Float) bool {
152+
return f.dec.Cmp(other.dec) <= 0
153+
}

0 commit comments

Comments
 (0)