turing-0.1.1: A simple simulator for Turing machines

Safe HaskellSafe
LanguageHaskell2010

Data.Turing

Contents

Description

This module defines everything required to simulate a simple deterministic Turing machine. There are several equivalent but slightly different definitions of Turing machines in use - ours has the machine write and move in each step of execution. In addition, we allow a special movement DontMove that results in just a write operation.

You just define a transition function using suitable state and input types and run it:

>>> :{
let
    f (q, Just 0) = Just (q, Just 0, MoveRight)
    f ("even", Just 1) = Just ("odd", Just 0, MoveRight)
    f ("odd", Just 1) = Just ("even", Just 0, MoveRight)
    f _ = Nothing
    t = mkTuringMachine f "even" ["even"] -- a machine that decides parity
in run t [0, 0, 1, 1, 1]
:}
Reject

Synopsis

The Turing machine

data TuringMachine s q Source

Abstract type representing a Turing machine. It is parameterized over the alphabet and state types. A full definition contains the initial state, a list of accepting states and the transition function. Construct through mkTuringMachine.

mkTuringMachine :: TransitionFunction s q -> q -> [q] -> TuringMachine s q Source

Construct a Turing machine from the transition function, its initial state and a list of accepting states.

Associated types

data Movement Source

A Turing machine has three options of moving its read head: left, right, or no move at all.

Constructors

MoveLeft 
MoveRight 
DontMove 

type TransitionFunction s q = (q, Maybe s) -> Maybe (q, Maybe s, Movement) Source

The transition function maps the current state and tape contents to a triple describing the new state, the value to write to the tape, and a head movement. If the function is Nothing for the current state and tape contents, the machine halts.

data MachineResult Source

A machine can either accept or reject the input (for now).

Constructors

Accept 
Reject 

Running a machine

run :: Eq q => TuringMachine s q -> [s] -> MachineResult Source

Run a machine indefinitely on the given input. If it halts, it either accepts or rejects the input.

runFor :: (Integral i, Eq q) => i -> TuringMachine s q -> [s] -> Maybe MachineResult Source

Run a machine for the given number of steps. If this is enough for it to halt, the result is the same as for run, wrapped in Just; otherwise it is Nothing.