turingMachine-1.0.0.0: An implementation of Turing Machine and Automaton

Copyright(c) Jorge Santiago Alvarez Cuadros 2016
LicenseGPL-3
Maintainersanjorgek@ciencias.unam.mx
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • GADTs
  • GADTSyntax
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • ExistentialQuantification
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll

Math.Model.Turing

Description

Turing machine abstaction

Documentation

class Ways a where Source #

Minimal complete definition

oposite

Methods

oposite :: a -> a Source #

Instances

Ways FW Source # 

Methods

oposite :: FW -> FW Source #

Ways LRS Source # 

Methods

oposite :: LRS -> LRS Source #

data LRS Source #

Constructors

L

Left move

S

No move

R

Right move

Instances

Bounded LRS Source # 

Methods

minBound :: LRS #

maxBound :: LRS #

Eq LRS Source # 

Methods

(==) :: LRS -> LRS -> Bool #

(/=) :: LRS -> LRS -> Bool #

Ord LRS Source # 

Methods

compare :: LRS -> LRS -> Ordering #

(<) :: LRS -> LRS -> Bool #

(<=) :: LRS -> LRS -> Bool #

(>) :: LRS -> LRS -> Bool #

(>=) :: LRS -> LRS -> Bool #

max :: LRS -> LRS -> LRS #

min :: LRS -> LRS -> LRS #

Show LRS Source # 

Methods

showsPrec :: Int -> LRS -> ShowS #

show :: LRS -> String #

showList :: [LRS] -> ShowS #

Ways LRS Source # 

Methods

oposite :: LRS -> LRS Source #

TuringM Tape Symbol LRS Source # 
TuringM Tape [Symbol] LRS Source # 

Methods

moveHead :: LRS -> Tape [Symbol] -> Tape [Symbol] Source #

data FW Source #

Constructors

Dw 
Lf 
Rt 
Up 

Instances

Bounded FW Source # 

Methods

minBound :: FW #

maxBound :: FW #

Eq FW Source # 

Methods

(==) :: FW -> FW -> Bool #

(/=) :: FW -> FW -> Bool #

Show FW Source # 

Methods

showsPrec :: Int -> FW -> ShowS #

show :: FW -> String #

showList :: [FW] -> ShowS #

Ways FW Source # 

Methods

oposite :: FW -> FW Source #

TuringM Tracks Symbol FW Source # 

type Delta a b c = (:->:) a b (b, c) Source #

type MDelta a b c = (:->:) a [b] ([b], [c]) Source #

liftD :: (Ord a, Ord b) => [(a, b, a, b, c)] -> Delta a b c Source #

liftMD :: (Ord a, Ord b) => [(a, [b], a, [b], [c])] -> MDelta a b c Source #

liftDAux :: (Ord a, Ord b) => [(a, b, a, b, c)] -> (:->:) a b (b, c) Source #

class Applicative t => Tapeable t a where Source #

Minimal complete definition

getHead, liftTape

Methods

getHead :: t a -> a Source #

liftTape :: Monoid (t a) => [a] -> t a Source #

Instances

Tapeable Tape Symbol Source #
>>> let tapeLifted = (liftTape "word")::Tape Symbol
>>> tapeLifted
T "" 'w' "ord"
Tapeable Tracks Symbol Source # 
Tapeable Tape [Symbol] Source # 

newtype MultiTape t a Source #

Constructors

MT [t a] 

getMHead :: Tapeable t a => MultiTape t a -> [a] Source #

liftMTape :: (Tapeable t a, Monoid (t a)) => [a] -> MultiTape t a Source #

class (Tapeable t b, Ways w) => TuringM t b w where Source #

Minimal complete definition

moveHead

Methods

moveHead :: Monoid b => w -> t b -> t b Source #

data Model a b c where Source #

Constructors

TS :: Ways c => Delta a b c -> Label a -> Final a -> Model a b c 

data MultiModel a b c where Source #

Constructors

MTS :: Ways c => MDelta a b c -> Label a -> [Final a] -> MultiModel a b c