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(5, 5, +, -).    7
    8:- use_module(library(lists)).

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.

author
- Michael T. Richter <ttmrichter@gmail.com>
version
- 1.0.0
See also
- http://en.wikipedia.org/wiki/Turing_Machine#Formal_definition /
license
- This program is free software. It comes without any warranty, to the extent permitted by applicable law. You can redistribute it and/or modify it under the terms of the Do What The Fuck You Want To Public License, Version 2, as published by Sam Hocevar. Consult http://www.wtfpl.net/txt/copying for more details.
   31:- multifile license:license/3.   32licence:license(wtfpl, lgpl,
   33                [ comment('Do What The Fuck You Want To Public License'),
   34                  url('http://www.wtfpl.net/txt/copying')]).
   35:- license(wtfpl).
 turing(+Config, +Rules, +TapeIn, -TapeOut) is semidet
Execute a Turing machine based on the provided Rules on TapeIn rendering TapeOut. Note that turing/4 is a meta-predicate and that Parameters and Rules are module-delimited as a result.
Arguments:
Config- C.f. default_config/5.
Rules- C.f. rule/5.
TapeIn- A list of symbols representing the input tape.
TapeOut- A list of symbols representing the output tape.
   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).
 perform(+Conf, +Rules, +State, +TapeIn, -TapeOut) is semidet
Performs one step of the rules on the current state according to the current machine configuration. Note that 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.

Arguments:
Conf- C.f. default_config/5.
Rules- C.f. rule/5.
State- The current state of the machine.
TapeIn- The input tape, divided into {Left, Right} sides.
TapeOut- The output tape, similarly divided.
   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) ).
 symbol(+Rin, -Symbol, -Rout, +Blank) is det
Extracts the current symbol from the right side of the input tape. Going past the right generates blank symbols. Since blank symbols are configurable, the blank symbol is passed in.
Arguments:
Rin- The right side of the tape.
Symbol- The symbol the head is over.
Rout- The right side of the tape after the symbol is removed.
Blank- The symbol used for a blank square.
   96symbol([],       B,   [], B).
   97symbol([Sym|Rs], Sym, Rs, _).
 action(+Action, +TapeIn, -TapeOut, +Blank) is semidet
Performs one of the following three legal actions: move the tape forward (left), keep the tape in place (stay), and move the tape backward (right).
Arguments:
Action- The action to perform: one of left, right, or stay.
TapeIn- The input tape, split into ={Left, Right}= components.
TapeOut- The output tape, similarly split.
Blank- The symbol to be interpreted as a blank.
  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(+Lin, +Rin, -Lout, -Rout, +Blank) is det
Helper predicate for action/4. Going past the left generates blank symbols. Because of some problems with indexing, to keep this deterministic the tape tuples ({Left, Right}) had to be broken out.
Arguments:
Lin- Left side of the tape input.
Rin- Right side of the tape input.
Lout- Left side of the tape output.
Rout- Right side of the tape output.
Blank- The configured blank character.
  127left([],     Rs, [], [B|Rs], B).
  128left([L|Ls], Rs, Ls, [L|Rs], _).
 right(+Lin, +Rin, -Lout, -Rout, +Blank) is det
Helper predicate for action/4. Going past the right generates blank symbols. Because of some problems with indexing, to keep this deterministic the tape tuples ({Left, Right}) had to be broken out.
Arguments:
Lin- Left side of the tape input.
Rin- Right side of the tape input.
Lout- Left side of the tape output.
Rout- Right side of the tape output.
Blank- The configured blank character.
  142right(L, [],     [B|L], [], B).
  143right(L, [S|Rs], [S|L], Rs, _).
 rule(+StateIn, +SymbolIn, -StateOut, -SymbolOut, -Action) is nondet
A machine is specified by a collection of rule/5 predicates using this footprint. The name of a given machine's rules is passed in to the turing/3 call. The file 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.

Arguments:
StateIn- The name of the current state of the machine.
SymbolIn- The symbol currently at the machine's head.
StateOut- The state the machine should move to after this rule is executed.
SymbolOut- The symbol that should be placed on the tape after this rule is executed.
Action- The action (right, left, stay) to be performed based on this rule
  164rule(_, _, _, _, _).
 default_config(-IState, -FStates, -RStates, -Blank, -Symbols) is det
These are the default parameters for a Turing machine used mainly as a means of demonstrating the making of a custom machine. The params call provides the legal states and symbols for use in the Turing machine. The Turing engine enforces state names and symbols as a strict subset of those provided.

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.

Arguments:
IState- The initial state of the machine when starting.
FStates- A list of the terminating states of the machine.
RStates- A list of the running states of the machine (must include the initial state).
Blank- The blank symbol.
Symbols- The complete list of legal tape symbols (must include the blank symbol).
  184default_config(IState, FStates, RStates, Blank, Symbols) :-
  185    IState  = q0,
  186    FStates = [qf],
  187    RStates = [IState],
  188    Blank   = b,
  189    Symbols = [Blank, 0, 1]