Turing machine

From HaskellWiki
Revision as of 02:01, 30 May 2006 by EndreyMark (talk | contribs) (In →‎Tagging structure: section: format the word CPS as a link to the Continuation page)
Jump to navigation Jump to search

Introduction

An article on Turing machines, maybe growing to a project to specify (and implement) a general purpose (toy or educational) programming language, that can describe each concrete Turing machine directly: a Turing machine definition language.

This article wants also to show an example how Haskell (and in general: functional programming) can have an impact on or suggest ideas even in (seemingly) entirely distant, remote areas.

The impact of Haskell to this Turing machine definition language is more than simply using Haskell as an implementation language for this project. The very syntax of this Turing machine definition language (and its main feature, its tagging structure) comes directly from functional programming languages (Haskell and combinatory logic).

Links

Implementations

Variants

There are several variants of defining the concept of a Turing machine. These variants can be classified across several aspects. I shall classify possible variants in terms of two questions:

  • how the machine behaves at transitions
  • how the the running of the machine terminates

A classifying aspect

Transition

I make a distinction between sum-like and product-like transition behavior:

product-like transition
means that the head moves and writes at each transition (this may have a funny consequence: sometimes, we have to undo the last moving step of the head at the end of running -- i.e. there may remain a superfluous last moving that has to be undone). Maybe that is why some of these variants extend the moving possibilities: besides left, right there is also an idle move.
sum-like transition
means that the head moves or writes at each transition (never both). [Mon:MathLog] describes this approach. I like this approach better, because it looks more economical conceptually (we do not have to undo any superfluous final movings, nor do we need to introduce idle moves) and because it looks nicer for me even conceptually.

Halting

Halting can be done in several ways -- a (second) special state (final state), or a special action (termination action) etc... Here, I avoid the concept of halting state. The only special state is the starting state, but I do not overload the concept of state in any other way -- halting is achieved in another way

A construct called Maybe2

Sum-like transition and avoiding the concept halting state -- they look like two independent, orthogonal aspects. But a construct (called Maybe2 in a -- maybe deprecated -- Hugs library module) can implement both aspect in one construct.

 data Maybe2 a b = Nothing2 | Just2 a b

Programming guidelines page recommends to avoid using this construct, and suggests modularizing it to Maybe (a, b). But here I prefer using Maybe2, because at this particular problem (defining Turing definition language) this deconstruction pattern does not appear in any other situations, so no redundance is caused by the use of Maybe2. And, to tell the truth, I like this construct.

Moves

There are variants of the Turing machine concept also across other problems, e.g. how the head and the tape moves related from each other: which is regarded as moving, which is immobile.

Using the facts that

  • the head is
    • finite (even if the states are included)
    • and even limited, even constant (having fixed a concrete Turing machine): it does not grow during a run
  • the tape is infinite, or (in some approaches to Turing machine concept) finite but unlimited, maintaining dynamically its appropriate size

I prefer a convention taken from a physical view: I regard the head as being mobile even if it is made from the heaviest transuranium metal or a black hole, and tape being (or growing) immobile even if it is made of the finest membrane.


Turing machine definition language as a programming language

I use term Turing machine definition language for what we generally mean when talking on the language of Turing simulator softwares: a language which can represent infinite -- even all possible -- concrete Turing machines, so it is able to serve as an (of course Turing complete, in the most literal meaning) programming language

Syntax

I was dreaming of a syntax reflecting the conceptual structure of the main concepts -- maybe reflecting even the logic of the Haskell implementation! In generally, I do not like special names (like start is for starting state, everything else...) -- I like the concept of tags much better -- I mean the concept of tags as shown in classical examples -- e.g. direct sum or Maybe.

Verbose syntax

Example

Incrementing a number represented in the tally (in other words, unary) notation:

starting : blank : Move right WITH starting;
starting : Letter 1 : Write Letter 1 WITH Becoming processing;
Becoming processing : blank  : Write Letter 1 WITH Becoming extended;
Becoming processing : Letter 1 : Move right WITH Becoming processing;
Becoming extended : blank : stop;
Becoming extended : Letter 1 : stop;

Tagging structure

As we can see, this Turing machine definition language has an algebraically motivated tagging structure. I have taken the idea from Haskell's sum-like datatypes (Maybe, Maybe2, Either) and from the continuation-passing-style implementation of sum-like datatypes (direct sum and Maybe) in Combinatory logic (see also Unlambda's union type).

This tagging structure makes such programs (i.e Turing machine definitions) more readable, that make use of different namespaces for symbols and states.

As symbols and states are different concept, most Turing machine definition languages allow us to use the same symbol for a state and a symbol -- they are simply in different namespaces. This is a natural consequence of the essential concept of Turing machine. [Mon:MathLog] leverages namespaces in an extreme way: everything -- states, symbols, even actions -- are coded as natural numbers.

The tagging structure enables us also to define the set of states and symbols in an easy way: no burnt-in presupposition is required (e.g. restricting the set of symbols for characters). Special keyword for declaring sets of states and sets of symbols are also superfluous.

Algebraic background of the tagging structure

Keywords can be classified according their corresponding type and tag coordinates, and coloring scheme can reflect this.

