Skip to content

Commit

Permalink
add write option max_depth/1
Browse files Browse the repository at this point in the history
  • Loading branch information
ichiban committed Jul 8, 2023
1 parent c6a441e commit 50e4279
Show file tree
Hide file tree
Showing 5 changed files with 101 additions and 38 deletions.
1 change: 1 addition & 0 deletions engine/atom.go
Original file line number Diff line number Diff line change
Expand Up @@ -129,6 +129,7 @@ var (
atomLog = NewAtom("log")
atomMax = NewAtom("max")
atomMaxArity = NewAtom("max_arity")
atomMaxDepth = NewAtom("max_depth")
atomMaxInteger = NewAtom("max_integer")
atomMemory = NewAtom("memory")
atomMin = NewAtom("min")
Expand Down
75 changes: 41 additions & 34 deletions engine/builtin.go
Original file line number Diff line number Diff line change
Expand Up @@ -1505,51 +1505,48 @@ func writeTermOption(opts *WriteOptions, option Term, env *Env) error {
return domainError(validDomainWriteOption, o, env)
}

if o.Functor() == atomVariableNames {
vns, err := variableNames(o, env)
if err != nil {
return err
}
opts.variableNames = vns
return nil
}

var b bool
switch v := env.Resolve(o.Arg(0)).(type) {
case Variable:
return InstantiationError(env)
case Atom:
switch v {
case atomTrue:
b = true
case atomFalse:
b = false
default:
return domainError(validDomainWriteOption, o, env)
}
default:
return domainError(validDomainWriteOption, o, env)
}

switch o.Functor() {
case atomQuoted:
b, err := writeTermOptionBool(o, env)
opts.quoted = b
return nil
return err
case atomIgnoreOps:
b, err := writeTermOptionBool(o, env)
opts.ignoreOps = b
return nil
return err
case atomNumberVars:
b, err := writeTermOptionBool(o, env)
opts.numberVars = b
return nil
default:
return domainError(validDomainWriteOption, o, env)
return err
case atomVariableNames:
vns, err := writeTermOptionVariableNames(o, env)
opts.variableNames = vns
return err
case atomMaxDepth:
n, err := writeTermOptionInteger(o, env)
opts.maxDepth = n
return err
}
}
return domainError(validDomainWriteOption, option, env)
}

func writeTermOptionBool(o Compound, env *Env) (bool, error) {
switch v := env.Resolve(o.Arg(0)).(type) {
case Variable:
return false, InstantiationError(env)
case Atom:
switch v {
case atomTrue:
return true, nil
case atomFalse:
return false, nil
}
default:
return domainError(validDomainWriteOption, o, env)
}
return false, domainError(validDomainWriteOption, o, env)
}

func variableNames(option Compound, env *Env) (map[Variable]Atom, error) {
func writeTermOptionVariableNames(option Compound, env *Env) (map[Variable]Atom, error) {
vns := map[Variable]Atom{}
iter := ListIterator{List: option.Arg(0), Env: env}
for iter.Next() {
Expand Down Expand Up @@ -1603,6 +1600,16 @@ func variableNames(option Compound, env *Env) (map[Variable]Atom, error) {
}
}

func writeTermOptionInteger(o Compound, env *Env) (Integer, error) {
switch v := env.Resolve(o.Arg(0)).(type) {
case Variable:
return 0, InstantiationError(env)
case Integer:
return v, nil
}
return 0, domainError(validDomainWriteOption, o, env)
}

// CharCode converts a single-rune Atom char to an Integer code, or vice versa.
func CharCode(vm *VM, char, code Term, k Cont, env *Env) *Promise {
switch ch := env.Resolve(char).(type) {
Expand Down
11 changes: 11 additions & 0 deletions engine/builtin_test.go
Original file line number Diff line number Diff line change
Expand Up @@ -4045,9 +4045,20 @@ func TestWriteTerm(t *testing.T) {
))), ok: true, output: `n`},

{title: `failure`, sOrA: mw, term: NewAtom("foo"), options: List(), err: err},

{title: `write_term(S, + +1, [max_depth(2)]).`, sOrA: w, term: atomPlus.Apply(atomPlus.Apply(Integer(1))), options: List(atomMaxDepth.Apply(Integer(2))), ok: true, output: `+ + ...`},
{title: `write_term(S, 1- -, [max_depth(2)]).`, sOrA: w, term: atomMinus.Apply(atomMinus.Apply(Integer(1))), options: List(atomMaxDepth.Apply(Integer(2))), ok: true, output: `... - -`},
{title: `write_term(S, 1+2+3, [max_depth(2)]).`, sOrA: w, term: atomPlus.Apply(atomPlus.Apply(Integer(1), Integer(2)), Integer(3)), options: List(atomMaxDepth.Apply(Integer(2))), ok: true, output: `... + ... +3`},
{title: `write_term(S, [1,2,3], [max_depth(2)]).`, sOrA: w, term: List(Integer(1), Integer(2), Integer(3)), options: List(atomMaxDepth.Apply(Integer(2))), ok: true, output: `[1,2|...]`},
{title: `write_term(S, s(s(0)), [max_depth(2)]).`, sOrA: w, term: NewAtom("s").Apply(NewAtom("s").Apply(Integer(0))), options: List(atomMaxDepth.Apply(Integer(2))), ok: true, output: `s(s(...))`},
{title: `write_term(S, _, [max_depth(_)]).`, sOrA: w, term: NewVariable(), options: List(atomMaxDepth.Apply(NewVariable())), err: InstantiationError(nil)},
{title: `write_term(S, _, [max_depth(foo)]).`, sOrA: w, term: NewVariable(), options: List(atomMaxDepth.Apply(NewAtom("foo"))), err: domainError(validDomainWriteOption, atomMaxDepth.Apply(NewAtom("foo")), nil)},
}

