text-register-machine-0.4.0: A Haskell implementation of the 1# Text Register Machine

Safe HaskellNone

Language.TRM.Base

Contents

Description

An implementation of Lawrence S. Moss' 1# language and Text Register Machine (http://www.indiana.edu/~iulg/trm/).

This module also includes a slightly higher-level language, 1#L, that replaces the forward and backward relative jumps of 1# with labels and goto instructions.

Synopsis

Basic Text Register Machine

Letters and Words

data Letter Source

Typed representation of the 1# letters.

Constructors

One 
Hash 

Instances

newtype Word Source

A wrapper around a list of Letters with an IsString instance, so that literal strings of 1s, #s, and whitespace can be used instead of lists of Ones and Hashes. This requires the -XOverloadedStrings flag.

 loop :: Word
 loop = "1### 11####"

Constructors

W [Letter] 

wordToString :: Word -> StringSource

Convert a Word back into a String.

Registers, Instructions, and Programs

data Instruction Source

Abstract syntax for the primitive 1# instructions.

instructionToString :: Instruction -> StringSource

Convert an Instruction to concrete syntax.

type Program = Vector InstructionSource

A 1# program is a Vector of Instructions.

programToString :: Program -> StringSource

Convert a Program to concrete syntax.

parseProgram :: Word -> Maybe ProgramSource

Parse a Word into a Program; returns Nothing if an invalid instruction is found.

Machine Implementation

data Machine Source

A Machine consists of a Program, a program counter, and a Map from registers to the words they contain.

Constructors

M 

Fields

program :: Program
 
pc :: Int
 
regs :: Map Register Word
 

Instances

step :: Machine -> Either Machine MachineSource

Performs the single Instruction indicated by the program counter, if available. Returns 'Left mach' if a step cannot be performed, and 'Right mach' with an updated Machine otherwise.

run :: Program -> Map Register Word -> Map Register WordSource

Given a Program and the initial state of the registers, return the final state of the registers.

phi :: Word -> [(Register, Word)] -> Maybe WordSource

Wrapper around run that parses the given Word into a Program, and then runs it in the given register state. Returns the value in register 1 once the program halts.

Returns Nothing when either the given Word fails to parse, or if the machine halts abnormally with an invalid program counter or values in registers other than register 1.

Labels and Gotos

Language Definition

type Label = IntSource

Label representation.

data LInstruction Source

Abstract syntax for a variant of 1#, 1#L with labels and gotos instead of forward and backward jumps.

type LProgram = Vector LInstructionSource

A 1#L program is a Vector of LInstructions.

Conversion Between Languages

toLabeledProgram :: Program -> LProgramSource

Convert a 1# Program into a semantically-equivalent 1#L LProgram. May fail with an error if the original Program is non-tidy, that is it contains forward or backward jumps to instructions outside of the program.

fromLabeledProgram :: LProgram -> ProgramSource

Convert a 1#L LProgram into a semantically-equivalent 1# Program. May fail with an error if the LProgram contains duplicate labels, jumps to undefined labels. An error will also occur if the LProgram contains a goto that would translate into a jump of 0 instructions, as this is impossible to express in 1#.

Concrete Syntax and Semantics

class LSymantics repr whereSource

Concrete syntax for 1#L, indexed by backend representation in the typed tagless style (http://okmij.org/ftp/tagless-final/index.html).

Methods

snocOne :: Register -> repr ()Source

Append a 1 to the end of the given Register.

snocHash :: Register -> repr ()Source

Append a # to the end of the given Register.

freshLabel :: repr LabelSource

Return a fresh Label to be used in a call to label or goto.

freshReg :: repr RegisterSource

Return a fresh Register that has not been used so far in the program.

label :: Label -> repr ()Source

Place a Label at the given point in the program. Note that a particular Label may be used only once per program.

goto :: Label -> repr ()Source

Unconditional jump to the given Label.

condSource

Arguments

:: Register

The Register to scrutinize.

-> repr ()

Run if the Register is empty.

-> repr ()

Run if the front of the Register is a 1.

-> repr ()

Run if the front of the Register is a #.

-> repr () 

Case analysis; pops a Letter from the front of the scrutinized Register, if non-empty. Note that in the default backend, new labels are automatically created and placed for the branches of the cond.

Instances

compileL :: Register -> LComp () -> LProgramSource

Compiles an LComp program into an LProgram, with an initial fresh register.

runL :: LComp () -> [(Register, Word)] -> Maybe WordSource

Given an LComp program and an initial register state, and then runs it in the given register state. May return Nothing if the program does not halt cleanly, as with run.

runL' :: LComp () -> [(Register, Word)] -> [(Register, Word)]Source

Given an LComp program and an initial register state, and then runs it in the given register state. May return Nothing if the program does not halt cleanly, as with run.

Useful helpers

do_ :: (LComp () -> LComp () -> LComp ()) -> LComp ()Source

A combinator to cleanly implement looping structures in LComp code.

Takes a function that expects two arguments, continue and break. The body of the function is a block of LComp code that gets repeated whenever continue is run. If break is run, control jumps to the instruction after the call to do_.

freshLabelHere :: (Monad repr, LSymantics repr) => repr LabelSource

Convenience function to create a fresh label and place it at the current position.

Examples

Backwards-Binary Notation

encodeBB :: Integral a => a -> WordSource

Encodes an Integral type into a Word of backwards-binary digits using 1s and #s for 1s and 0s, respectively. Note that the representation of zero is a single # rather than the empty Word.

decodeBB :: Num a => Word -> aSource

Decodes a Word containing backwards-binary digits into a Num type. Fails with an error if the Word is empty.