Types (represented with colors)
Special keywords
are common in all Turing machines. They are colored.
user-given names
are specific for a concrete Turing machine. They are colorless, more exactly, black in case of light background, and white in case of dark background.
States, symbols

States and symbols are rather different concepts in the theory of Turing machines, but they both have (maybe incidentally) a common feature. It is worth of distinguishing a special state (the starting state) -- and the same is true at symbols (blank symbol). This has a consequence: the tagging structure is the same for these two rather different concepts, and this common tagging structure can be covered by Maybe.

Tag Maybe-like
Just Nothing
Concept (type) Symbol Letter blank
State Becoming starting
Result of transition

Representation of halting, and in non-halting cases maintaining new state and action -- this has also a tagging structure. It is Maybe2.

Tag Maybe2-like
Just2 Nothing2
Concept (type) Result of transition WITH stop
Arity (represented with font)

The keywords have different arities, and it can be represented with syntax highlighting (by mapping a font type to each arity). But also pure ASCII text can contain this information by appropriate capitalization rules.

Constant keywords
are either Nothing-like things for special cases (symbol blank, state starting), the Nothing2-like solution for halting (stop), or direction constants like left, right, or user-named things (state or symbol names, varying in each concrete Turing machine). They are typeset with normal font, and it is recommended to type them without any capitals (of course, user-given state and symbol names can ignore this, because state and symbol names are part of the specific Turing machine, so the Turing machine definition language does not restrict their use).
Unary keywords
are one-parameter commands like Write, Move, or one-parameter state/symbol constructors like Becoming, Letter. They are typeset with italic, and just the beginning letter is capitalized.
Binary keywords
like WITH, but considering the idea of currying, the colon sign : is also typeset the same way: they are typeset with bold, and they are either typed with all capitals (WITH), or they consist of a symbol (:)

Concise syntax

Example
0 : _ : -> / 0
0 : '1 : !'1 / @processing
@processing : _ : !'1 / @extended
@processing : '1 : -> / @processing
@extended : _ : .
@extended : '1 : .
Motivation of signs
  • 0 signing starting state comes from David S. Woodruff's Turing machine interpreter TM
  • Exclamation mark signing the concept of writing comes from the Z model-based formal specification language, where exclamation mark is used to mark output variables
  • Repeated colons signing compound cases come from the concept of currying.
  • At-character signing state comes from its literal meaning in natural languages (in everyday English language, as a preposition for expressing being at places times or states) -- also reflected in its use in e-mail addresses
  • Apostrophe signing a (non-blank) letter comes from using apostrophes in programming languages for character literals and from using apostrophes (or upper corners) for quotations in mathematical logic
  • Slash-character signing the concept of compound action (allowing the possibility of halting instead) comes from the theory of automata
  • Dot signing termination is hard to explain. In Prolog, dot is a terminating symbol, but in another sense: it terminates syntactical units (rules and facts), not processes!

Implementation

Representations of main concepts

Language
 module Language where

 import Util (Maybe2 (Nothing2, Just2))

 type Turing becoming letter = UnsafeTuring (Maybe becoming) (Maybe letter)
 type UnsafeTuring state symbol = state -> symbol -> Maybe2 (Action symbol) state
 data Action symbol = Write symbol | Move Bool
Observable non-emptiness: special state, special symbol

Most conceptual frameworks of Turing machine concept allow us a big liberty at choosing the set of states and symbols -- but empty set is not allowed. Of course Haskell types are never empty, but non-emptiness provided by undefined is not enough. We need discernible, observable non-emptiness. This restriction is reflected directly in the representation of language concepts: we require the presence of a special symbol and a special state.

The trick of Turing versus UnsafeTuring distinction with Maybe solves the problem of special state and symbol. Special symbol is called blank and special state is called starting. The presence of special symbol, special state is reflected directly in the representation of language concepts -- and both are represented by Nothing.

This way allows us a big liberty at choosing the set of states and symbols -- we do not have to restrict the user's freedom to use any types for both symbols and states. Strings, integers, enumerations, characters, booleans...

Halting

Another -- maybe analogous -- problem is the representation of halting. There may be alternative solutions: introduction of concepts like halting state or halting action, etc... I felt that Maybe2 (Hugs has this data type in a library module) is a conceptually esthetic solution.

Tape

At first I wrote a circular program to make double linked list to implement a Bi-directionally infinite tape. It is superfluous, there is a more simple solution:

 module Tape where

 import Util (Stream (Cons))

 data Tape a = Tp {left, right :: Stream a, cell :: a}
 move :: Bool -> Tape a -> Tape a
 put :: a -> Tape a -> Tape a
 get :: Tape a -> a

...

Utility module
 module Util where

 data Maybe2 a b = Nothing2 | Just2 a b
 data Stream a = Cons a (Stream a)

Extending language

A pattern language, or some other extending possibilities, to avoid redundancies. Maybe a macro language as at David S. Woodruff's Turing machine interpreter TM. Other syntactic sugar.

Bibliography

[Mon:MathLog]
Monk, J. Donald: Mathematical Logic. Springer-Verlag, New York * Heidelberg * Berlin, 1976.