Skip to content

Commit eec929d

Browse files
authored
Merge pull request #21 from axone-protocol/security/forbid-halt
Security/forbid halt
2 parents d446d5b + 3a63e6e commit eec929d

File tree

4 files changed

+24
-20
lines changed

4 files changed

+24
-20
lines changed

README.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ The following customizations have been made to adapt the original `ichiban/prolo
4242
- Removed support for trigonometric functions (`sin`, `cos`, `tan`, `asin`, `acos`, `atan`).
4343
- Introduced VM hooks for enhanced Prolog execution control.
4444
- Added support for the `Dict` term.
45+
- `halt/0` and `halt/1` are forbidden and will throw an error.
4546

4647
## License
4748

engine/builtin.go

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1960,7 +1960,9 @@ func PeekChar(vm *VM, streamOrAlias, char Term, k Cont, env *Env) *Promise {
19601960
}
19611961
}
19621962

1963-
var osExit = os.Exit
1963+
var osExit = func(_ int) {
1964+
panic("halt/1 is not allowed")
1965+
}
19641966

19651967
// Halt exits the process with exit code of n.
19661968
func Halt(_ *VM, n Term, k Cont, env *Env) *Promise {

engine/builtin_test.go

Lines changed: 16 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,12 @@ func TestCall(t *testing.T) {
3737
vm.Register0(NewAtom("do_not_call_wrapped"), func(*VM, Cont, *Env) *Promise {
3838
panic(errors.New("told you"))
3939
})
40+
vm.Register0(NewAtom("do_not_call_exception"), func(*VM, Cont, *Env) *Promise {
41+
panic(Exception{NewAtom("error").Apply(NewAtom("panic_error").Apply(NewAtom("told you")))})
42+
})
43+
vm.Register0(NewAtom("do_not_call_misc_error"), func(*VM, Cont, *Env) *Promise {
44+
panic(42)
45+
})
4046
assert.NoError(t, vm.Compile(context.Background(), `
4147
foo.
4248
foo(_, _).
@@ -64,9 +70,11 @@ f(g([a, [b, c|X], Y{x:5}])).
6470

6571
{title: `cover all`, goal: atomComma.Apply(atomCut, NewAtom("f").Apply(NewAtom("g").Apply(List(NewAtom("a"), PartialList(NewVariable(), NewAtom("b"), NewAtom("c")), makeDict(NewAtom("foo"), NewAtom("x"), Integer(5)))))), ok: true},
6672
{title: `out of memory`, goal: NewAtom("foo").Apply(NewVariable(), NewVariable(), NewVariable(), NewVariable(), NewVariable(), NewVariable(), NewVariable(), NewVariable(), NewVariable()), err: resourceError(resourceMemory, nil), mem: 1},
67-
{title: `panic`, goal: NewAtom("do_not_call"), err: PanicError{errors.New("told you")}},
68-
{title: `panic (lazy)`, goal: NewAtom("lazy_do_not_call"), err: PanicError{errors.New("told you")}},
69-
{title: `panic (wrapped)`, goal: NewAtom("do_not_call_wrapped"), err: PanicError{errors.New("told you")}},
73+
{title: `panic`, goal: NewAtom("do_not_call"), err: Exception{NewAtom("error").Apply(NewAtom("panic_error").Apply(NewAtom("told you")))}},
74+
{title: `panic (lazy)`, goal: NewAtom("lazy_do_not_call"), err: Exception{NewAtom("error").Apply(NewAtom("panic_error").Apply(NewAtom("told you")))}},
75+
{title: `panic (wrapped)`, goal: NewAtom("do_not_call_wrapped"), err: Exception{NewAtom("error").Apply(NewAtom("panic_error").Apply(NewAtom("told you")))}},
76+
{title: `panic (exception)`, goal: NewAtom("do_not_call_exception"), err: Exception{NewAtom("error").Apply(NewAtom("panic_error").Apply(NewAtom("told you")))}},
77+
{title: `panic (misc)`, goal: NewAtom("do_not_call_misc_error"), err: Exception{NewAtom("error").Apply(NewAtom("panic_error").Apply(NewAtom("42")))}},
7078
}
7179

7280
for _, tt := range tests {
@@ -5519,20 +5527,11 @@ func TestPeekChar(t *testing.T) {
55195527

55205528
func Test_Halt(t *testing.T) {
55215529
t.Run("ok", func(t *testing.T) {
5522-
var exitCalled bool
5523-
osExit = func(code int) {
5524-
assert.Equal(t, 2, code)
5525-
exitCalled = true
5526-
}
5527-
defer func() {
5528-
osExit = os.Exit
5529-
}()
5530-
5531-
ok, err := Halt(nil, Integer(2), Success, nil).Force(context.Background())
5532-
assert.NoError(t, err)
5533-
assert.True(t, ok)
5534-
5535-
assert.True(t, exitCalled)
5530+
ok, err := Delay(func(ctx context.Context) *Promise {
5531+
return Halt(nil, Integer(2), Success, nil)
5532+
}).Force(context.Background())
5533+
assert.EqualError(t, err, "error(panic_error(halt/1 is not allowed))")
5534+
assert.False(t, ok)
55365535
})
55375536

55385537
t.Run("n is a variable", func(t *testing.T) {

engine/promise.go

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -162,10 +162,12 @@ func ensurePromise(p **Promise) {
162162

163163
func panicError(r interface{}) error {
164164
switch r := r.(type) {
165+
case Exception:
166+
return r
165167
case error:
166-
return PanicError{r}
168+
return Exception{term: atomError.Apply(NewAtom("panic_error").Apply(NewAtom(r.Error())))}
167169
default:
168-
return PanicError{fmt.Errorf("%v", r)}
170+
return Exception{term: atomError.Apply(NewAtom("panic_error").Apply(NewAtom(fmt.Sprintf("%v", r))))}
169171
}
170172
}
171173

0 commit comments

Comments
 (0)