1%-----------------------------------------------------------------------------% 2% vim: ft=prolog ts=4 sw=4 et wm=0 tw=0 3%-----------------------------------------------------------------------------% 4:- module(turing, [turing/4, 5 default_config/5]). 6:- meta_predicate turing( , , , ). 7 8:- use_module(library(lists)).
31:- multifile license:license/3. 32licencelicense(wtfpl, lgpl, 33 [ comment('Do What The Fuck You Want To Public License'), 34 url('http://www.wtfpl.net/txt/copying')]). 35:- license(wtfpl).
Rules
on TapeIn
rendering
TapeOut
. Note that turing/4 is a meta-predicate and that Parameters
and
Rules
are module-delimited as a result.
48turing(Config, Rules, TapeIn, TapeOut) :-
49 call(Config, IS, _, _, _, _),
50 perform(Config, Rules, IS, {[], TapeIn}, {Ls, Rs}),
51 reverse(Ls, Ls1),
52 append(Ls1, Rs, TapeOut).
TapeIn
and TapeOut
are divided into
pairs {Left, Right}
. The current symbol being read is the head of the
Right
side of the tape.
Note also that the output tape is built up in reverse on the left side. The
final whole tape must be built of the reversed Left
and the Right
.
70perform(Config, Rules, State, TapeIn, TapeOut) :-
71 call(Config, _, FS, RS, B, Symbols),
72 ( memberchk(State, FS) ->
73 % A stopping state has been reached.
74 TapeOut = TapeIn
75
76 ; memberchk(State, RS) ->
77 {LeftIn, RightIn} = TapeIn,
78 symbol(RightIn, Symbol, RightRem, B),
79 memberchk(Symbol, Symbols), % Is this a legal symbol?
80 once(call(Rules, State, Symbol, NewSymbol, Action, NewState)),
81 memberchk(NewSymbol, Symbols), % Is this a legal symbol?
82 action(Action, {LeftIn, [NewSymbol|RightRem]}, {LeftOut, RightOut}, B),
83 perform(Config, Rules, NewState, {LeftOut, RightOut}, TapeOut) ).
96symbol([], B, [], B). 97symbol([Sym|Rs], Sym, Rs, _).
left
), keep the tape in place (stay
), and move the tape backward
(right
).
110action(left, {Lin, Rin}, {Lout, Rout}, B) :- left(Lin, Rin, Lout, Rout, B). 111action(stay, Tape, Tape, _). 112action(right, {Lin, Rin}, {Lout, Rout}, B) :- right(Lin, Rin, Lout, Rout, B).
{Left, Right}
) had to be broken out.
127left([], Rs, [], [B|Rs], B). 128left([L|Ls], Rs, Ls, [L|Rs], _).
{Left, Right}
) had to be broken out.
142right(L, [], [B|L], [], B). 143right(L, [S|Rs], [S|L], Rs, _).
turing_test.pl
illustrates some sample turing machines and
how they are called.
Note that this is a model of how rules should be coded, not a predicate that's intended for use.
164rule(_, _, _, _, _).
Note that this is a model of how a machine configuration should be coded. It may be called, but in reality is not very useful a setup.
184default_config(IState, FStates, RStates, Blank, Symbols) :-
185 IState = q0,
186 FStates = [qf],
187 RStates = [IState],
188 Blank = b,
189 Symbols = [Blank, 0, 1]
Turing machine simulation
Simulate a universal turing machine. To define a Turing machine, the caller must supply two things: a machine configuration (c.f. default_config/5), and a set of machine rules (c.f. rules/5). The file
turing_test.pl
(the name is a joke, yes) contains two examples of Turing machines.This code is known to be compatible with SWI-Prolog and YAP Prolog. Other dialects may require alteration.