Skip to content

Commit

Permalink
Merge pull request #174 from ichiban/nth0
Browse files Browse the repository at this point in the history
add nth0/3 and rename nth/3 -> nth1/3
  • Loading branch information
ichiban authored Mar 19, 2022
2 parents 830c647 + 2d0ae53 commit 08fb802
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 5 deletions.
3 changes: 2 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -224,7 +224,8 @@ for sols.Next() {
| List Processing | `append(List1, List2, List3)` | | Succeeds if `List3` is the concatination of `List1` and `List2`. | Prolog |
| | `member(Elem, List)` | | Succeeds if `Elem` is a member of `List`. | Prolog |
| | `length(List, Length)` | | Succeeds if `Length` is the length of `List`. | Prolog |
| | `nth(N, List, Elem)` | | Succeeds if `Elem` is the `N`-th element of `List`. | Prolog |
| | `nth0(N, List, Elem)` | | Succeeds if `Elem` is the `N`-th element of `List`, counting from 0. | Prolog |
| | `nth1(N, List, Elem)` | | Succeeds if `Elem` is the `N`-th element of `List`, counting from 1. | Prolog |
| Term Expansion | `expand_term(In, Out)` | | Unifies `Out` with an expanded term for `In`. | [Go](https://pkg.go.dev/github.com/ichiban/prolog/engine#State.ExpandTerm) |
| Environment Variable | `environ(Key, Value)` | | Succeeds if an environment variable `Key` has a value `Value`. | [Go](https://pkg.go.dev/github.com/ichiban/prolog/engine#Environ) |
| DCG | `phrase(GRBody, S0, S)` | | Succeeds if a different list `S0-S` satisfies the grammar rule `GRBody`. | Go |
Expand Down
15 changes: 11 additions & 4 deletions bootstrap.pl
Original file line number Diff line number Diff line change
Expand Up @@ -238,12 +238,19 @@
length([], 0).
length([_|Xs], N) :- length(Xs, L), N is L + 1.

:- built_in(nth/3).
nth(1, [Elem|_], Elem) :- !.
nth(N, [_|Rest], Elem) :-
:- built_in(nth0/3).
nth0(0, [Elem|_], Elem) :- !.
nth0(N, [_|Rest], Elem) :-
N > 0,
M is N - 1,
nth0(M, Rest, Elem).

:- built_in(nth1/3).
nth1(1, [Elem|_], Elem) :- !.
nth1(N, [_|Rest], Elem) :-
N > 1,
M is N - 1,
nth(M, Rest, Elem).
nth1(M, Rest, Elem).

:- built_in(maplist/2).
maplist(_Cont, []).
Expand Down

0 comments on commit 08fb802

Please sign in to comment.