var vm VM
vm.operators.define(500, operatorSpecifierYFX, atomPlus)
vm.operators.define(200, operatorSpecifierFY, atomPlus)
vm.operators.define(200, operatorSpecifierYF, atomMinus)
for _, tt := range tests {
t.Run(tt.title, func(t *testing.T) {
buf.Reset()
Expand Down
51 changes: 47 additions & 4 deletions engine/compound.go
Original file line number Diff line number Diff line change
Expand Up @@ -80,6 +80,12 @@ func writeCompoundList(w io.Writer, c Compound, opts *WriteOptions, env *Env) er
_ = c.Arg(0).WriteTerm(&ew, opts, env)
iter := ListIterator{List: c.Arg(1), Env: env}
for iter.Next() {
opts.maxDepth--
if opts.maxDepth == 0 {
_, _ = fmt.Fprint(&ew, "|")
_ = atomElipsis.WriteTerm(&ew, opts, nil)
break
}
_, _ = fmt.Fprint(&ew, ",")
_ = iter.Current().WriteTerm(&ew, opts, env)
}
Expand Down Expand Up @@ -143,7 +149,15 @@ func writeCompoundOpPrefix(w io.Writer, c Compound, opts *WriteOptions, env *Env
opts = opts.withLeft(operator{}).withRight(operator{})
}
_ = c.Functor().WriteTerm(&ew, opts.withLeft(operator{}).withRight(operator{}), env)
_ = c.Arg(0).WriteTerm(&ew, opts.withPriority(r).withLeft(*op), env)
{
opts := opts.withPriority(r).withLeft(*op)
opts.maxDepth--
if opts.maxDepth == 0 {
_ = atomElipsis.WriteTerm(&ew, opts, env)
} else {
_ = c.Arg(0).WriteTerm(&ew, opts, env)
}
}
if openClose {
_, _ = fmt.Fprint(&ew, ")")
}
Expand All @@ -162,7 +176,15 @@ func writeCompoundOpPostfix(w io.Writer, c Compound, opts *WriteOptions, env *En
_, _ = fmt.Fprint(&ew, "(")
opts = opts.withLeft(operator{}).withRight(operator{})
}
_ = c.Arg(0).WriteTerm(&ew, opts.withPriority(l).withRight(*op), env)
{
opts := opts.withPriority(l).withRight(*op)
opts.maxDepth--
if opts.maxDepth == 0 {
_ = atomElipsis.WriteTerm(&ew, opts, env)
} else {
_ = c.Arg(0).WriteTerm(&ew, opts, env)
}
}
_ = c.Functor().WriteTerm(&ew, opts.withLeft(operator{}).withRight(operator{}), env)
if openClose {
_, _ = fmt.Fprint(&ew, ")")
Expand All @@ -186,14 +208,30 @@ func writeCompoundOpInfix(w io.Writer, c Compound, opts *WriteOptions, env *Env,
_, _ = fmt.Fprint(&ew, "(")
opts = opts.withLeft(operator{}).withRight(operator{})
}
_ = c.Arg(0).WriteTerm(&ew, opts.withPriority(l).withRight(*op), env)
{
opts := opts.withPriority(l).withRight(*op)
opts.maxDepth--
if opts.maxDepth == 0 {
_ = atomElipsis.WriteTerm(&ew, opts, env)
} else {
_ = c.Arg(0).WriteTerm(&ew, opts, env)
}
}
switch c.Functor() {
case atomComma, atomBar:
_, _ = fmt.Fprint(&ew, c.Functor().String())
default:
_ = c.Functor().WriteTerm(&ew, opts.withLeft(operator{}).withRight(operator{}), env)
}
_ = c.Arg(1).WriteTerm(&ew, opts.withPriority(r).withLeft(*op), env)
{
opts := opts.withPriority(r).withLeft(*op)
opts.maxDepth--
if opts.maxDepth == 0 {
_ = atomElipsis.WriteTerm(&ew, opts, env)
} else {
_ = c.Arg(1).WriteTerm(&ew, opts, env)
}
}
if openClose {
_, _ = fmt.Fprint(&ew, ")")
}
Expand All @@ -206,10 +244,15 @@ func writeCompoundFunctionalNotation(w io.Writer, c Compound, opts *WriteOptions
_ = c.Functor().WriteTerm(&ew, opts, env)
_, _ = fmt.Fprint(&ew, "(")
opts = opts.withLeft(operator{}).withPriority(999)
opts.maxDepth--
for i := 0; i < c.Arity(); i++ {
if i != 0 {
_, _ = fmt.Fprint(&ew, ",")
}
if opts.maxDepth == 0 {
_ = atomElipsis.WriteTerm(&ew, opts, env)
continue
}
_ = c.Arg(i).WriteTerm(&ew, opts, env)
}
_, _ = fmt.Fprint(&ew, ")")
Expand Down
1 change: 1 addition & 0 deletions engine/term.go
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ type WriteOptions struct {
visited map[termID]struct{}
prefixMinus bool
left, right operator
maxDepth Integer
}

func (o WriteOptions) withQuoted(quoted bool) *WriteOptions {
Expand Down

0 comments on commit 50e4279

Please sign in to comment.